Levente Uzonyi uploaded a new version of Kernel to project The Inbox:
http://source.squeak.org/inbox/Kernel-ul.903.mcz ==================== Summary ==================== Name: Kernel-ul.903 Author: ul Time: 15 February 2015, 9:57:57.503 pm UUID: f1522d00-538e-45d7-a988-e541ea56db56 Ancestors: Kernel-nice.902 Introduced MTRandom, an implementation of the 32-bit Mersenne Twister PRNG. It includes a version optimized for Squeak, which is used by default. It's a possible replacement for Random. Removed LargePositiveInteger >> #atRandom:, since it's something that Random >> #nextInt: should do. Alternatively it can do something different later (eg send #nextLargeInt:). This is for review-only. If we decide to use this generator, then Random has to be replaced with this. After loading, the generator will only used by ThreadSafeRandom class >> #default. If you want to replace all existing generators in the image, then you can use the following snippet: | old new | old := Random allInstances. new := old collect: [ :each | MTRandom new ]. old elementsForwardIdentityTo: new =============== Diff against Kernel-nice.902 =============== Item was removed: - ----- Method: LargePositiveInteger>>atRandom: (in category 'truncation and round off') ----- - atRandom: aGenerator - "Answer a random integer from 1 to self picked from aGenerator." - - | chunkByteLength chunkBitLength chunkCount chunkMax bigRandomInteger | - chunkByteLength := 3. - chunkBitLength := chunkByteLength * 8. - chunkCount := - self highBitOfMagnitude + chunkBitLength - 1 // chunkBitLength "self would fit in that many chunks..." - + 2. "and two more chunks (48 bits) so as to have a pretty fair distribution" - chunkMax := 1<<chunkBitLength-1. - - "fill a big random integer by chunks of 3 bytes (24 bits)" - bigRandomInteger := self class new: chunkCount*chunkByteLength neg: false. - 0 to: chunkCount*chunkByteLength - 1 by: chunkByteLength do: [:byteOffset | - | chunk | - chunk := (aGenerator nextInt: chunkMax) - 1. - 1 to: chunkByteLength do: [:byteIndex | - bigRandomInteger digitAt: byteOffset + byteIndex put: (chunk digitAt: byteIndex)]]. - - ^self * bigRandomInteger >> (chunkCount * chunkBitLength) + 1! Item was added: + Object subclass: #MTRandom + instanceVariableNames: 'states index parameters' + classVariableNames: '' + poolDictionaries: '' + category: 'Kernel-Numbers'! + + !MTRandom commentStamp: 'ul 2/15/2015 15:02' prior: 0! + I implement the 32-bit version of the Mersenne Twister PRNG, based on http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/ARTICLES/mt.pdf . Alternatively the w parameter (number of bits per word) can be less than 32, but it should be at least 27. + + Instance Variables + index: <Integer> + parameters: <MTRandomParameters> + states: <Array> + + index + - the index of the state, which should be used to generate the next random integer value + + parameters + - an MTRandomParameters instance which defines the parameters to be used with this genetator. Must be set before the seed is defined. + + states + - a WordArray holding the internal state of the generator + ! Item was added: + ----- Method: MTRandom class>>new (in category 'instance creation') ----- + new + + | seed | + seed := Time primUTCMicrosecondClock. + seed = 0 ifTrue: [ seed := Time millisecondClockValue ]. + ^self seed: seed! Item was added: + ----- Method: MTRandom class>>parameters:seed: (in category 'instance creation') ----- + parameters: anMTRandomParameters seed: anInteger + + ^self basicNew + parameters: anMTRandomParameters seed: anInteger; + yourself! Item was added: + ----- Method: MTRandom class>>seed: (in category 'instance creation') ----- + seed: anInteger + + ^self + parameters: MTRandomParameters mt521b30 + seed: anInteger! Item was added: + ----- Method: MTRandom>>check: (in category 'compatibility - die rolling') ----- + check: nDice + "Roll some dice, WoD-style." + + ^ self check: nDice difficulty: 6! Item was added: + ----- Method: MTRandom>>check:against: (in category 'compatibility - die rolling') ----- + check: nAttack against: nDefend + "Roll some dice, WoD-style." + + ^ self check: nAttack against: nDefend difficulty: 6! Item was added: + ----- Method: MTRandom>>check:against:difficulty: (in category 'compatibility - die rolling') ----- + check: nAttack against: nDefend difficulty: diff + "Roll some dice, WoD-style." + + | attacks defends | + attacks := self check: nAttack difficulty: diff. + attacks < 0 ifTrue: [^ attacks]. + defends := self check: nDefend difficulty: diff. + ^ attacks - defends min: 0! Item was added: + ----- Method: MTRandom>>check:difficulty: (in category 'compatibility - die rolling') ----- + check: nDice difficulty: diff + "Roll some dice, WoD-style." + + | result | + result := 0. + nDice timesRepeat: + [ | die | + (die := self nextInt: 10) = 1 + ifTrue: [result := result - 1] + ifFalse: [die >= diff ifTrue: [result := result + 1]]]. + ^ result! Item was added: + ----- Method: MTRandom>>diceToken: (in category 'compatibility - die rolling') ----- + diceToken: stream + "Private. Mini scanner, see #roll:" + + stream atEnd ifTrue: [^ nil]. + stream peek isDigit ifTrue: [^ Number readFrom: stream]. + ^ stream next asLowercase! Item was added: + ----- Method: MTRandom>>generate (in category 'private') ----- + generate + "Generate untempered numbers into the states variable, and reset the index to 1." + + parameters generate: states. + index := 1! Item was added: + ----- Method: MTRandom>>next (in category 'accessing') ----- + next + "Answer a random 53-bit Float from the [0, 1) interval. The implementation assumes that the w parameter is between 27 and 53." + + | multiplier | + multiplier := parameters wFloatMultiplier. + ^self nextValue asFloat * multiplier + (self nextValue bitAnd: multiplier - 1) / 9.007199254740992e15 "(1 << 53) asFloat"! Item was added: + ----- Method: MTRandom>>next: (in category 'compatibility') ----- + next: anInteger + "To be exchangable with Random." + + ^self next: anInteger into: (Array new: anInteger)! Item was added: + ----- Method: MTRandom>>next:into: (in category 'compatibility') ----- + next: anInteger into: anArray + "To be exchangable with Random." + + 1 to: anInteger do: [ :index | anArray at: index put: self next ]. + ^anArray! Item was added: + ----- Method: MTRandom>>nextInt: (in category 'accessing') ----- + nextInt: anInteger + "Answer a random integer value from the interval [1, anInteger]" + + anInteger strictlyPositive ifFalse: [ self error: 'Range must be positive' ]. + anInteger isLarge ifTrue: [ ^self nextLargeInt: anInteger ]. + "Here we assume that the w parameter is at least 30. Using any less is a waste." + anInteger isPowerOfTwo ifTrue: [ ^(self nextValue bitAnd: anInteger - 1) + 1 ]. + ^(self next * anInteger) truncated + 1! Item was added: + ----- Method: MTRandom>>nextLargeInt: (in category 'private') ----- + nextLargeInt: anInteger + + | byteCount bigRandom remainder remainingBits i | + byteCount := anInteger digitLength + 4. + bigRandom := LargePositiveInteger new: byteCount. + remainder := remainingBits := 0. + i := 1. + [ i <= byteCount ] whileTrue: [ + remainingBits >= 8 + ifTrue: [ + bigRandom at: i put: (remainder bitAnd: 16rFF). + remainder := remainder bitShift: -8. + remainingBits := remainingBits - 8. + i := i + 1 ] + ifFalse: [ + remainingBits = 0 + ifTrue: [ remainder := self nextValue ] + ifFalse: [ + | newRandom | + newRandom := self nextValue. "Assume that at least 8 new bits are generated" + bigRandom at: i put: (remainder bitShift: 8 - remainingBits) + + (newRandom bitAnd: (1 bitShift: 8 - remainingBits) - 1). + i := i + 1. + remainder := newRandom bitShift: 0 - remainingBits ]. + remainingBits := parameters w - remainingBits ] ]. + ^(anInteger * bigRandom bitShift: -8 * byteCount) + 1 + ! Item was added: + ----- Method: MTRandom>>nextValue (in category 'private') ----- + nextValue + "Answer a random integer between 0 and wordMask, and increment the index." + + | result | + result := states at: index. + result isLarge + ifTrue: [ result := parameters temperLarge: result ] + ifFalse: [ result := parameters temperSmall: result ]. + (index := index + 1) > states size ifTrue: [ self generate ]. + ^result! Item was added: + ----- Method: MTRandom>>parameters:seed: (in category 'initialization') ----- + parameters: anMTRandomParameters seed: anInteger + "Initialize the generator for the given parameters, and seed." + + parameters := anMTRandomParameters. + self seed: anInteger! Item was added: + ----- Method: MTRandom>>roll: (in category 'compatibility - die rolling') ----- + roll: diceString + "Roll some dice, DnD-style, according to this mini-grammar: + dice := epxr {pm expr} + pm := '+' | '-' + expr := num | num dD | dD numP | num dD numP + dD := 'd' | 'D' + num := digit+ + numP := num | '%'" + + | stream op result | + stream := diceString readStream. + result := 0. + op := #+. + [ | res range dice token | + token := self diceToken: stream. + token isNumber + ifTrue: [dice := token. + token := self diceToken: stream] + ifFalse: [token == $d + ifTrue: [dice := 1] + ifFalse: [res := 0]]. + token == $d + ifTrue: [token := self diceToken: stream. + token isNumber + ifTrue: [range := token. + token := self diceToken: stream] + ifFalse: [token == $% + ifTrue: [range := 100. + token := self diceToken: stream] + ifFalse: [range := 6]]. + res := 0. + dice timesRepeat: [res := res + (self nextInt: range)]]. + result := result perform: op with: res. + token ifNil: [^ result]. + (token == $+ or: [token == $-]) + ifFalse: [self error: 'unknown token ' , token]. + op := token asSymbol] repeat! Item was added: + ----- Method: MTRandom>>seed: (in category 'initialization') ----- + seed: anInteger + "Initialize the generator for the given seed." + + states := parameters createStatesArrayForSeed: anInteger. + self generate! Item was added: + Object subclass: #MTRandomParameters + instanceVariableNames: 'p w a m b c uDiv sMul tMul lDiv upperMask lowerMask wordMask n l u s t bShifted cShifted r wFloatMultiplier' + classVariableNames: 'MT19937b32 MT521b30 MT521b31 MT521b32' + poolDictionaries: '' + category: 'Kernel-Numbers'! + + !MTRandomParameters commentStamp: 'ul 2/15/2015 03:13' prior: 0! + I provide the parameters for MTRandom instances. Once initialized, my values must not be changed, because they are shared among multiple MTRandom instances. + + Instance Variables + a: <Integer> + b: <Integer> + bShifted: <Integer> + c: <Integer> + cShifted: <Integer> + l: <Integer> + lDiv: <Integer> + lowerMask: <Integer> + m: <Integer> + n: <Integer> + p: <Integer> + r: <Integer> + s: <Integer> + sMul: <Integer> + t: <Integer> + tMul: <ObjeIntegerct> + u: <Integer> + uDiv: <Integer> + upperMask: <Integer> + w: <Integer> + wFloatMultiplier: <Integer> + wordMask: <Integer> + + a + - the last row of matrix A + + b + - tempering mask b + + bShifted + - tempering mask b shifted by s. This is a computed value. + + c + - tempering mask c + + cShifted + - tempering mask c shifted by t. This is a computed value. + + l + - the bits used for lower shifts. Its value must be negative. + + lDiv + - this number can be used to replace shifting by l with a division. This is a computed value. + + lowerMask + - the mask for the low r bits + + m + - the middle term + + n + - the number of words used in the state array. This is a computed value. + + p + - the exponent of the period of the generator. 2^p-1 must be a mersenne prime, therefore p must be a prime. + + r + - the number of set bits in the lowerMask. This is a computed value. + + s + - the shifts used after applying the tempering mask b + + sMul + - this number can be used to replace shifting by s with a multiplication. This is a computed value. + + t + - the shifts used after applying the tempering mask c + + tMul + - this number can be used to replace shifting by t with a multiplication. This is a computed value. + + u + - the bits used for upper shifts. Its value must be negative. + + uDiv + - this number can be used to replace shifting by u with a division. This is a computed value. + + upperMask + - a mask with w - r set bits in the upper region, and r zero bits in the lower region. This is a computed value. + + w + - the number of bits in a word + + wFloatMultiplier + - a multiplier which can create an 53 bit number from a word. This is a computed value. + + wordMask + - a mask with w bits + ! Item was added: + ----- Method: MTRandomParameters class>>initialize (in category 'class initialization') ----- + initialize + " self initialize " + + MT19937b32 := self new initializeForMT19937. + MT521b32 := self new initializeForMT521. + MT521b31 := self new initializeFor31BitsMT521. + MT521b30 := self new initializeFor30BitsMT521.! Item was added: + ----- Method: MTRandomParameters class>>mt19937b32 (in category 'accessing') ----- + mt19937b32 + + ^MT19937b32! Item was added: + ----- Method: MTRandomParameters class>>mt521b30 (in category 'accessing') ----- + mt521b30 + + ^MT521b30! Item was added: + ----- Method: MTRandomParameters class>>mt521b31 (in category 'accessing') ----- + mt521b31 + + ^MT521b31! Item was added: + ----- Method: MTRandomParameters class>>mt521b32 (in category 'accessing') ----- + mt521b32 + + ^MT521b32! Item was added: + ----- Method: MTRandomParameters>>a (in category 'accessing') ----- + a + + ^ a! Item was added: + ----- Method: MTRandomParameters>>b (in category 'accessing') ----- + b + + ^ b! Item was added: + ----- Method: MTRandomParameters>>bShifted (in category 'accessing') ----- + bShifted + + ^ bShifted! Item was added: + ----- Method: MTRandomParameters>>c (in category 'accessing') ----- + c + + ^ c! Item was added: + ----- Method: MTRandomParameters>>cShifted (in category 'accessing') ----- + cShifted + + ^ cShifted! Item was added: + ----- Method: MTRandomParameters>>calculateValues (in category 'private') ----- + calculateValues + " Calculate multipliers, divisors and masks used by the actual implementation. " + + self + assert: p isPrime; + assert: (w between: 27 and: 32); + assert: u < 0; + assert: l < 0. + n := (p / w) ceiling. "The size of the array." + r := n * w - p. "The number of bits in lowerMask" + lDiv := 1 bitShift: l negated. + uDiv := 1 bitShift: u negated. + sMul := 1 bitShift: s. + tMul := 1 bitShift: t. + bShifted := b bitShift: s negated. + cShifted := c bitShift: t negated. + wordMask := 1 bitShift: w - 1. + lowerMask := 1 bitShift: r - 1. + upperMask := wordMask - lowerMask. + wFloatMultiplier := 1 bitShift: (53 - w)! Item was added: + ----- Method: MTRandomParameters>>createStatesArrayForSeed: (in category 'generatring') ----- + createStatesArrayForSeed: anInteger + "Create an array for these parameters and the given seed. Hash the seed if it's not a 32-bit unsigned integer." + + | seed states | + seed := (anInteger between: 0 and: 16rFFFFFFFF) + ifTrue: [ anInteger ] + ifFalse: [ self hashSeed: anInteger ]. + states := Array new: n. + 1 to: n do: [ :i | + states at: i put: (wordMask bitAnd: seed). + seed := 16rFFFFFFFF bitAnd: (16r6C078965 * (seed bitXor: seed // 1073741824 "bitShift: -30") + i) ]. + ^states! Item was added: + ----- Method: MTRandomParameters>>generate: (in category 'generatring') ----- + generate: states + "Generate untempered numbers into the states variable. Choose the best method based on word size." + + wordMask isLarge ifTrue: [ ^self generateLarge: states ]. + ^self generateSmall: states! Item was added: + ----- Method: MTRandomParameters>>generateLarge: (in category 'generatring') ----- + generateLarge: states + "Generate untempered numbers into the states variable. Split up the operation into three parts to avoid the use of #atWrap: for accessing the states array. Optimized for LargeInteger operations." + + | i limit y offset | + "Part 1" + i := 0. + offset := m. + limit := n - offset. + [ (i := i + 1) <= limit ] whileTrue: [ + y := (upperMask bitAnd: (states at: i)) bitOr: (lowerMask bitAnd: (states at: i + 1)). + states + at: i + put: (y even + ifTrue: [ (states at: i + offset) bitXor: y // 2 ] + ifFalse: [ a bitXor: ((states at: i + offset) bitXor: y // 2) ]) ]. + "Part 2" + limit := n - 1. + offset := m - n + 1. + [ (i := i + 1) <= limit ] whileTrue: [ + y := (upperMask bitAnd: (states at: i)) bitOr: (lowerMask bitAnd: (states at: i + 1)). + states + at: i + put: (y even + ifTrue: [ (states at: i + offset) bitXor: y // 2 ] + ifFalse: [ a bitXor: ((states at: i + offset) bitXor: y // 2) ]) ]. + "Part 3" + y := (upperMask bitAnd: (states at: i)) bitOr: (lowerMask bitAnd: (states at: 1)). + states + at: i + put: (y even + ifTrue: [ (states at: m) bitXor: y // 2 ] + ifFalse: [ a bitXor: ((states at: m) bitXor: y // 2) ])! Item was added: + ----- Method: MTRandomParameters>>generateSmall: (in category 'generatring') ----- + generateSmall: states + "Generate untempered numbers into the states variable. Split up the operation into three parts to avoid the use of #atWrap: for accessing the states array. Optimized for SmallInteger operations." + + | i limit y offset | + "Part 1" + i := 0. + offset := m. + limit := n - offset. + [ (i := i + 1) <= limit ] whileTrue: [ + y := (upperMask bitAnd: (states at: i)) bitOr: (lowerMask bitAnd: (states at: i + 1)). + states + at: i + put: ((y bitAnd: 1) = 0 + ifTrue: [ (states at: i + offset) bitXor: (y bitShift: -1) ] + ifFalse: [ a bitXor: ((states at: i + offset) bitXor: (y bitShift: -1)) ]) ]. + "Part 2" + limit := n - 1. + offset := m - n + 1. + [ (i := i + 1) <= limit ] whileTrue: [ + y := (upperMask bitAnd: (states at: i)) bitOr: (lowerMask bitAnd: (states at: i + 1)). + states + at: i + put: ((y bitAnd: 1) = 0 + ifTrue: [ (states at: i + offset) bitXor: (y bitShift: -1) ] + ifFalse: [ a bitXor: ((states at: i + offset) bitXor: (y bitShift: -1)) ]) ]. + "Part 3" + y := (upperMask bitAnd: (states at: i)) bitOr: (lowerMask bitAnd: (states at: 1)). + states + at: i + put: ((y bitAnd: 1) = 0 + ifTrue: [ (states at: m) bitXor: (y bitShift: -1) ] + ifFalse: [ a bitXor: ((states at: m) bitXor: (y bitShift: -1)) ])! Item was added: + ----- Method: MTRandomParameters>>hashSeed: (in category 'private') ----- + hashSeed: anInteger + "Use the 32-bit version of the FNV-1a algorithm to hash the seed, and produce a 32-bit unsigned integer." + + | fnvPrime hash | + fnvPrime := 16777619 " 32-bit FVN prime ". + hash := anInteger negative + ifTrue: [ 3490449840 " mix in the sign as (2166136261 bitXor: 2r1010101) * 16777619 bitAnd: 16rFFFFFFFF "] + ifFalse: [ 2166136261 " 32-bit FVN offset basis "]. + 1 to: anInteger digitLength do: [ :index | + hash := 16rFFFFFFFF bitAnd: (hash bitXor: (anInteger digitAt: index)) * fnvPrime ]. + ^hash! Item was added: + ----- Method: MTRandomParameters>>initializeFor30BitsMT521 (in category 'initialize-release') ----- + initializeFor30BitsMT521 + "30-bit MT521 parameters. generated with a modified version of dcmt, ID=4172. http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/DC/dc.html" + + p := 521. + w := 30. + m := 9. + a := 16r2c0b19af. + u := -12. + l := -18. + s := 7. + t := 15. + b := 16r1caf6480. + c := 16r3fcd0000. + self calculateValues + ! Item was added: + ----- Method: MTRandomParameters>>initializeFor31BitsMT521 (in category 'initialize-release') ----- + initializeFor31BitsMT521 + "31-bit MT521 parameters, generated with dcmt, ID=4172. http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/DC/dc.html" + + p := 521. + w := 31. + m := 8. + a := 16r54dc9020. + u := -12. + l := -18. + s := 7. + t := 15. + b := 16r4bbadf80. + c := 16r3dee8000. + self calculateValues! Item was added: + ----- Method: MTRandomParameters>>initializeForMT19937 (in category 'initialize-release') ----- + initializeForMT19937 + "32-bit MT19937 parameters as in http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/ARTICLES/mt.pdf on page 8." + + p := 19937. + w := 32. + m := 397. + a := 16r9908B0DF. + u := -11. + l := -18. + s := 7. + t := 15. + b := 16r9D2C5680. + c := 16rEFC60000. + self calculateValues! Item was added: + ----- Method: MTRandomParameters>>initializeForMT521 (in category 'initialize-release') ----- + initializeForMT521 + "32-bit MT521 parameters, generated with dcmt, ID=4172. http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/DC/dc.html" + + p := 521. + w := 32. + m := 8. + a := 16rF0C1E1B8. + u := -12. + l := -18. + s := 7. + t := 15. + b := 16r74BD5f80. + c := 16rFFD50000. + self calculateValues! Item was added: + ----- Method: MTRandomParameters>>l (in category 'accessing') ----- + l + + ^ l! Item was added: + ----- Method: MTRandomParameters>>lDiv (in category 'accessing') ----- + lDiv + + ^ lDiv! Item was added: + ----- Method: MTRandomParameters>>lowerMask (in category 'accessing') ----- + lowerMask + + ^ lowerMask! Item was added: + ----- Method: MTRandomParameters>>m (in category 'accessing') ----- + m + + ^ m! Item was added: + ----- Method: MTRandomParameters>>n (in category 'accessing') ----- + n + + ^ n! Item was added: + ----- Method: MTRandomParameters>>r (in category 'accessing') ----- + r + + ^ r! Item was added: + ----- Method: MTRandomParameters>>s (in category 'accessing') ----- + s + + ^ s! Item was added: + ----- Method: MTRandomParameters>>sMul (in category 'accessing') ----- + sMul + + ^ sMul! Item was added: + ----- Method: MTRandomParameters>>t (in category 'accessing') ----- + t + + ^ t! Item was added: + ----- Method: MTRandomParameters>>tMul (in category 'accessing') ----- + tMul + + ^ tMul! Item was added: + ----- Method: MTRandomParameters>>temperLarge: (in category 'tempering') ----- + temperLarge: anInteger + " Optimized for 32-bit LargeInteger operations. " + + | y | + y := anInteger bitXor: anInteger // uDiv. + y := y bitXor: ((y bitAnd: bShifted) * sMul). + y := y bitXor: ((y bitAnd: cShifted) * tMul). + ^y bitXor: y // lDiv! Item was added: + ----- Method: MTRandomParameters>>temperSmall: (in category 'tempering') ----- + temperSmall: anInteger + " Optimized for SmallInteger operations. " + + | y | + y := anInteger bitXor: (anInteger bitShift: u). + y := ((y bitAnd: bShifted) bitShift: s) bitXor: y. + y := ((y bitAnd: cShifted) bitShift: t) bitXor: y. + ^(y bitShift: l) bitXor: y! Item was added: + ----- Method: MTRandomParameters>>u (in category 'accessing') ----- + u + + ^ u! Item was added: + ----- Method: MTRandomParameters>>uDiv (in category 'accessing') ----- + uDiv + + ^ uDiv! Item was added: + ----- Method: MTRandomParameters>>upperMask (in category 'accessing') ----- + upperMask + + ^ upperMask! Item was added: + ----- Method: MTRandomParameters>>w (in category 'accessing') ----- + w + + ^ w! Item was added: + ----- Method: MTRandomParameters>>wFloatMultiplier (in category 'accessing') ----- + wFloatMultiplier + + ^ wFloatMultiplier! Item was added: + ----- Method: MTRandomParameters>>wordMask (in category 'accessing') ----- + wordMask + + ^ wordMask! Item was changed: ----- Method: ThreadSafeRandom class>>default (in category 'accessing') ----- default + ^self value: MTRandom new! - ^self value: Random new! |
Free forum by Nabble | Edit this page |