sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
sed: Output line too long.
'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: '<historical>' 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
|