checkin from browser
authorClaus Gittinger <cg@exept.de>
Thu, 07 Dec 2000 09:46:20 +0100
changeset 95 362e58ff28ba
parent 94 9fd9d470e29b
child 96 d3bad7e5e094
checkin from browser
RegressionTests__BlockTest.st
RegressionTests__EnumerationTests.st
RegressionTests__IntegerTest.st
RegressionTests__OperationInQueueTests.st
RegressionTests__SharedQueueTest.st
--- a/RegressionTests__BlockTest.st	Fri Dec 01 18:31:50 2000 +0100
+++ b/RegressionTests__BlockTest.st	Thu Dec 07 09:46:20 2000 +0100
@@ -2,7 +2,7 @@
 
 "{ NameSpace: RegressionTests }"
 
-Object subclass:#BlockTest
+TestCase subclass:#BlockTest
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -10,7 +10,7 @@
 !
 
 
-!BlockTest class methodsFor:'varArgBlocks'!
+!BlockTest methodsFor:'varArgBlocks'!
 
 getVarArgBlock1
      |b|
@@ -50,14 +50,6 @@
 
 !
 
-testAll
-    self testVarArgBlocks.
-
-    "
-     self testAll
-    "
-!
-
 testVarArgBlock1
     |b|
 
@@ -65,9 +57,9 @@
 
     b value.
     b code notNil ifTrue:[
-	Transcript showCR:'blocks code is jitted'
+        Transcript showCR:'blocks code is jitted'
     ] ifFalse:[
-	Transcript showCR:'*** blocks code is NOT jitted'
+        Transcript showCR:'*** blocks code is NOT jitted'
     ].
 
     b value.
@@ -75,7 +67,7 @@
     b value:'arg1' value:'arg2' value:'arg3' value:'arg4'
 
     "
-     self testVarArgBlock1
+     self new testVarArgBlock1
     "
 !
 
@@ -86,27 +78,27 @@
 
     b value.
     b code notNil ifTrue:[
-	Transcript showCR:'blocks code is jitted'
+        Transcript showCR:'blocks code is jitted'
     ] ifFalse:[
-	Transcript showCR:'*** blocks code is NOT jitted'
+        Transcript showCR:'*** blocks code is NOT jitted'
     ].
 
-    b value     = #()  ifFalse:[ self halt ].
-    (b value:1) = #(1) ifFalse:[ self halt ].
-    (b value:1 value:2) = #(1 2) ifFalse:[ self halt ].
-    (b value:1 value:2 value:3) = #(1 2 3) ifFalse:[ self halt ].
-    (b value:1 value:2 value:3 value:4) = #(1 2 3 4) ifFalse:[ self halt ].
-    (b valueWithArguments:#(1 2 3 4)) = #(1 2 3 4) ifFalse:[ self halt ].
+    self assert:( b value     = #() ).
+    self assert:( (b value:1) = #(1) ).
+    self assert:( (b value:1 value:2) = #(1 2) ).
+    self assert:( (b value:1 value:2 value:3) = #(1 2 3) ).
+    self assert:( (b value:1 value:2 value:3 value:4) = #(1 2 3 4) ).
+    self assert:( (b valueWithArguments:#(1 2 3 4)) = #(1 2 3 4) ).
 
-    (b perform:#value)     = #()  ifFalse:[ self halt ].
-    (b perform:#'value:' with:1) = #(1) ifFalse:[ self halt ].
-    (b perform:#'value:value:' with:1 with:2) = #(1 2) ifFalse:[ self halt ].
-    (b perform:#'value:value:value:' with:1 with:2 with:3) = #(1 2 3) ifFalse:[ self halt ].
-    (b perform:#'value:value:value:value:' with:1 with:2 with:3 with:4) = #(1 2 3 4) ifFalse:[ self halt ].
-    (b perform:#'valueWithArguments:' with:#(1 2 3 4)) = #(1 2 3 4) ifFalse:[ self halt ].
+    self assert:( (b perform:#value)     = #()  ).
+    self assert:( (b perform:#'value:' with:1) = #(1) ).
+    self assert:( (b perform:#'value:value:' with:1 with:2) = #(1 2) ).
+    self assert:( (b perform:#'value:value:value:' with:1 with:2 with:3) = #(1 2 3) ).
+    self assert:( (b perform:#'value:value:value:value:' with:1 with:2 with:3 with:4) = #(1 2 3 4) ).
+    self assert:( (b perform:#'valueWithArguments:' with:#(1 2 3 4)) = #(1 2 3 4) ).
 
     "
-     self testVarArgBlock2
+     self new testVarArgBlock2
     "
 !
 
@@ -117,35 +109,42 @@
 
     b value.
     b code notNil ifTrue:[
-	Transcript showCR:'blocks code is jitted'
+        Transcript showCR:'blocks code is jitted'
     ] ifFalse:[
-	Transcript showCR:'*** blocks code is NOT jitted'
+        Transcript showCR:'*** blocks code is NOT jitted'
     ].
 
-    b value     = 0  ifFalse:[ self halt ].
-    (b value:1) = 1 ifFalse:[ self halt ].
-    (b value:1 value:2) = 2 ifFalse:[ self halt ].
-    (b value:1 value:2 value:3) = 3 ifFalse:[ self halt ].
-    (b value:1 value:2 value:3 value:4) = 4 ifFalse:[ self halt ].
-    (b valueWithArguments:#(1 2 3 4)) = 4 ifFalse:[ self halt ].
+    self assert:( b value     = 0  ).
+    self assert:( (b value:1) = 1  ).
+    self assert:( (b value:1 value:2) = 2 ).
+    self assert:( (b value:1 value:2 value:3) = 3 ).
+    self assert:( (b value:1 value:2 value:3 value:4) = 4 ).
+    self assert:( (b valueWithArguments:#(1 2 3 4)) = 4 ).
 
-    (b perform:#value)     = 0  ifFalse:[ self halt ].
-    (b perform:#'value:' with:1) = 1 ifFalse:[ self halt ].
-    (b perform:#'value:value:' with:1 with:2) = 2 ifFalse:[ self halt ].
-    (b perform:#'value:value:value:' with:1 with:2 with:3) = 3 ifFalse:[ self halt ].
-    (b perform:#'value:value:value:value:' with:1 with:2 with:3 with:4) = 4 ifFalse:[ self halt ].
-    (b perform:#'valueWithArguments:' with:#(1 2 3 4)) = 4 ifFalse:[ self halt ].
+    self assert:( (b perform:#value)     = 0  ).
+    self assert:( (b perform:#'value:' with:1) = 1 ).
+    self assert:( (b perform:#'value:value:' with:1 with:2) = 2 ).
+    self assert:( (b perform:#'value:value:value:' with:1 with:2 with:3) = 3 ).
+    self assert:( (b perform:#'value:value:value:value:' with:1 with:2 with:3 with:4) = 4 ).
+    self assert:( (b perform:#'valueWithArguments:' with:#(1 2 3 4)) = 4 ).
 
     "
-     self testVarArgBlock3
+     self new testVarArgBlock3
     "
 !
 
-testVarArgBlocks
+xtestAll
+    self testVarArgBlocks.
+
+    "
+     self new xtestAll
+    "
+!
+
+xtestVarArgBlocks
     self testVarArgBlock1.
     self testVarArgBlock2.
     self testVarArgBlock3.
-
 ! !
 
 !BlockTest class methodsFor:'documentation'!
--- a/RegressionTests__EnumerationTests.st	Fri Dec 01 18:31:50 2000 +0100
+++ b/RegressionTests__EnumerationTests.st	Thu Dec 07 09:46:20 2000 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'exept:regression' }"
 
+"{ NameSpace: RegressionTests }"
+
 Object subclass:#EnumerationTests
 	instanceVariableNames:''
 	classVariableNames:''
@@ -18,12 +20,12 @@
     a := (1 to:100) asArray.
 
     10 timesRepeat:[
-        a keysAndValuesDo:[:index :val |
-            ObjectMemory scavenge.
-            index printString.
-            ObjectMemory scavenge.
-            val printString.
-        ]
+	a keysAndValuesDo:[:index :val |
+	    ObjectMemory scavenge.
+	    index printString.
+	    ObjectMemory scavenge.
+	    val printString.
+	]
     ]
 
     "
--- a/RegressionTests__IntegerTest.st	Fri Dec 01 18:31:50 2000 +0100
+++ b/RegressionTests__IntegerTest.st	Thu Dec 07 09:46:20 2000 +0100
@@ -145,7 +145,8 @@
 !
 
 alwaysTrue
-    ^ true.!
+    ^ true.
+!
 
 doConstantIntegerShift
     "arithmetic tests.
@@ -165,7 +166,8 @@
     "
 
     "Created: / 6.6.1999 / 14:47:51 / cg"
-    "Modified: / 9.6.1999 / 17:49:57 / cg"!
+    "Modified: / 9.6.1999 / 17:49:57 / cg"
+!
 
 flagsSlot
     "arithmetic tests.
@@ -180,7 +182,8 @@
     "
 
     "Created: / 6.6.1999 / 14:47:51 / cg"
-    "Modified: / 9.6.1999 / 17:49:57 / cg"!
+    "Modified: / 9.6.1999 / 17:49:57 / cg"
+!
 
 num_00000000000007FFF
     ^ 16r00000000000007FFF
@@ -944,7 +947,8 @@
 
     "
      self testIntegerShifts3
-    "!
+    "
+!
 
 testLargeAddition
     "general conversion & arithmetic tests.
--- a/RegressionTests__OperationInQueueTests.st	Fri Dec 01 18:31:50 2000 +0100
+++ b/RegressionTests__OperationInQueueTests.st	Thu Dec 07 09:46:20 2000 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'exept:regression' }"
 
+"{ NameSpace: RegressionTests }"
+
 TestCase subclass:#OperationInQueueTests
 	instanceVariableNames:''
 	classVariableNames:''
@@ -49,34 +51,34 @@
     self assert:(opQ size == 0).
 
     p0 := [
-        opQ scheduleOperation:[ Delay waitForSeconds:1.].
+	opQ scheduleOperation:[ Delay waitForSeconds:1.].
     ] fork.
 
     p1 := [
-        rslt1 := opQ scheduleOperation:(val1 := '1').
+	rslt1 := opQ scheduleOperation:(val1 := '1').
     ] fork.
 
     p2 := [
-        rslt2 := opQ scheduleOperation:(val2 := '2').
+	rslt2 := opQ scheduleOperation:(val2 := '2').
     ] fork.
 
     p3 := [
-        rslt3 := opQ scheduleOperation:(val3 := '3').
+	rslt3 := opQ scheduleOperation:(val3 := '3').
     ] fork.
 
     Delay waitForSeconds:0.2.
     self assert:((sz := opQ size) == 3).
 
     p1b := [
-        rslt1b := opQ scheduleOperation:(val1b := '1').
+	rslt1b := opQ scheduleOperation:(val1b := '1').
     ] fork.
 
     p2b := [
-        rslt2b := opQ scheduleOperation:(val2b := '2').
+	rslt2b := opQ scheduleOperation:(val2b := '2').
     ] fork.
 
     p3b := [
-        rslt3b := opQ scheduleOperation:(val3b := '3').
+	rslt3b := opQ scheduleOperation:(val3b := '3').
     ] fork.
 
     Delay waitForSeconds:0.1.
--- a/RegressionTests__SharedQueueTest.st	Fri Dec 01 18:31:50 2000 +0100
+++ b/RegressionTests__SharedQueueTest.st	Thu Dec 07 09:46:20 2000 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'exept:regression' }"
 
+"{ NameSpace: RegressionTests }"
+
 TestCase subclass:#SharedQueueTest
 	instanceVariableNames:''
 	classVariableNames:''
@@ -21,19 +23,19 @@
     s2 := ReadWriteStream on:(Array new:1000).
 
     p1 := [
-        [
-            s1 nextPut:q next
-        ] loop.
+	[
+	    s1 nextPut:q next
+	] loop.
     ] fork.
 
     p2 := [
-        [
-            s2 nextPut:q next
-        ] loop.
+	[
+	    s2 nextPut:q next
+	] loop.
     ] fork.
 
     1 to:1000 do:[:i|
-        q nextPut:i
+	q nextPut:i
     ].
 
     Delay waitForMilliseconds:20.
@@ -50,17 +52,17 @@
     next2 := s2 next.
 
     1 to: 1000 do:[:i|
-        self should:[
-            next1 == i ifTrue:[
-                next1 := s1 next.
-                true.
-            ] ifFalse:[
-                next2 == i ifTrue:[
-                    next2 := s2 next.
-                    true
-                ].
-            ]
-        ]
+	self should:[
+	    next1 == i ifTrue:[
+		next1 := s1 next.
+		true.
+	    ] ifFalse:[
+		next2 == i ifTrue:[
+		    next2 := s2 next.
+		    true
+		].
+	    ]
+	]
     ].
 !
 
@@ -75,25 +77,25 @@
     s2 := ReadWriteStream on:(Array new:20000).
 
     p1 := [
-        [
-            s1 nextPut:q next
-        ] loop.
+	[
+	    s1 nextPut:q next
+	] loop.
     ] fork.
 
     p2 := [
-        [
-            s2 nextPut:q next
-        ] loop.
+	[
+	    s2 nextPut:q next
+	] loop.
     ] fork.
 
     pw := [
-        1 to:10000 do:[:i|
-            q nextPut:i+scale
-        ].
+	1 to:10000 do:[:i|
+	    q nextPut:i+scale
+	].
     ] fork.
 
     1 to:10000 do:[:i|
-        q nextPut:i
+	q nextPut:i
     ].
 
     pw waitUntilTerminated.
@@ -109,23 +111,23 @@
 
     next1 := next2 := 0.
     self should:[
-        s1 contents conform:[:i|
-            i < scale ifTrue:[
-                next1 < i and:[next1 := i. true]
-            ] ifFalse:[
-                next2 < i and:[next2 := i. true]
-            ].
-        ].
+	s1 contents conform:[:i|
+	    i < scale ifTrue:[
+		next1 < i and:[next1 := i. true]
+	    ] ifFalse:[
+		next2 < i and:[next2 := i. true]
+	    ].
+	].
     ].
     next1 := next2 := 0.
     self should:[
-        s2 contents conform:[:i|
-            i < scale ifTrue:[
-                next1 < i and:[next1 := i. true]
-            ] ifFalse:[
-                next2 < i and:[next2 := i. true]
-            ].
-        ].
+	s2 contents conform:[:i|
+	    i < scale ifTrue:[
+		next1 < i and:[next1 := i. true]
+	    ] ifFalse:[
+		next2 < i and:[next2 := i. true]
+	    ].
+	].
     ].
 
     s1 reset.
@@ -136,8 +138,8 @@
     all addAll:s2 contents.
 
     1 to: 10000 do:[:i|
-        self assert:((all at:i) == i).
-        self assert:((all at:(i+10000)) == (i+scale)).
+	self assert:((all at:i) == i).
+	self assert:((all at:(i+10000)) == (i+scale)).
     ].
 !
 
@@ -149,14 +151,14 @@
     q := SharedQueue new:10.
 
     [
-        1 to:1000 do:[:i|
-            q nextPut:i.
-        ].
+	1 to:1000 do:[:i|
+	    q nextPut:i.
+	].
     ] fork.
     [
-        1 to:1000 do:[:i|
-            q nextPut:i+scale.
-        ].
+	1 to:1000 do:[:i|
+	    q nextPut:i+scale.
+	].
     ] fork.
 
 
@@ -164,14 +166,14 @@
     next2 := next1 + scale.
 
     2000 timesRepeat:[ |i|
-        i := q next.
-        i < scale ifTrue:[
-            self assert:i == next1.
-            next1 := next1 + 1.
-        ] ifFalse:[
-            self assert:i == next2.
-            next2 := next2 + 1.
-        ]
+	i := q next.
+	i < scale ifTrue:[
+	    self assert:i == next1.
+	    next1 := next1 + 1.
+	] ifFalse:[
+	    self assert:i == next2.
+	    next2 := next2 + 1.
+	]
     ].
 
     self assert:next1 == 1001.
@@ -195,13 +197,13 @@
     q := SharedQueue new:10.
 
     [
-        1 to:1000 do:[:i|
-            q nextPut:i.
-        ].
+	1 to:1000 do:[:i|
+	    q nextPut:i.
+	].
     ] fork.
 
     1 to: 1000 do:[:i|
-        self assert:q next == i.
+	self assert:q next == i.
     ].
 
     self assert:q isEmpty
@@ -210,7 +212,7 @@
 testRemoveAll
 
     0 to:10 do:[:i|
-        self removeAllSize:10 fill:i.
+	self removeAllSize:10 fill:i.
     ].
 ! !
 
@@ -223,7 +225,7 @@
     q := SharedQueue new:size.
 
     1 to:fill do:[:i|
-        q nextPut:i.
+	q nextPut:i.
     ].
     q removeAll.
     self assert:q isEmpty.