initial checkin
authorClaus Gittinger <cg@exept.de>
Mon, 16 Jun 2003 11:20:11 +0200
changeset 192 403ba5cd66c4
parent 191 cbfe2c02da13
child 193 6ead28d62b77
initial checkin
RegressionTests__ComplexTest.st
RegressionTests__FloatTest.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/RegressionTests__ComplexTest.st	Mon Jun 16 11:20:11 2003 +0200
@@ -0,0 +1,149 @@
+"{ Package: 'exept:regression' }"
+
+"{ NameSpace: RegressionTests }"
+
+TestCase subclass:#ComplexTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'tests-Regression'
+!
+
+
+!ComplexTest methodsFor:'tests'!
+
+testAddition
+	| c1 c2 |
+
+	self shouldnt: [ c1 := Complex real: 1 imaginary: 2 ] raise: Exception.
+	self shouldnt: [ c2 := Complex real: 3 imaginary: 4 ] raise: Exception.
+
+	self should: [ (c1 + c2) = (Complex real: 4 imaginary: 6) ].
+!
+
+testCreation
+        | c |
+
+        false ifTrue:[
+            "cg: I dont think this has to be known outside complex"
+            "i.e. should it really be allowed to create complex numbers with new ?"
+            self should: [ (c := Complex new) realPart = 0 ].
+            self should: [ c imaginaryPart = 0 ].
+        ].
+        self should: [ (c := Complex real: 1 imaginary: 2) realPart = 1 ].
+        self should: [ c imaginaryPart = 2 ]
+!
+
+testDivision
+	| c1 c2 |
+
+	self shouldnt: [ c1 := Complex real: 2 imaginary: 2 ] raise: Exception.
+	self shouldnt: [ c2 := Complex real: 3 imaginary: 6 ] raise: Exception.
+
+	self should: [ (c1 / c1) = (Complex real: 1 imaginary: 0) ].
+	self should: [ (c1 / c2) = (Complex real: 2/5 imaginary: (-2/15)) ].
+	self should: [ (c2 / c1) = (Complex real: 9/4 imaginary: 3/4) ].
+
+	self should: [ c2 / 3 = (Complex real: 1 imaginary: 2) ].
+	self should: [ c1 / 2 = (Complex real: 1 imaginary: 1) ].
+!
+
+testEquality
+	self should: [ 3 = (Complex real: 3 imaginary: 0) ].
+	self should: [ (Complex real: 3 imaginary: 0) = 3 ].
+
+	self should: [ 3.0 = (Complex real: 3 imaginary: 0) ].
+	self should: [ (Complex real: 3 imaginary: 0) = 3.0 ].
+
+	self shouldnt: [ 3 = (Complex real: 3 imaginary: 1) ].
+	self shouldnt: [ (Complex real: 3 imaginary: 1) = 3 ].
+
+	self shouldnt: [ 3.0 = (Complex real: 3 imaginary: 1) ].
+	self shouldnt: [ (Complex real: 3 imaginary: 1) = 3.0 ].
+
+	self should: [ 3 ~= (Complex real: 3 imaginary: 1) ].
+	self should: [ (Complex real: 3 imaginary: 1) ~= 3 ].
+
+	self should: [ 3.0 ~= (Complex real: 3 imaginary: 1) ].
+	self should: [ (Complex real: 3 imaginary: 1) ~= 3.0 ].
+!
+
+testModulus
+	| c1 c2 |
+
+	"Test case where |a| < |b| in complex number (a + ib)."
+
+	self shouldnt: [ c1 := Complex real: 2 imaginary: 3 ] raise: Exception.
+	self should: [ c1 modulus = (3 * ((1 + ((2 / 3) * (2 / 3))) sqrt)) ].
+
+	"Test case where |a| >= |b| in complex number (a + ib)."
+
+	self shouldnt: [ c2 := Complex real: 4 imaginary: -2 ] raise: Exception.
+	self should: [ c2 modulus = (4 * ((1 + ((-2 / 4) * (-2 / 4))) sqrt)) ].
+!
+
+testMultiplication
+	| c1 c2 |
+
+	self shouldnt: [ c1 := Complex real: 1 imaginary: 2 ] raise: Exception.
+	self shouldnt: [ c2 := Complex real: 3 imaginary: 4 ] raise: Exception.
+
+	self should: [ (c1 * c2) = (Complex real: -5 imaginary: 10) ].
+	self should: [ (c1 * Complex zero) = Complex zero ].
+
+	self should: [ c1 * 5 = (Complex real: 5 imaginary: 10) ].
+	self should: [ c1 * 1.1 = (Complex real: 1.1 imaginary: 2.2) ].
+	self should: [ c1 * (2/3) = (Complex real: 2/3 imaginary: 4/3) ].
+!
+
+testRaisedTo
+	| c |
+
+	self shouldnt: [ c := Complex real: 3 imaginary: 2 ] raise: Exception.
+	self should: [ (c raisedTo: 2) = (c * c) ].
+	self should: [ (c raisedTo: 3) = (c * c * c) ].
+	self should: [ (c raisedTo: 4) = (c * c * c * c) ].
+!
+
+testSqrt
+        | c w |
+
+        self shouldnt: [ c := Complex real: 0 imaginary: 0 ] raise: Exception.
+        self should: [ c sqrt = 0 ].
+
+        self shouldnt: [ c := Complex real: 9 imaginary: 4 ] raise: Exception.
+        "cg: that cannot be tested easily, due to rounding errors"
+        "original" false ifTrue:[
+            self should: [ w := 3 * (((1 + (1 + ((4/9) * (4/9))) sqrt) / 2) sqrt).
+                            c sqrt = (Complex real: w imaginary: 4 / (2 * w)) ].
+        ] ifFalse:[
+            self should: [ |t1 t2 epsilon|
+                            w := 3 * (((1 + (1 + ((4/9) * (4/9))) sqrt) / 2) sqrt).
+                            t1 := c sqrt.
+                            t2 := (Complex real: w imaginary: 4 / (2 * w)).
+                            epsilon := 0.0000001.
+                            (t1 realPart - t2 realPart) < epsilon
+                            and:[ (t1 imaginaryPart - t2 imaginaryPart) < epsilon ]
+                         ].
+        ].
+
+        self shouldnt: [ c := Complex imaginary: -2 ] raise: Exception.
+        "self should: [ c sqrt = (Complex real: 1 imaginary: -1) ].  Should be true, but rounding bites us..."
+        self should: [ (c sqrt realPart - 1) abs < 1.0e-10 ].
+        self should: [ (c sqrt imaginaryPart + 1) abs < 1.0e-10 ].
+!
+
+testSubtraction
+	| c1 c2 |
+
+	self shouldnt: [ c1 := Complex real: 1 imaginary: 2 ] raise: Exception.
+	self shouldnt: [ c2 := Complex real: 3 imaginary: 4 ] raise: Exception.
+
+	self should: [ (c1 - c2) = (Complex real: -2 imaginary: -2) ].
+! !
+
+!ComplexTest class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/RegressionTests__FloatTest.st	Mon Jun 16 11:20:11 2003 +0200
@@ -0,0 +1,430 @@
+"{ Package: 'exept:regression' }"
+
+"{ NameSpace: RegressionTests }"
+
+TestCase subclass:#FloatTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'tests-Regression'
+!
+
+
+!FloatTest methodsFor:'tests'!
+
+test01_Nan
+    "NaN in all avaliable formats."
+
+    |shouldBeNaN|
+
+    shouldBeNaN := 0.0 uncheckedDivide: 0.0.
+    self assert:( shouldBeNaN isMemberOf:Float ).
+    self assert:( shouldBeNaN isNaN ).
+    self assert:( shouldBeNaN isFinite not ).
+
+    shouldBeNaN := 0.0 asShortFloat uncheckedDivide: 0.0 asShortFloat.
+    self assert:( shouldBeNaN isMemberOf:ShortFloat ).
+    self assert:( shouldBeNaN isNaN ).
+    self assert:( shouldBeNaN isFinite not ).
+
+    shouldBeNaN := 0.0 asLongFloat uncheckedDivide: 0.0 asLongFloat.
+    self assert:( shouldBeNaN isMemberOf:LongFloat ).
+    self assert:( shouldBeNaN isNaN ).
+    self assert:( shouldBeNaN isFinite not ).
+
+    shouldBeNaN := 0.0 uncheckedDivide: 0.0.
+    self assert:( shouldBeNaN isNaN ).
+    self assert:( shouldBeNaN asShortFloat isNaN ).
+    self assert:( shouldBeNaN asLongFloat isNaN ).
+
+    shouldBeNaN := 0.0 asShortFloat uncheckedDivide: 0.0.
+    self assert:( shouldBeNaN isNaN ).
+    self assert:( shouldBeNaN asFloat isNaN ).
+    self assert:( shouldBeNaN asLongFloat isNaN ).
+
+    shouldBeNaN := 0.0 asLongFloat uncheckedDivide: 0.0.
+    self assert:( shouldBeNaN isNaN ).
+    self assert:( shouldBeNaN asShortFloat isNaN ).
+    self assert:( shouldBeNaN asLongFloat isNaN ).
+
+    shouldBeNaN := 0.0 uncheckedDivide: 0.0.
+    self should:[ shouldBeNaN asInteger ] raise:DomainError.
+
+"/ mhmh - the following are not true.
+"/    self should:[ shouldBeNaN + 1 ] raise:DomainError.
+"/    self should:[ shouldBeNaN + 1.0 ] raise:DomainError.
+"/    self should:[ shouldBeNaN + 1.0 asShortFloat ] raise:DomainError.
+"/    self should:[ shouldBeNaN + 1.0 asLongFloat ] raise:DomainError.
+"/
+"/    self should:[ shouldBeNaN - 1 ] raise:DomainError.
+"/    self should:[ shouldBeNaN - 1.0 ] raise:DomainError.
+"/    self should:[ shouldBeNaN - 1.0 asShortFloat ] raise:DomainError.
+"/    self should:[ shouldBeNaN - 1.0 asLongFloat ] raise:DomainError.
+
+    "/ but these are:
+    self assert:( shouldBeNaN + 1 ) isNaN.
+    self assert:( shouldBeNaN + 1.0 ) isNaN.
+    self assert:( shouldBeNaN + 1.0 asShortFloat ) isNaN.
+    self assert:( shouldBeNaN + 1.0 asLongFloat ) isNaN.
+
+    self assert:( shouldBeNaN - 1 ) isNaN.
+    self assert:( shouldBeNaN - 1.0 ) isNaN.
+    self assert:( shouldBeNaN - 1.0 asShortFloat ) isNaN.
+    self assert:( shouldBeNaN - 1.0 asLongFloat ) isNaN.
+
+    "
+     self basicNew test01_Nan
+    "
+!
+
+test02_Inf
+    "Infinity in all avaliable formats."
+
+    |check shouldBeInf|
+
+    check := 
+        [:v1 :v2 |
+
+            shouldBeInf := v1 uncheckedDivide: v2.
+
+            self assert:( shouldBeInf isMemberOf:v1 class ).
+            self assert:( shouldBeInf isNaN not ).
+            self assert:( shouldBeInf isFinite not ).
+            self assert:( shouldBeInf isInfinite ).
+            self assert:( shouldBeInf positive ).
+            self assert:( shouldBeInf negative not ).
+            self assert:( shouldBeInf isNegativeInfinity not).
+            self assert:( shouldBeInf isPositiveInfinity ).
+
+            shouldBeInf := v1 negated uncheckedDivide: v2.
+
+            self assert:( shouldBeInf isMemberOf:v1 class ).
+            self assert:( shouldBeInf isNaN not ).
+            self assert:( shouldBeInf isFinite not ).
+            self assert:( shouldBeInf isInfinite ).
+            self assert:( shouldBeInf positive not).
+            self assert:( shouldBeInf negative ).
+            self assert:( shouldBeInf isNegativeInfinity ).
+            self assert:( shouldBeInf isPositiveInfinity not ).
+        ].
+
+    check value: 1.0 value: 0.0.
+    check value: 1.0 asShortFloat value: 0.0 asShortFloat.
+    check value: 1.0 asLongFloat value: 0.0 asLongFloat.
+
+"/ these are not guaranteed to work with uncheckedDivide...
+"/    check value: 1.0 value: 0.0 asShortFloat.
+"/    check value: 1.0 value: 0.0 asLongFloat.
+"/
+"/    check value: 1.0 asShortFloat value: 0.0.
+"/    check value: 1.0 asShortFloat value: 0.0 asLongFloat.
+"/
+"/    check value: 1.0 asLongFloat value: 0.0 asShortFloat.
+"/    check value: 1.0 asLongFloat value: 0.0.
+
+    "
+     self basicNew test02_Inf
+    "
+!
+
+test03_Conversion
+    self assert:( 1.0 asTrueFraction == 1 ).
+    self assert:( 2.0 asTrueFraction == 2 ).
+    self assert:( 4.0 asTrueFraction == 4 ).
+    self assert:( 8.0 asTrueFraction == 8 ).
+    self assert:( 16.0 asTrueFraction == 16 ).
+    self assert:( 1048576.0 asTrueFraction == 1048576 ).
+    self assert:( 0.5 asTrueFraction = (1/2) ).
+    self assert:( 0.25 asTrueFraction = (1/4) ).
+    self assert:( 0.125 asTrueFraction = (1/8) ).
+
+    self assert:( 1.0 asShortFloat asTrueFraction == 1 ).
+    self assert:( 2.0 asShortFloat asTrueFraction == 2 ).
+    self assert:( 4.0 asShortFloat asTrueFraction == 4 ).
+    self assert:( 8.0 asShortFloat asTrueFraction == 8 ).
+    self assert:( 16.0 asShortFloat asTrueFraction == 16 ).
+    self assert:( 1048576.0 asShortFloat asTrueFraction == 1048576 ).
+    self assert:( 0.5 asShortFloat asTrueFraction = (1/2) ).
+    self assert:( 0.25 asShortFloat asTrueFraction = (1/4) ).
+    self assert:( 0.125 asShortFloat asTrueFraction = (1/8) ).
+
+    self assert:( 1.0 asLongFloat asTrueFraction == 1 ).
+    self assert:( 2.0 asLongFloat asTrueFraction == 2 ).
+    self assert:( 4.0 asLongFloat asTrueFraction == 4 ).
+    self assert:( 8.0 asLongFloat asTrueFraction == 8 ).
+    self assert:( 16.0 asLongFloat asTrueFraction == 16 ).
+    self assert:( 1048576.0 asLongFloat asTrueFraction == 1048576 ).
+    self assert:( 0.5 asLongFloat asTrueFraction = (1/2) ).
+    self assert:( 0.25 asLongFloat asTrueFraction = (1/4) ).
+    self assert:( 0.125 asLongFloat asTrueFraction = (1/8) ).
+
+    "
+     self basicNew test03_Conversion
+    "
+!
+
+test04_Arithmetic
+    self assert:( 1.0 + 1.0 ) class == Float.
+    self assert:( 1.0 + 1.0 asShortFloat) class == Float.
+    self assert:( 1.0 + 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 + 1) class == Float.
+
+    self assert:( 1.0 asShortFloat + 1.0 ) class == Float.
+    self assert:( 1.0 asShortFloat + 1.0 asShortFloat) class == ShortFloat.
+    self assert:( 1.0 asShortFloat + 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 asShortFloat + 1) class == ShortFloat.
+
+    self assert:( 1.0 asLongFloat + 1.0 ) class == LongFloat.
+    self assert:( 1.0 asLongFloat + 1.0 asShortFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat + 1.0 asFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat + 1 ) class == LongFloat.
+
+
+    self assert:( 1.0 - 1.0 ) class == Float.
+    self assert:( 1.0 - 1.0 asShortFloat) class == Float.
+    self assert:( 1.0 - 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 - 1) class == Float.
+
+    self assert:( 1.0 asShortFloat - 1.0 ) class == Float.
+    self assert:( 1.0 asShortFloat - 1.0 asShortFloat) class == ShortFloat.
+    self assert:( 1.0 asShortFloat - 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 asShortFloat - 1) class == ShortFloat.
+
+    self assert:( 1.0 asLongFloat - 1.0 ) class == LongFloat.
+    self assert:( 1.0 asLongFloat - 1.0 asShortFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat - 1.0 asFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat - 1 ) class == LongFloat.
+
+
+    self assert:( 1.0 * 1.0 ) class == Float.
+    self assert:( 1.0 * 1.0 asShortFloat) class == Float.
+    self assert:( 1.0 * 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 * 1) class == Float.
+
+    self assert:( 1.0 asShortFloat * 1.0 ) class == Float.
+    self assert:( 1.0 asShortFloat * 1.0 asShortFloat) class == ShortFloat.
+    self assert:( 1.0 asShortFloat * 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 asShortFloat * 1) class == ShortFloat.
+
+    self assert:( 1.0 asLongFloat * 1.0 ) class == LongFloat.
+    self assert:( 1.0 asLongFloat * 1.0 asShortFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat * 1.0 asFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat * 1 ) class == LongFloat.
+
+
+    self assert:( 1.0 / 1.0 ) class == Float.
+    self assert:( 1.0 / 1.0 asShortFloat) class == Float.
+    self assert:( 1.0 / 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 / 1) class == Float.
+
+    self assert:( 1.0 asShortFloat / 1.0 ) class == Float.
+    self assert:( 1.0 asShortFloat / 1.0 asShortFloat) class == ShortFloat.
+    self assert:( 1.0 asShortFloat / 1.0 asLongFloat) class == LongFloat.
+    self assert:( 1.0 asShortFloat / 1) class == ShortFloat.
+
+    self assert:( 1.0 asLongFloat / 1.0 ) class == LongFloat.
+    self assert:( 1.0 asLongFloat / 1.0 asShortFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat / 1.0 asFloat ) class == LongFloat.
+    self assert:( 1.0 asLongFloat / 1 ) class == LongFloat.
+
+    "
+     self basicNew test04_Arithmetic
+    "
+!
+
+test05_Comparing
+    self assert:( 2.0 = 2 ).
+    self assert:( 2.0 = 2.0 asShortFloat ).
+    self assert:( 2.0 = 2.0 asLongFloat ).
+
+    self assert:( 2.0 asShortFloat = 2 ).
+    self assert:( 2.0 asShortFloat = 2.0 asShortFloat ).
+    self assert:( 2.0 asShortFloat = 2.0 asLongFloat ).
+
+    self assert:( 2.0 asLongFloat = 2 ).
+    self assert:( 2.0 asLongFloat = 2.0 asShortFloat ).
+    self assert:( 2.0 asLongFloat = 2.0 asLongFloat ).
+
+    self assert:( 2 asLongFloat = 2 ).
+    self assert:( 2 asLongFloat = 2.0 asShortFloat ).
+    self assert:( 2 asLongFloat = 2.0 asLongFloat ).
+
+    "
+     self basicNew test05_Comparing
+    "
+!
+
+test06_MiscMath
+    #(
+        sqrt
+        exp
+        ln
+        sin
+        cos
+        tan
+        arcSin
+        arcCos
+        arcTan
+    ) do:[:op |
+        self assert:( 0.5 perform:op ) class == Float.
+        self assert:( 0.5 asShortFloat perform:op ) class == Float.
+        self assert:( 0.5 asLongFloat perform:op ) class == LongFloat.
+        self assert:( (0.5 perform:op) - (0.5 asShortFloat perform:op) ) < 0.000001.
+        self assert:( (0.5 perform:op) - (0.5 asLongFloat perform:op) ) < 0.000001.
+        self assert:( (0.5 perform:op) - (0.5 perform:op) asShortFloat ) < 0.000001.
+        self assert:( (0.5 perform:op) - (0.5 perform:op) asLongFloat ) < 0.000001.
+    ]
+
+    "
+     self basicNew test06_MiscMath
+    "
+!
+
+test07_Truncation
+    |check|
+
+    check := [:num |
+        self assert:( num fractionPart + num truncated ) = num.
+        self assert:( num fractionPart + num truncated ) class == num class.
+    ].
+
+    check value:1.6.
+    check value:-1.6.
+
+    check value:1.6 asShortFloat.
+    check value:-1.6 asShortFloat.
+
+    check value:1.6 asLongFloat.
+    check value:-1.6 asLongFloat.
+
+
+    self assert:( 1.6 ceiling ) = 2.
+    self assert:( 1.6 asShortFloat ceiling ) = 2.
+    self assert:( 1.6 asLongFloat ceiling ) = 2.
+
+    self assert:( 1.6 ceilingAsFloat ) = 2.0.
+    self assert:( 1.6 ceilingAsFloat ) class == Float.
+    self assert:( 1.6 asShortFloat ceilingAsFloat ) = 2.0 asShortFloat.
+    self assert:( 1.6 asShortFloat ceilingAsFloat ) class == ShortFloat.
+    self assert:( 1.6 asLongFloat ceilingAsFloat ) = 2.0 asLongFloat.
+    self assert:( 1.6 asLongFloat ceilingAsFloat ) class == LongFloat.
+
+
+    self assert:( 1.6 floor ) = 1.
+    self assert:( 1.6 asShortFloat floor ) = 1.
+    self assert:( 1.6 asLongFloat floor ) = 1.
+
+    self assert:( 1.6 floorAsFloat ) = 1.0.
+    self assert:( 1.6 floorAsFloat ) class == Float.
+    self assert:( 1.6 asShortFloat floorAsFloat ) = 1.0 asShortFloat.
+    self assert:( 1.6 asShortFloat floorAsFloat ) class == ShortFloat.
+    self assert:( 1.6 asLongFloat floorAsFloat ) = 1.0 asLongFloat.
+    self assert:( 1.6 asLongFloat floorAsFloat ) class == LongFloat.
+
+
+    self assert:( 0.4 rounded ) class == SmallInteger.    
+    self assert:( 0.4 rounded = 0 ).    
+    self assert:( 0.5 rounded = 1 ).     
+    self assert:( 0.6 rounded = 1 ).     
+    self assert:( -0.4 rounded = 0 ).    
+    self assert:( -0.5 rounded = -1 ).    
+    self assert:( -0.6 rounded = -1 ).    
+
+    self assert:( 0.4 roundedAsFloat ) class == Float.    
+    self assert:( 0.4 roundedAsFloat  = 0.0 ).    
+    self assert:( 0.5 roundedAsFloat  = 1.0 ).    
+    self assert:( 0.6 roundedAsFloat  = 1.0 ).    
+    self assert:( -0.4 roundedAsFloat = 0 ).    
+    self assert:( -0.5 roundedAsFloat = -1.0 ).    
+    self assert:( -0.6 roundedAsFloat = -1.0 ).    
+
+    self assert:( 0.4 asShortFloat rounded ) class == SmallInteger.    
+    self assert:( 0.4 asShortFloat rounded = 0 ).    
+    self assert:( 0.5 asShortFloat rounded = 1 ).     
+    self assert:( 0.6 asShortFloat rounded = 1 ).     
+    self assert:( -0.4 asShortFloat rounded = 0 ).    
+    self assert:( -0.5 asShortFloat rounded = -1 ).    
+    self assert:( -0.6 asShortFloat rounded = -1 ).    
+
+    self assert:( 0.4 asShortFloat roundedAsFloat ) class == ShortFloat.    
+    self assert:( 0.4 asShortFloat roundedAsFloat  = 0.0 ).    
+    self assert:( 0.5 asShortFloat roundedAsFloat  = 1.0 ).    
+    self assert:( 0.6 asShortFloat roundedAsFloat  = 1.0 ).    
+    self assert:( -0.4 asShortFloat roundedAsFloat = 0 ).    
+    self assert:( -0.5 asShortFloat roundedAsFloat = -1.0 ).    
+    self assert:( -0.6 asShortFloat roundedAsFloat = -1.0 ).    
+
+    self assert:( 0.4 asLongFloat rounded ) class == SmallInteger.    
+    self assert:( 0.4 asLongFloat rounded = 0 ).    
+    self assert:( 0.5 asLongFloat rounded = 1 ).     
+    self assert:( 0.6 asLongFloat rounded = 1 ).     
+    self assert:( -0.4 asLongFloat rounded = 0 ).    
+    self assert:( -0.5 asLongFloat rounded = -1 ).    
+    self assert:( -0.6 asLongFloat rounded = -1 ).    
+
+    self assert:( 0.4 asLongFloat roundedAsFloat ) class == LongFloat.    
+    self assert:( 0.4 asLongFloat roundedAsFloat  = 0.0 ).    
+    self assert:( 0.5 asLongFloat roundedAsFloat  = 1.0 ).    
+    self assert:( 0.6 asLongFloat roundedAsFloat  = 1.0 ).    
+    self assert:( -0.4 asLongFloat roundedAsFloat = 0 ).    
+    self assert:( -0.5 asLongFloat roundedAsFloat = -1.0 ).    
+    self assert:( -0.6 asLongFloat roundedAsFloat = -1.0 ).    
+
+    self assert:( 0.4 truncated ) class == SmallInteger.    
+    self assert:( 0.4 truncated = 0 ).    
+    self assert:( 0.5 truncated = 0 ).     
+    self assert:( 0.6 truncated = 0 ).     
+    self assert:( -0.4 truncated = 0 ).    
+    self assert:( -0.5 truncated = 0 ).    
+    self assert:( -0.6 truncated = 0 ).    
+
+    self assert:( 0.4 truncatedAsFloat ) class == Float.    
+    self assert:( 0.4 truncatedAsFloat  = 0.0 ).    
+    self assert:( 0.5 truncatedAsFloat  = 0.0 ).    
+    self assert:( 0.6 truncatedAsFloat  = 0.0 ).    
+    self assert:( -0.4 truncatedAsFloat = 0 ).    
+    self assert:( -0.5 truncatedAsFloat = 0.0 ).    
+    self assert:( -0.6 truncatedAsFloat = 0.0 ).    
+
+    self assert:( 0.4 asShortFloat truncated ) class == SmallInteger.    
+    self assert:( 0.4 asShortFloat truncated = 0 ).    
+    self assert:( 0.5 asShortFloat truncated = 0 ).     
+    self assert:( 0.6 asShortFloat truncated = 0 ).     
+    self assert:( -0.4 asShortFloat truncated = 0 ).    
+    self assert:( -0.5 asShortFloat truncated = 0 ).    
+    self assert:( -0.6 asShortFloat truncated = 0 ).    
+
+    self assert:( 0.4 asShortFloat truncatedAsFloat ) class == ShortFloat.    
+    self assert:( 0.4 asShortFloat truncatedAsFloat  = 0.0 ).    
+    self assert:( 0.5 asShortFloat truncatedAsFloat  = 0.0 ).    
+    self assert:( 0.6 asShortFloat truncatedAsFloat  = 0.0 ).    
+    self assert:( -0.4 asShortFloat truncatedAsFloat = 0 ).    
+    self assert:( -0.5 asShortFloat truncatedAsFloat = 0.0 ).    
+    self assert:( -0.6 asShortFloat truncatedAsFloat = 0.0 ).    
+
+    self assert:( 0.4 asLongFloat truncated ) class == SmallInteger.    
+    self assert:( 0.4 asLongFloat truncated = 0 ).    
+    self assert:( 0.5 asLongFloat truncated = 0 ).     
+    self assert:( 0.6 asLongFloat truncated = 0 ).     
+    self assert:( -0.4 asLongFloat truncated = 0 ).    
+    self assert:( -0.5 asLongFloat truncated = 0 ).    
+    self assert:( -0.6 asLongFloat truncated = 0 ).    
+
+    self assert:( 0.4 asLongFloat truncatedAsFloat ) class == LongFloat.    
+    self assert:( 0.4 asLongFloat truncatedAsFloat  = 0.0 ).    
+    self assert:( 0.5 asLongFloat truncatedAsFloat  = 0.0 ).    
+    self assert:( 0.6 asLongFloat truncatedAsFloat  = 0.0 ).    
+    self assert:( -0.4 asLongFloat truncatedAsFloat = 0 ).    
+    self assert:( -0.5 asLongFloat truncatedAsFloat = 0.0 ).    
+    self assert:( -0.6 asLongFloat truncatedAsFloat = 0.0 ).    
+
+    "
+     self basicNew test07_Truncation
+    "
+! !
+
+!FloatTest class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !