#BUGFIX by cg
authorClaus Gittinger <cg@exept.de>
Tue, 28 May 2019 16:22:21 +0200
changeset 2251 ba4e69d7fcc8
parent 2250 e10a24080dbf
child 2252 81d1e190c613
#BUGFIX by cg class: RegressionTests::LargeFloatTest comment/format in:25 methods
RegressionTests__LargeFloatTest.st
--- a/RegressionTests__LargeFloatTest.st	Tue May 28 09:46:43 2019 +0200
+++ b/RegressionTests__LargeFloatTest.st	Tue May 28 16:22:21 2019 +0200
@@ -67,13 +67,15 @@
 !LargeFloatTest methodsFor:'private'!
 
 checkDoublePrecision: y forFunction: func precision: n
-	"Check that doubling the precision, then rounding would lead to the same result"
-	
-	| anLargeFloat singlePrecisionResult |
-	anLargeFloat _ y asLargeFloatPrecision: n.
-	singlePrecisionResult _ anLargeFloat perform: func.
-	self checkThatEvaluatingFunction: func toDoublePrecisionOf: anLargeFloat equals: singlePrecisionResult.
-	^singlePrecisionResult
+        "Check that doubling the precision, then rounding would lead to the same result"
+        
+        | anLargeFloat singlePrecisionResult |
+        anLargeFloat := y asLargeFloatPrecision: n.
+        singlePrecisionResult := anLargeFloat perform: func.
+        self checkThatEvaluatingFunction: func toDoublePrecisionOf: anLargeFloat equals: singlePrecisionResult.
+        ^singlePrecisionResult
+
+    "Modified (format): / 28-05-2019 / 16:19:41 / Claus Gittinger"
 !
 
 checkDoublePrecisionSerie: serie forFunction: func 
@@ -85,53 +87,58 @@
 !
 
 checkDoublePrecisionSerieVsFloat: serie forFunction: func 
-	^serie reject: [:y |
-		| farb |
-		farb _ self checkDoublePrecision: y forFunction: func precision: Float precision.
-		[(y asFloat perform: func) = farb] on: ZeroDivide do: [false]]
+        ^serie reject: [:y |
+                | farb |
+                farb := self checkDoublePrecision: y forFunction: func precision: Float precision.
+                [(y asFloat perform: func) = farb] on: ZeroDivide do: [false]]
+
+    "Modified (format): / 28-05-2019 / 16:19:45 / Claus Gittinger"
 !
 
 checkThatEvaluatingFunction: func toDoublePrecisionOf: anLargeFloat equals: singlePrecisionResult
-	"Check that doubling the precision, then rounding would lead to the same result"
-	
-	| n doublePrecision doublePrecisionResult lowBits |
-	n _ anLargeFloat precision.
-	doublePrecision _ anLargeFloat asLargeFloatPrecision: n * 2.
-	doublePrecisionResult _ doublePrecision perform: func.
-	
-	"Note: the test must be guarded against double rounding error condition.
-	For example, suppose the single precision is 4 bits, double precision 8 bits.
-	If exact result is 1.001 | 0111 | 1001...
-	Then the nearest double is rounded to upper 1.001 | 1000
-	Then the nearest single to the double is rounded to upper 1.010
-	But the nearest single to the exact result should have been 1.001
-	To avoid this, we have to check if the second rounding is an exact tie"
-	doublePrecisionResult normalize.
-	lowBits _ doublePrecisionResult mantissa bitAnd: 1<<n-1.
-	lowBits = (1<<(n-1))
-		ifTrue:
-			["double precision is ambiguous - retry with quadruple..."
-			^self checkThatEvaluatingFunction: func toQuadruplePrecisionOf: anLargeFloat equals: singlePrecisionResult].
-	self assert: ((doublePrecisionResult asLargeFloatPrecision: n)- singlePrecisionResult) isZero
-	
+        "Check that doubling the precision, then rounding would lead to the same result"
+        
+        | n doublePrecision doublePrecisionResult lowBits |
+        n := anLargeFloat precision.
+        doublePrecision := anLargeFloat asLargeFloatPrecision: n * 2.
+        doublePrecisionResult := doublePrecision perform: func.
+        
+        "Note: the test must be guarded against double rounding error condition.
+        For example, suppose the single precision is 4 bits, double precision 8 bits.
+        If exact result is 1.001 | 0111 | 1001...
+        Then the nearest double is rounded to upper 1.001 | 1000
+        Then the nearest single to the double is rounded to upper 1.010
+        But the nearest single to the exact result should have been 1.001
+        To avoid this, we have to check if the second rounding is an exact tie"
+        doublePrecisionResult normalize.
+        lowBits := doublePrecisionResult mantissa bitAnd: 1<<n-1.
+        lowBits = (1<<(n-1))
+                ifTrue:
+                        ["double precision is ambiguous - retry with quadruple..."
+                        ^self checkThatEvaluatingFunction: func toQuadruplePrecisionOf: anLargeFloat equals: singlePrecisionResult].
+        self assert: ((doublePrecisionResult asLargeFloatPrecision: n)- singlePrecisionResult) isZero
+
+    "Modified (comment): / 28-05-2019 / 16:20:03 / Claus Gittinger"
 !
 
 checkThatEvaluatingFunction: func toQuadruplePrecisionOf: anLargeFloat equals: singlePrecisionResult
-	"Check that quadrupling the precision, then rounding would lead to the same result"
-	
-	| n quadruplePrecision quadruplePrecisionResult lowBits |
-	n _ anLargeFloat precision.
-	quadruplePrecision _ anLargeFloat asLargeFloatPrecision: n * 4.
-	quadruplePrecisionResult _ quadruplePrecision perform: func.
-	
-	"Guard against double rounding error condition (exact tie)"
-	quadruplePrecisionResult normalize.
-	lowBits _ quadruplePrecisionResult mantissa bitAnd: 1<<(3*n)-1.
-	lowBits = (1<<(3*n-1))
-		ifTrue:
-			["quadruple precision is ambiguous - give up..."
-			^self].
-	self assert: ((quadruplePrecisionResult asLargeFloatPrecision: n)- singlePrecisionResult) isZero.
+        "Check that quadrupling the precision, then rounding would lead to the same result"
+        
+        | n quadruplePrecision quadruplePrecisionResult lowBits |
+        n := anLargeFloat precision.
+        quadruplePrecision := anLargeFloat asLargeFloatPrecision: n * 4.
+        quadruplePrecisionResult := quadruplePrecision perform: func.
+        
+        "Guard against double rounding error condition (exact tie)"
+        quadruplePrecisionResult normalize.
+        lowBits := quadruplePrecisionResult mantissa bitAnd: 1<<(3*n)-1.
+        lowBits = (1<<(3*n-1))
+                ifTrue:
+                        ["quadruple precision is ambiguous - give up..."
+                        ^self].
+        self assert: ((quadruplePrecisionResult asLargeFloatPrecision: n)- singlePrecisionResult) isZero.
+
+    "Modified (format): / 28-05-2019 / 16:19:52 / Claus Gittinger"
 ! !
 
 !LargeFloatTest methodsFor:'setup'!
@@ -176,19 +183,20 @@
 testIEEEArithmeticVersusFloat
         | floats ops ref new |
         self skipIf:true description:'fails'.
-        floats _ #(1.0 2.0 3.0 5.0 10.0 2r1.0e52 2r1.0e53 2r1.0e54 0.5 0.25 2r1.0e-52 2r1.0e-53 2r1.0e-54 1.0e60 0.1 1.1e-30 1.0e-60) copyWith: Float pi.
-        ops _ #(#+ #- #* #/ #= #< #> ).
+        floats := #(1.0 2.0 3.0 5.0 10.0 2r1.0e52 2r1.0e53 2r1.0e54 0.5 0.25 2r1.0e-52 2r1.0e-53 2r1.0e-54 1.0e60 0.1 1.1e-30 1.0e-60) copyWith: Float pi.
+        ops := #(#+ #- #* #/ #= #< #> ).
         ops
                 do: [:op | floats
                                 do: [:f1 | floats
                                                 do: [:f2 | 
-                                                        ref _ f1 perform: op with: f2.
-                                                        new _ (f1 asLargeFloatPrecision: 53)
+                                                        ref := f1 perform: op with: f2.
+                                                        new := (f1 asLargeFloatPrecision: 53)
                                                                                 perform: op
                                                                                 with: (f2 asLargeFloatPrecision: 53).
                                                         self assert: new = ref]]]
 
     "Modified: / 28-05-2019 / 09:43:50 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:47 / Claus Gittinger"
 !
 
 testIEEEArithmeticVersusIntegerAndFraction
@@ -198,13 +206,13 @@
 
         | floats ops ref new intAndFractions |
         self skipIf:true description:'fails'.
-        floats _ #(1.0e0 2.0e0 3.0e0 5.0e0 10.0e0) 
+        floats := #(1.0e0 2.0e0 3.0e0 5.0e0 10.0e0) 
                                 , (#(52 53 54 -52 -53 -54) collect: [:e | 1.0e0 timesTwoPower: e]) 
                                         , #(0.5e0 0.25e0 1.0e60 0.1e0 1.1e-30 1.0e-60) copyWith: Float pi.
-        intAndFractions _ #(1 3 5 10 12345678901234567890 -1 -22 -3) copyWith: 7/9.
-        intAndFractions _ intAndFractions , (intAndFractions collect: [:e | e reciprocal]).
+        intAndFractions := #(1 3 5 10 12345678901234567890 -1 -22 -3) copyWith: 7/9.
+        intAndFractions := intAndFractions , (intAndFractions collect: [:e | e reciprocal]).
         
-        ops _ 1/10 = 0.1
+        ops := 1/10 = 0.1
                 ifTrue: [#(#+ #- #* #/)]
                 ifFalse: [#(#+ #- #* #/ #= #< #>)]. "BEWARE: LargeFloat compare exactly, Float don't, unless http://bugs.squeak.org/view.php?id=3374"
         ops do: 
@@ -213,32 +221,33 @@
                                         [:f1 | 
                                         intAndFractions do: 
                                                         [:f2 | 
-                                                        ref _ f1 perform: op with: f2 asFloat.
-                                                        new _ (f1 asLargeFloatPrecision: 53) perform: op
+                                                        ref := f1 perform: op with: f2 asFloat.
+                                                        new := (f1 asLargeFloatPrecision: 53) perform: op
                                                                                 with: (f2 asLargeFloatPrecision: 53).
                                                         self assert: new = ref.
-                                                        new _ f1 perform: op
+                                                        new := f1 perform: op
                                                                                 with: (f2 asLargeFloatPrecision: 53).
                                                         self assert: new = ref.
                                                         
-                                                        ref _ f1 perform: op with: f2.
-                                                        new _ (f1 asLargeFloatPrecision: 53) perform: op
+                                                        ref := f1 perform: op with: f2.
+                                                        new := (f1 asLargeFloatPrecision: 53) perform: op
                                                                                 with: f2.
                                                         self assert: new = ref.
                                                         
-                                                        ref _ f2 asFloat perform: op with: f1.
-                                                        new _ (f2 asLargeFloatPrecision: 53) perform: op
+                                                        ref := f2 asFloat perform: op with: f1.
+                                                        new := (f2 asLargeFloatPrecision: 53) perform: op
                                                                                 with: (f1 asLargeFloatPrecision: 53).
                                                         self assert: new = ref.
-                                                        new _ (f2 asLargeFloatPrecision: 53) perform: op with: f1.
+                                                        new := (f2 asLargeFloatPrecision: 53) perform: op with: f1.
                                                         self assert: new = ref.
                                                         
-                                                        ref _ f2 perform: op with: f1.
-                                                        new _ f2 perform: op
+                                                        ref := f2 perform: op with: f1.
+                                                        new := f2 perform: op
                                                                                 with: (f1 asLargeFloatPrecision: 53).
                                                         self assert: new = ref]]]
 
     "Modified: / 28-05-2019 / 09:43:46 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:54 / Claus Gittinger"
 !
 
 testMultiply
@@ -276,37 +285,40 @@
 testRaisedToNegativeInteger
         | n |
         self skipIf:true description:'fails'.
-        n _ 11.
+        n := 11.
         1 to: 1<<n-1 do: [:i |
                 self assert: ((i asLargeFloatPrecision: n) raisedToInteger: -49)
                         equals: ((i raisedToInteger: -49) asLargeFloatPrecision: n) ].
 
     "Modified: / 28-05-2019 / 09:43:39 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:36 / Claus Gittinger"
 !
 
 testRaisedToPositiveInteger
         | n |
         self skipIf:true description:'fails'.
-        n _ 11.
+        n := 11.
         1 to: 1<<n-1 do: [:i |
                 self assert: ((i asLargeFloatPrecision: n) raisedToInteger: 49)
                         equals: ((i raisedToInteger: 49) asLargeFloatPrecision: n) ].
 
     "Modified: / 28-05-2019 / 09:43:35 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:40 / Claus Gittinger"
 !
 
 testReciprocal
         | b |
         self skipIf:true description:'fails'.
-        b _ 1 << (Float precision - 1).
+        b := 1 << (Float precision - 1).
         1 to: 10000 do: [:i |
                 | a |
-                a _ i asLargeFloatPrecision: Float precision.
+                a := i asLargeFloatPrecision: Float precision.
                 self assert: a reciprocal = i asFloat reciprocal.
                 self assert: (a+b) reciprocal = (i+b) asFloat reciprocal.
                 self assert: a negated reciprocal = i asFloat negated reciprocal.]
 
     "Modified: / 28-05-2019 / 09:43:31 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:44 / Claus Gittinger"
 !
 
 testRoundToNearestEven
@@ -502,8 +514,8 @@
 testInfinityAndNaN
         | inf nan |
         self skipIf:true description:'fails'.
-        inf _ Float infinity.
-        nan _ Float nan.
+        inf := Float infinity.
+        nan := Float nan.
         self assert: inf + two equals: inf.
         self assert: half + inf negated equals: inf negated.    
         self assert: (nan + minusOne)  isNaN .
@@ -531,6 +543,7 @@
         self deny: nan = one.
 
     "Modified: / 28-05-2019 / 09:44:14 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:59 / Claus Gittinger"
 ! !
 
 !LargeFloatTest methodsFor:'testing-compare'!
@@ -626,64 +639,67 @@
 testAsFloatWithUnderflow
         | fmin fminA |
         self skipIf:true description:'fails'.
-        fmin _ Float fmin.
-        fminA _ fmin asLargeFloatPrecision: one precision.
+        fmin := Float fmin.
+        fminA := fmin asLargeFloatPrecision: one precision.
         Float emin - Float precision + 1 to: Float emin + 1 do: [:n |
                 self assert: ((one timesTwoPower: n) + fminA) asFloat = ((1.0e0 timesTwoPower: n) + fmin)].
 
     "Modified: / 28-05-2019 / 09:44:30 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:31 / Claus Gittinger"
 !
 
 testAsMinimalDecimalFraction
         | emax emin leadingOne significands |
 
         self skipIf:true description:'fails'.
-        significands _ 0 to: 1<<10-1.
-        leadingOne _ 1<<10.
-        emin _ -14.
-        emax _ 15.
+        significands := 0 to: 1<<10-1.
+        leadingOne := 1<<10.
+        emin := -14.
+        emax := 15.
         
         "Test all normal finite half precision float"
         emin to: emax do: [:e | 
                 significands do: [:s |
                         | f |
-                        f _ (leadingOne + s asLargeFloatPrecision: 11) timesTwoPower: e - 10.
+                        f := (leadingOne + s asLargeFloatPrecision: 11) timesTwoPower: e - 10.
                         self assert: (f asMinimalDecimalFraction asLargeFloatPrecision: 11) = f]].
         
         "Test all subnormal finite half precision float"
         significands do: [:s |
                 | f |
-                f _ (s asLargeFloatPrecision: s highBit) timesTwoPower: emin - 10.
+                f := (s asLargeFloatPrecision: s highBit) timesTwoPower: emin - 10.
                 self assert: (f asMinimalDecimalFraction asLargeFloatPrecision: s highBit) = f].
 
     "Modified: / 28-05-2019 / 09:44:37 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:23 / Claus Gittinger"
 !
 
 testPrintAndEvaluate
         <timeout: 50 "seconds">
         | emax emin leadingOne significands |
         self skipIf:true description:'fails'.
-        significands _ 0 to: 1<<10-1.
-        leadingOne _ 1<<10.
-        emin _ -14.
-        emax _ 15.
+        significands := 0 to: 1<<10-1.
+        leadingOne := 1<<10.
+        emin := -14.
+        emax := 15.
         
         "Test all normal finite half precision float"
         emin to: emax do: [:e | 
                 significands do: [:s |
                         | f |
-                        f _ (leadingOne + s asLargeFloatPrecision: 11) timesTwoPower: e - 10.
+                        f := (leadingOne + s asLargeFloatPrecision: 11) timesTwoPower: e - 10.
                         self assert: (Compiler evaluate: f storeString) = f.
                         self assert: (Compiler evaluate: f printString) = f.]].
         
         "Test all subnormal finite half precision float"
         significands do: [:s |
                 | f |
-                f _ (s asLargeFloatPrecision: s highBit) timesTwoPower: emin - 10.
+                f := (s asLargeFloatPrecision: s highBit) timesTwoPower: emin - 10.
                 self assert: (Compiler evaluate: f storeString) = f.
                 self assert: (Compiler evaluate: f printString) = f].
 
     "Modified: / 28-05-2019 / 09:44:42 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:11 / Claus Gittinger"
 ! !
 
 !LargeFloatTest methodsFor:'testing-functions'!
@@ -692,18 +708,19 @@
         <timeout: 10 "seconds">
         | badExp serie |
         self skipIf:true description:'fails'.
-        serie _ ((-20 to: 20) collect: [:e |e asFloat]).
-        badExp _ self checkDoublePrecisionSerieVsFloat: serie forFunction: #exp.
+        serie := ((-20 to: 20) collect: [:e |e asFloat]).
+        badExp := self checkDoublePrecisionSerieVsFloat: serie forFunction: #exp.
         badExp isEmpty ifFalse: [Transcript cr; show: 'bad exp for ' , badExp printString]
 
     "Modified: / 28-05-2019 / 09:44:47 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:40 / Claus Gittinger"
 !
 
 testExpLn
         |n|
         self skipIf:true description:'fails'.
         self assert: (1 asLargeFloatPrecision: 53) exp asFloat = 1 asFloat exp.
-        n _ 5 exp.
+        n := 5 exp.
         self assert: ((5 asLargeFloatPrecision: 53) exp - n)abs <= n ulp.
         "self assert: (5 asLargeFloatPrecision: 53) exp asFloat = 5 asFloat exp."
         self assert: ((5 asLargeFloatPrecision: 53) exp ln asFloat - n ln)abs <= 5.0 ulp.
@@ -712,17 +729,19 @@
          which results in an error of almost one ulp in '5 exp'"
 
     "Modified: / 28-05-2019 / 09:44:52 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:17 / Claus Gittinger"
 !
 
 testLn
         <timeout: 10 "seconds">
         | badLn serie |
         self skipIf:true description:'fails'.
-        serie _ ((1 to: 100) collect: [:e |e asFloat]).
-        badLn _ self checkDoublePrecisionSerieVsFloat: serie forFunction: #ln.
+        serie := ((1 to: 100) collect: [:e |e asFloat]).
+        badLn := self checkDoublePrecisionSerieVsFloat: serie forFunction: #ln.
         badLn isEmpty ifFalse: [Transcript cr; show: 'bad ln for ' , badLn printString]
 
     "Modified: / 28-05-2019 / 09:44:57 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:04 / Claus Gittinger"
 !
 
 testLnDomainError
@@ -739,11 +758,12 @@
         "knowing that (10**3) < (2**10), 100 bits are enough for representing 10**30 exactly"
         self assert: ((10 raisedTo: 30) asLargeFloatPrecision: 100) sqrt = (10 raisedTo: 15).
 
-        serie _ ((0 to: 20) collect: [:e | e asFloat]) , ((2 to: 20) collect: [:e | e reciprocal asFloat]).
-        badSqrt _ self checkDoublePrecisionSerieVsFloat: serie forFunction: #sqrt.
+        serie := ((0 to: 20) collect: [:e | e asFloat]) , ((2 to: 20) collect: [:e | e reciprocal asFloat]).
+        badSqrt := self checkDoublePrecisionSerieVsFloat: serie forFunction: #sqrt.
         badSqrt isEmpty ifFalse: [Transcript cr; show: 'bad sqrt for ' , badSqrt printString]
 
     "Modified: / 28-05-2019 / 09:45:04 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:57 / Claus Gittinger"
 !
 
 testSqrtDomainError
@@ -760,10 +780,11 @@
         <timeout: 5 "seconds">
         | serie |
         self skipIf:true description:'fails'.
-        serie _ ((1 to: 10) , #(1.0001 100 1000 1.0e20)) collect: [:e | e asFloat].
+        serie := ((1 to: 10) , #(1.0001 100 1000 1.0e20)) collect: [:e | e asFloat].
         self checkDoublePrecisionSerie: serie forFunction: #arCosh
 
     "Modified: / 28-05-2019 / 09:45:36 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:12 / Claus Gittinger"
 !
 
 testArCoshDomainError
@@ -777,20 +798,22 @@
         <timeout: 10 "seconds">
         | serie |
         self skipIf:true description:'fails'.
-        serie _ ((-5 to: 10) , #(1.0e-20 1.0e-10  0.9999 1.0001 100 1000 1.0e20)) collect: [:e | e asFloat].
+        serie := ((-5 to: 10) , #(1.0e-20 1.0e-10  0.9999 1.0001 100 1000 1.0e20)) collect: [:e | e asFloat].
         self checkDoublePrecisionSerie: serie forFunction: #arSinh
 
     "Modified: / 28-05-2019 / 09:45:47 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:27 / Claus Gittinger"
 !
 
 testArTanh
         <timeout: 20 "seconds">
         | serie |
         self skipIf:true description:'fails'.
-        serie _ ((-19 to: 19) collect: [:e | (e / 20) asFloat]) , ((-6 to: 6) collect: [:e | (e / 7) asFloat]) , #(1.0e-20 1.0e-10 0.99 0.9999 0.999999).
+        serie := ((-19 to: 19) collect: [:e | (e / 20) asFloat]) , ((-6 to: 6) collect: [:e | (e / 7) asFloat]) , #(1.0e-20 1.0e-10 0.99 0.9999 0.999999).
         self checkDoublePrecisionSerie: serie forFunction: #arTanh
 
     "Modified: / 28-05-2019 / 09:45:52 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:17 / Claus Gittinger"
 !
 
 testArTanhDomainError
@@ -887,35 +910,38 @@
         self skipIf:true description:'endless loop'.
         -5 to: 5 by: 4/10 do: [:y |
                 | yf yd |
-                yf _ y asLargeFloatPrecision: Float precision.
-                yd _ yf asLargeFloatPrecision: Float precision * 2.
+                yf := y asLargeFloatPrecision: Float precision.
+                yd := yf asLargeFloatPrecision: Float precision * 2.
                 -5 to: 5 by: 4/10 do: [:x |
                         | xf xd  |
-                        xf _ x asLargeFloatPrecision: Float precision.
-                        xd _ xf asLargeFloatPrecision: Float precision * 2.
+                        xf := x asLargeFloatPrecision: Float precision.
+                        xd := xf asLargeFloatPrecision: Float precision * 2.
                         self assert: ((yd arcTan: xd) asFloat - (yf arcTan: xf) asFloat) isZero]].
 
     "Modified: / 28-05-2019 / 08:36:55 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:24 / Claus Gittinger"
 !
 
 testCos
         <timeout: 30 "seconds">
         | badCos |
         self skipIf:true description:'endless loop'.
-        badCos _ self checkDoublePrecisionSerieVsFloat: self trigonometricSerie forFunction: #cos.
+        badCos := self checkDoublePrecisionSerieVsFloat: self trigonometricSerie forFunction: #cos.
         badCos isEmpty ifFalse: [Transcript cr; show: 'bad cos for angles (degrees) ' , (badCos collect: [:i | i radiansToDegrees rounded]) printString]
 
     "Modified: / 28-05-2019 / 08:37:06 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:20:36 / Claus Gittinger"
 !
 
 testSin
         <timeout: 30 "seconds">
         | badSin |
         self skipIf:true description:'endless loop'.
-        badSin _ self checkDoublePrecisionSerieVsFloat: self trigonometricSerie forFunction: #sin.
+        badSin := self checkDoublePrecisionSerieVsFloat: self trigonometricSerie forFunction: #sin.
         badSin isEmpty ifFalse: [Transcript cr; show: 'bad sin for angles (degrees) ' , (badSin collect: [:i | i radiansToDegrees rounded]) printString]
 
     "Modified: / 28-05-2019 / 08:37:09 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:47 / Claus Gittinger"
 !
 
 testSincos
@@ -923,26 +949,28 @@
         self skipIf:true description:'endless loop'.
         self trigonometricSerie do: [:aFloat |
                 | x sc s c |
-                x _ aFloat asLargeFloatPrecision: 53.
-                sc _ x sincos.
-                s _ x sin.
-                c _ x cos.
+                x := aFloat asLargeFloatPrecision: 53.
+                sc := x sincos.
+                s := x sin.
+                c := x cos.
                 self assert: sc size = 2.
 
                 self assert: sc first = s.
                 self assert: sc last = c]
 
     "Modified: / 28-05-2019 / 08:37:15 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:21:52 / Claus Gittinger"
 !
 
 testTan
         <timeout: 30 "seconds">
         | badTan |
         self skipIf:true description:'endless loop'.
-        badTan _ self checkDoublePrecisionSerieVsFloat: self trigonometricSerie forFunction: #tan.
+        badTan := self checkDoublePrecisionSerieVsFloat: self trigonometricSerie forFunction: #tan.
         badTan isEmpty ifFalse: [Transcript cr; show: 'bad tan for angles (degrees) ' , (badTan collect: [:i | i radiansToDegrees rounded]) printString]
 
     "Modified: / 28-05-2019 / 08:37:19 / Claus Gittinger"
+    "Modified (format): / 28-05-2019 / 16:22:01 / Claus Gittinger"
 !
 
 testVeryLargeCos