'From Croquet1.0beta of 24 March 2006 [latest update: #6665] on 26 March 2006 at 6:00:26 pm'! TestCase subclass: #FloatMathPluginTests instanceVariableNames: 'random' classVariableNames: '' poolDictionaries: '' category: 'VMMaker-Plugins'! !FloatMathPluginTests commentStamp: '' prior: 0! FloatMathPluginTests buildSuite run.! !FloatMathPluginTests methodsFor: 'running' stamp: 'ar 3/26/2006 16:52'! makeLargeTestData "self basicNew makeLargeTestData" self makeTestData: 'sin-large.dat' using:[:f| self sin: f] seed: 432567 rounds: 1000000. self makeTestData: 'log-large.dat' using:[:f| self ln: f abs] seed: 432567 rounds: 1000000. self makeTestData: 'sqrt-large.dat' using:[:f| self sqrt: f abs] seed: 432567 rounds: 1000000. self makeTestData: 'atan-large.dat' using:[:f| self arcTan: f] seed: 432567 rounds: 1000000. self makeTestData: 'exp-large.dat' using:[:f| self exp: f] seed: 432567 rounds: 1000000. ! ! !FloatMathPluginTests methodsFor: 'running' stamp: 'ar 3/26/2006 16:52'! makeSmallTestData "self basicNew makeSmallTestData" self makeTestData: 'sin-small.dat' using:[:f| self sin: f] seed: 321567 rounds: 10000. self makeTestData: 'log-small.dat' using:[:f| self ln: f abs] seed: 321567 rounds: 10000. self makeTestData: 'sqrt-small.dat' using:[:f| self sqrt: f abs] seed: 321567 rounds: 10000. self makeTestData: 'atan-small.dat' using:[:f| self arcTan: f] seed: 321567 rounds: 10000. self makeTestData: 'exp-small.dat' using:[:f| self exp: f] seed: 321567 rounds: 10000. ! ! !FloatMathPluginTests methodsFor: 'running' stamp: 'ar 3/26/2006 16:11'! makeTestData: fileName using: aBlock seed: seed rounds: rounds | bytes out float result | bytes := ByteArray new: 8. out := FileStream newFileNamed: fileName. [ out binary. out nextNumber: 4 put: rounds. out nextNumber: 4 put: seed. random := Random seed: seed. float := Float basicNew: 2. 'Creating test data for: ', fileName displayProgressAt: Sensor cursorPoint from: 1 to: rounds during:[:bar| 1 to: rounds do:[:i| i \\ 10000 = 0 ifTrue:[bar value: i]. [1 to: 8 do:[:j| bytes at: j put: (random nextInt: 256)-1]. float basicAt: 1 put: (bytes unsignedLongAt: 1 bigEndian: true). float basicAt: 2 put: (bytes unsignedLongAt: 5 bigEndian: true). float isNaN] whileTrue. result := aBlock value: float. out nextNumber: 4 put: (result basicAt: 1). out nextNumber: 4 put: (result basicAt: 2). ]. ]. ] ensure:[out close]. ! ! !FloatMathPluginTests methodsFor: 'running' stamp: 'ar 3/26/2006 16:58'! runTest: aBlock | bytes out float result | bytes := ByteArray new: 8. out := WriteStream on: ByteArray new. float := Float basicNew: 2. 1 to: 10000 do:[:i| [1 to: 8 do:[:j| bytes at: j put: (random nextInt: 256)-1]. float basicAt: 1 put: (bytes unsignedLongAt: 1 bigEndian: true). float basicAt: 2 put: (bytes unsignedLongAt: 5 bigEndian: true). float isNaN] whileTrue. result := aBlock value: float. out nextNumber: 4 put: (result basicAt: 1). out nextNumber: 4 put: (result basicAt: 2). ]. ^self md5HashMessage: out contents.! ! !FloatMathPluginTests methodsFor: 'running' stamp: 'ar 3/26/2006 14:38'! setUp random := Random seed: 253213.! ! !FloatMathPluginTests methodsFor: 'running' stamp: 'ar 3/26/2006 16:53'! verifyTestData: fileName using: aBlock | rounds seed bytes float result in expected count bits | in := [FileStream readOnlyFileNamed: fileName] on: FileDoesNotExistException do:[:ex| ex return: nil]. in ifNil:[^nil]. count := bits := 0. bytes := ByteArray new: 8. [ in binary. rounds := in nextNumber: 4. seed := in nextNumber: 4. random := Random seed: seed. float := Float basicNew: 2. expected := Float basicNew: 2. 'Verifying test data from: ', fileName displayProgressAt: Sensor cursorPoint from: 1 to: rounds during:[:bar| 1 to: rounds do:[:i| i \\ 10000 = 0 ifTrue:[bar value: i]. [1 to: 8 do:[:j| bytes at: j put: (random nextInt: 256)-1]. float basicAt: 1 put: (bytes unsignedLongAt: 1 bigEndian: true). float basicAt: 2 put: (bytes unsignedLongAt: 5 bigEndian: true). float isNaN] whileTrue. result := aBlock value: float. expected basicAt: 1 put: (in nextNumber: 4). expected basicAt: 2 put: (in nextNumber: 4). ((expected isNaN and:[result isNaN]) or:[expected = result]) ifFalse:[ (expected basicAt: 1) = (result basicAt: 1) ifFalse:[self error: 'Verification failure']. count := count + 1. bits := bits + ((expected basicAt: 2) - (result basicAt: 2)) abs. ]. ]. ]. ] ensure:[in close]. self assert: count = 0. "all the same"! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:42'! testArcCos | hash | hash := self runTest:[:f| self arcCos: f]. self assert: hash = 175366936335278026567589867783483480383! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:44'! testArcCosH | hash | hash := self runTest:[:f| self arcCosH: f]. self assert: hash = 6724426144112251941037505276242428134! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:43'! testArcSin | hash | hash := self runTest:[:f| self arcSin: f]. self assert: hash = 27372132577303862731837100895783885417! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:42'! testArcSinH | hash | hash := self runTest:[:f| self arcSinH: f]. self assert: hash = 255911863578190171815115260235896145802! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:43'! testArcTan | hash | hash := self runTest:[:f| self arcTan: f]. self assert: hash = 17311773710959114634056077345168823659! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:51'! testArcTan2 | hash | hash := self runTest:[:f| self arcTan2: f with: f]. self assert: hash = 287068347279655848752274030373495709564! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:44'! testArcTanH | hash | hash := self runTest:[:f| self arcTanH: f]. self assert: hash = 295711907369004359459882231908879164929! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:45'! testCos | hash | hash := self runTest:[:f| self cos: f]. self assert: hash = 110207739557966732640546618158077332978! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:42'! testCosH | hash | hash := self runTest:[:f| self cosH: f]. self assert: hash = 139309299067563830037108641802292492276! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 14:27'! testExp | hash | hash := self runTest:[:f| self exp: f]. self assert: hash = 264681209343177480335132131244505189510! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 14:27'! testFloatAt | hash flt | flt := FloatArray new: 1. hash := self runTest:[:f| flt at: 1 put: f. flt at: 1]. self assert: hash = 80498428122197125691266588764018905399! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 14:27'! testFraction | hash | hash := self runTest:[:f| self fractionPart: f]. self assert: hash = 320444785026869345695277323179170692004! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:51'! testHypot | hash | hash := self runTest:[:f| self hypot: f with: f+1]. self assert: hash = 217113721886532765853628735806816720346! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 14:27'! testLog | hash | hash := self runTest:[:f| self ln: f abs]. self assert: hash = 24389651894375564945708989023746058645! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:42'! testLog10 | hash | hash := self runTest:[:f| self log10: f abs]. self assert: hash = 135564553959509933253581837789050718785! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:44'! testSin | hash | hash := self runTest:[:f| self sin: f]. self assert: hash = 290162321010315440569513182938961037473! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:44'! testSinH | hash | hash := self runTest:[:f| self sinH: f]. self assert: hash = 146029709156303766079448006055284064911! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 14:28'! testSqrt | hash | hash := self runTest:[:f| self sqrt: f abs]. self assert: hash = 112236588358122834093969606123302196127! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:45'! testTan | hash | hash := self runTest:[:f| self tan: f]. self assert: hash = 169918898922109300293069449425089094780! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 17:43'! testTanH | hash | hash := self runTest:[:f| self tanH: f]. self assert: hash = 15738508136206638425252880299326548123! ! !FloatMathPluginTests methodsFor: 'tests' stamp: 'ar 3/26/2006 14:28'! testTimesTwoPower | hash | hash := self runTest:[:f| self timesTwoPower: f with: (random nextInt: 200) - 100]. self assert: hash = 278837335583284459890979576373223649870.! ! !FloatMathPluginTests methodsFor: 'data' stamp: 'ar 3/26/2006 17:56'! testAtanData self verifyTestData: 'atan-small.dat' using:[:f| self arcTan: f]. self verifyTestData: 'atan-large.dat' using:[:f| self arcTan: f]. ! ! !FloatMathPluginTests methodsFor: 'data' stamp: 'ar 3/26/2006 17:56'! testExpData self verifyTestData: 'exp-small.dat' using:[:f| self exp: f]. self verifyTestData: 'exp-large.dat' using:[:f| self exp: f]. ! ! !FloatMathPluginTests methodsFor: 'data' stamp: 'ar 3/26/2006 17:56'! testLogData self verifyTestData: 'log-small.dat' using:[:f| self ln: f abs]. self verifyTestData: 'log-large.dat' using:[:f| self ln: f abs]. ! ! !FloatMathPluginTests methodsFor: 'data' stamp: 'ar 3/26/2006 17:56'! testSinData self verifyTestData: 'sin-small.dat' using:[:f| self sin: f]. self verifyTestData: 'sin-large.dat' using:[:f| self sin: f]. ! ! !FloatMathPluginTests methodsFor: 'data' stamp: 'ar 3/26/2006 17:56'! testSqrtData self verifyTestData: 'sqrt-small.dat' using:[:f| self sqrt: f abs]. self verifyTestData: 'sqrt-large.dat' using:[:f| self sqrt: f abs].! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:34'! arcCosH: f ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:34'! arcCos: f ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:34'! arcSinH: f ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:34'! arcSin: f ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:35'! arcTan2: value with: arg ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:35'! arcTanH: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 14:29'! arcTan: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:35'! cosH: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:35'! cos: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 14:29'! exp: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 14:29'! fractionPart: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:36'! hypot: x with: y ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:24'! ln: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:41'! log10: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:37'! sinH: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 14:29'! sin: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 14:29'! sqrt: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:37'! tanH: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 17:37'! tan: value ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'math' stamp: 'ar 3/26/2006 14:29'! timesTwoPower: f with: arg ^self primitiveFailed! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! md5HashMessage: aStringOrByteArray ^ self md5HashStream: (ReadStream on: aStringOrByteArray asByteArray) ! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! md5HashStream: aStream | start buffer bytes sz n words hash large | hash := Array with: 16r67452301 with: 16rEFCDAB89 with: 16r98BADCFE with: 16r10325476. words := Array new: 16. buffer := ByteArray new: 64. start _ aStream position. [aStream atEnd] whileFalse: [ bytes _ aStream nextInto: buffer. (bytes size < 64 or:[aStream atEnd]) ifTrue:[ sz := bytes size. buffer replaceFrom: 1 to: sz with: bytes startingAt: 1. buffer from: sz+1 to: buffer size put: 0. sz < 56 ifTrue:[ buffer at: sz + 1 put: 128. "trailing bit" ] ifFalse:[ "not enough room for the length, so just pad this one, then..." sz < 64 ifTrue:[buffer at: sz + 1 put: 128]. 1 to: 16 do:[:i| words at: i put: (buffer unsignedLongAt: i*4-3 bigEndian: false)]. self md5Transform: words hash: hash. "process one additional block of padding ending with the length" buffer atAllPut: 0. sz = 64 ifTrue: [buffer at: 1 put: 128]. ]. "Fill in the final 8 bytes with the 64-bit length in bits." n _ (aStream position - start) * 8. 7 to: 0 by: -1 do:[:i| buffer at: (buffer size - i) put: ((n bitShift: 7-i*-8) bitAnd: 255)]. ]. 1 to: 16 do:[:i| words at: i put: (buffer unsignedLongAt: i*4-3 bigEndian: false)]. self md5Transform: words hash: hash. ]. bytes := ByteArray new: 16. bytes unsignedLongAt: 1 put: (hash at: 4) bigEndian: true. bytes unsignedLongAt: 5 put: (hash at: 3) bigEndian: true. bytes unsignedLongAt: 9 put: (hash at: 2) bigEndian: true. bytes unsignedLongAt: 13 put: (hash at: 1) bigEndian: true. large := LargePositiveInteger new: 16. 1 to: 16 do:[:i| large digitAt: i put: (bytes at: i)]. ^large normalize! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! md5Transform: in hash: hash "This adds the incoming words to the existing hash" | a b c d | a := hash at: 1. b := hash at: 2. c := hash at: 3. d := hash at: 4. a := self step1: a x: b y: c z: d data: (in at: 1) add: 16rD76AA478 shift: 7. d := self step1: d x: a y: b z: c data: (in at: 2) add: 16rE8C7B756 shift: 12. c := self step1: c x: d y: a z: b data: (in at: 3) add: 16r242070DB shift: 17. b := self step1: b x: c y: d z: a data: (in at: 4) add: 16rC1BDCEEE shift: 22. a := self step1: a x: b y: c z: d data: (in at: 5) add: 16rF57C0FAF shift: 7. d := self step1: d x: a y: b z: c data: (in at: 6) add: 16r4787C62A shift: 12. c := self step1: c x: d y: a z: b data: (in at: 7) add: 16rA8304613 shift: 17. b := self step1: b x: c y: d z: a data: (in at: 8) add: 16rFD469501 shift: 22. a := self step1: a x: b y: c z: d data: (in at: 9) add: 16r698098D8 shift: 7. d := self step1: d x: a y: b z: c data: (in at: 10) add: 16r8B44F7AF shift: 12. c := self step1: c x: d y: a z: b data: (in at: 11) add: 16rFFFF5BB1 shift: 17. b := self step1: b x: c y: d z: a data: (in at: 12) add: 16r895CD7BE shift: 22. a := self step1: a x: b y: c z: d data: (in at: 13) add: 16r6B901122 shift: 7. d := self step1: d x: a y: b z: c data: (in at: 14) add: 16rFD987193 shift: 12. c := self step1: c x: d y: a z: b data: (in at: 15) add: 16rA679438E shift: 17. b := self step1: b x: c y: d z: a data: (in at: 16) add: 16r49B40821 shift: 22. a := self step2: a x: b y: c z: d data: (in at: 2) add: 16rF61E2562 shift: 5. d := self step2: d x: a y: b z: c data: (in at: 7) add: 16rC040B340 shift: 9. c := self step2: c x: d y: a z: b data: (in at: 12) add: 16r265E5A51 shift: 14. b := self step2: b x: c y: d z: a data: (in at: 1) add: 16rE9B6C7AA shift: 20. a := self step2: a x: b y: c z: d data: (in at: 6) add: 16rD62F105D shift: 5. d := self step2: d x: a y: b z: c data: (in at: 11) add: 16r02441453 shift: 9. c := self step2: c x: d y: a z: b data: (in at: 16) add: 16rD8A1E681 shift: 14. b := self step2: b x: c y: d z: a data: (in at: 5) add: 16rE7D3FBC8 shift: 20. a := self step2: a x: b y: c z: d data: (in at: 10) add: 16r21E1CDE6 shift: 5. d := self step2: d x: a y: b z: c data: (in at: 15) add: 16rC33707D6 shift: 9. c := self step2: c x: d y: a z: b data: (in at: 4) add: 16rF4D50D87 shift: 14. b := self step2: b x: c y: d z: a data: (in at: 9) add: 16r455A14ED shift: 20. a := self step2: a x: b y: c z: d data: (in at: 14) add: 16rA9E3E905 shift: 5. d := self step2: d x: a y: b z: c data: (in at: 3) add: 16rFCEFA3F8 shift: 9. c := self step2: c x: d y: a z: b data: (in at: 8) add: 16r676F02D9 shift: 14. b := self step2: b x: c y: d z: a data: (in at: 13) add: 16r8D2A4C8A shift: 20. a := self step3: a x: b y: c z: d data: (in at: 6) add: 16rFFFA3942 shift: 4. d := self step3: d x: a y: b z: c data: (in at: 9) add: 16r8771F681 shift: 11. c := self step3: c x: d y: a z: b data: (in at: 12) add: 16r6D9D6122 shift: 16. b := self step3: b x: c y: d z: a data: (in at: 15) add: 16rFDE5380C shift: 23. a := self step3: a x: b y: c z: d data: (in at: 2) add: 16rA4BEEA44 shift: 4. d := self step3: d x: a y: b z: c data: (in at: 5) add: 16r4BDECFA9 shift: 11. c := self step3: c x: d y: a z: b data: (in at: 8) add: 16rF6BB4B60 shift: 16. b := self step3: b x: c y: d z: a data: (in at: 11) add: 16rBEBFBC70 shift: 23. a := self step3: a x: b y: c z: d data: (in at: 14) add: 16r289B7EC6 shift: 4. d := self step3: d x: a y: b z: c data: (in at: 1) add: 16rEAA127FA shift: 11. c := self step3: c x: d y: a z: b data: (in at: 4) add: 16rD4EF3085 shift: 16. b := self step3: b x: c y: d z: a data: (in at: 7) add: 16r04881D05 shift: 23. a := self step3: a x: b y: c z: d data: (in at: 10) add: 16rD9D4D039 shift: 4. d := self step3: d x: a y: b z: c data: (in at: 13) add: 16rE6DB99E5 shift: 11. c := self step3: c x: d y: a z: b data: (in at: 16) add: 16r1FA27CF8 shift: 16. b := self step3: b x: c y: d z: a data: (in at: 3) add: 16rC4AC5665 shift: 23. a := self step4: a x: b y: c z: d data: (in at: 1) add: 16rF4292244 shift: 6. d := self step4: d x: a y: b z: c data: (in at: 8) add: 16r432AFF97 shift: 10. c := self step4: c x: d y: a z: b data: (in at: 15) add: 16rAB9423A7 shift: 15. b := self step4: b x: c y: d z: a data: (in at: 6) add: 16rFC93A039 shift: 21. a := self step4: a x: b y: c z: d data: (in at: 13) add: 16r655B59C3 shift: 6. d := self step4: d x: a y: b z: c data: (in at: 4) add: 16r8F0CCC92 shift: 10. c := self step4: c x: d y: a z: b data: (in at: 11) add: 16rFFEFF47D shift: 15. b := self step4: b x: c y: d z: a data: (in at: 2) add: 16r85845DD1 shift: 21. a := self step4: a x: b y: c z: d data: (in at: 9) add: 16r6FA87E4F shift: 6. d := self step4: d x: a y: b z: c data: (in at: 16) add: 16rFE2CE6E0 shift: 10. c := self step4: c x: d y: a z: b data: (in at: 7) add: 16rA3014314 shift: 15. b := self step4: b x: c y: d z: a data: (in at: 14) add: 16r4E0811A1 shift: 21. a := self step4: a x: b y: c z: d data: (in at: 5) add: 16rF7537E82 shift: 6. d := self step4: d x: a y: b z: c data: (in at: 12) add: 16rBD3AF235 shift: 10. c := self step4: c x: d y: a z: b data: (in at: 3) add: 16r2AD7D2BB shift: 15. b := self step4: b x: c y: d z: a data: (in at: 10) add: 16rEB86D391 shift: 21. a := (a + (hash at: 1)) bitAnd: 16rFFFFFFFF. hash at: 1 put: a. b := (b + (hash at: 2)) bitAnd: 16rFFFFFFFF. hash at: 2 put: b. c := (c + (hash at: 3)) bitAnd: 16rFFFFFFFF. hash at: 3 put: c. d := (d + (hash at: 4)) bitAnd: 16rFFFFFFFF. hash at: 4 put: d. ^hash! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! rotate: value by: amount "Rotate value left by amount" | lowMask highMask | lowMask := (1 bitShift: 32-amount) - 1. highMask := 16rFFFFFFFF - lowMask. ^((value bitAnd: lowMask) bitShift: amount) + ((value bitAnd: highMask) bitShift: amount-32)! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! step1: w x: x y: y z: z data: data add: add shift: s "First step in MD5 transformation" | f result | f := z bitXor: (x bitAnd: (y bitXor: z)). result := w + f + data + add. result := self rotate: result by: s. ^result + x bitAnd: 16rFFFFFFFF! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! step2: w x: x y: y z: z data: data add: add shift: s "First step in MD5 transformation" | f result | f := y bitXor: (z bitAnd: (x bitXor: y)). result := w + f + data + add. result := self rotate: result by: s. ^result + x bitAnd: 16rFFFFFFFF! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! step3: w x: x y: y z: z data: data add: add shift: s "First step in MD5 transformation" | f result | f := (x bitXor: y) bitXor: z. result := w + f + data + add. result := self rotate: result by: s. ^result + x bitAnd: 16rFFFFFFFF! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:19'! step4: w x: x y: y z: z data: data add: add shift: s "First step in MD5 transformation" | f result | f := y bitXor: (x bitOr: (z bitXor: 16rFFFFFFFF)). result := w + f + data + add. result := self rotate: result by: s. ^result + x bitAnd: 16rFFFFFFFF! ! !FloatMathPluginTests methodsFor: 'md5' stamp: 'ar 3/26/2006 15:20'! testMD5 self assert: (self md5HashMessage: 'a') = 16r0CC175B9C0F1B6A831C399E269772661. self assert: (self md5HashMessage: 'abc') = 16r900150983CD24FB0D6963F7D28E17F72. self assert: (self md5HashMessage: 'message digest') = 16rF96B697D7CB7938D525A2F31AAF161D0. self assert: (self md5HashMessage: 'abcdefghijklmnopqrstuvwxyz') = 16rC3FCD3D76192E4007DFB496CCA67E13B. self assert: (self md5HashMessage: 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789') = 16rD174AB98D277D9F5A5611C2C9F419D9F. self assert: (self md5HashMessage: '12345678901234567890123456789012345678901234567890123456789012345678901234567890') = 16r57EDF4A22BE3C955AC49DA2E2107B67A.! !