added rerun-defect tests; fixed button enable bug
authorClaus Gittinger <cg@exept.de>
Wed, 06 Dec 2000 16:25:04 +0100
changeset 6 78bb1397e43d
parent 5 260add6a74a1
child 7 7dcf9b537f11
added rerun-defect tests; fixed button enable bug
ExampleSetTest.st
SUnitDelay.st
SUnitNameResolver.st
SUnitTest.st
TestCase.st
TestFailure.st
TestResult.st
TestRunner.st
TestSuite.st
TestSuitesCompoundScriptTest.st
TestSuitesHierarchyScriptTest.st
TestSuitesScriptTest.st
TestSuitesScripter.st
--- a/ExampleSetTest.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/ExampleSetTest.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,29 +1,30 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:11:03 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 TestCase subclass:#ExampleSetTest
 	instanceVariableNames:'full empty'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitTests'
+	category:'SUnit-Tests'
 !
 
 !ExampleSetTest methodsFor:'Running'!
 
 setUp
 	empty := Set new.
-	full := Set with: 5 with: #abc! !
+	full := Set with: 5 with: #abc
+! !
 
 !ExampleSetTest methodsFor:'Testing'!
 
 testAdd
 	empty add: 5.
-	self assert: (empty includes: 5)!
+	self assert: (empty includes: 5)
+!
 
 testGrow
 	empty addAll: (1 to: 100).
-	self assert: empty size = 100!
+	self assert: empty size = 100
+!
 
 testIllegal
 	self 
@@ -31,20 +32,24 @@
 		raise: TestResult error.
 	self 
 		should: [empty at: 5 put: #abc] 
-		raise: TestResult error!
+		raise: TestResult error
+!
 
 testIncludes
 	self assert: (full includes: 5).
-	self assert: (full includes: #abc)!
+	self assert: (full includes: #abc)
+!
 
 testOccurrences
 	self assert: (empty occurrencesOf: 0) = 0.
 	self assert: (full occurrencesOf: 5) = 1.
 	full add: 5.
-	self assert: (full occurrencesOf: 5) = 1!
+	self assert: (full occurrencesOf: 5) = 1
+!
 
 testRemove
 	full remove: 5.
 	self assert: (full includes: #abc).
-	self deny: (full includes: 5)! !
+	self deny: (full includes: 5)
+! !
 
--- a/SUnitDelay.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/SUnitDelay.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,11 +1,9 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:10:54 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 Delay subclass:#SUnitDelay
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitPreload'
+	category:'SUnit-Preload'
 !
 
--- a/SUnitNameResolver.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/SUnitNameResolver.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,12 +1,10 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:10:54 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 Object subclass:#SUnitNameResolver
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitPreload'
+	category:'SUnit-Preload'
 !
 
 !SUnitNameResolver class methodsFor:'Camp Smalltalk'!
--- a/SUnitTest.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/SUnitTest.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,21 +1,21 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:11:03 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 TestCase subclass:#SUnitTest
 	instanceVariableNames:'hasRun hasSetup hasRanOnce'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitTests'
+	category:'SUnit-Tests'
 !
 
 !SUnitTest methodsFor:'Accessing'!
 
 hasRun
-	^hasRun!
+	^hasRun
+!
 
 hasSetup
-	^hasSetup! !
+	^hasSetup
+! !
 
 !SUnitTest methodsFor:'Private'!
 
@@ -26,23 +26,28 @@
 !
 
 fail
-	self assert: false!
+	self assert: false
+!
 
-noop!
+noop
+!
 
 setRun
-	hasRun := true! !
+	hasRun := true
+! !
 
 !SUnitTest methodsFor:'Running'!
 
 setUp
-	hasSetup := true! !
+	hasSetup := true
+! !
 
 !SUnitTest methodsFor:'Testing'!
 
 testAssert
 	self assert: true.
-	self deny: false!
+	self deny: false
+!
 
 testDebugUI
 	"This should break"
@@ -77,7 +82,8 @@
 	self assert: result correctCount = 0.
 	self assert: result failureCount = 0.
 	self assert: result runCount = 1.
-	self assert: result errorCount = 1!
+	self assert: result errorCount = 1
+!
 
 testException
 	self should: [self error: 'foo'] raise: TestResult error
@@ -91,35 +97,41 @@
 	result := case run.
 	self assert: result correctCount = 0.
 	self assert: result failureCount = 1.
-	self assert: result runCount = 1!
+	self assert: result runCount = 1
+!
 
 testFailureDebugUI
 	"This should fail !!"
-	self fail!
+	self fail
+!
 
 testIsNotRerunOnDebug
 	| case |
 	case := self class selector: #testRanOnlyOnce.
 	case run.
-	case debug!
+	case debug
+!
 
 testRan
 	| case |
 	case := self class selector: #setRun.
 	case run.
 	self assert: case hasSetup.
-	self assert: case hasRun!
+	self assert: case hasRun
+!
 
 testRanOnlyOnce
 	self assert: hasRanOnce ~= true.
-	hasRanOnce := true.!
+	hasRanOnce := true.
+!
 
 testResult
 	| case result |
 	case := self class selector: #noop.
 	result := case run.
 	self assert: result runCount = 1.
-	self assert: result correctCount = 1!
+	self assert: result correctCount = 1
+!
 
 testRunning
 	(SUnitDelay forSeconds: 2) wait
@@ -129,7 +141,8 @@
 
 testShould
 	self should: [true].
-	self shouldnt: [false]!
+	self shouldnt: [false]
+!
 
 testSuite
 	| suite result |
@@ -139,5 +152,6 @@
 	result := suite run.
 	self assert: result runCount = 2.
 	self assert: result correctCount = 1.
-	self assert: result failureCount = 1! !
+	self assert: result failureCount = 1
+! !
 
--- a/TestCase.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestCase.st	Wed Dec 06 16:25:04 2000 +0100
@@ -4,7 +4,7 @@
 	instanceVariableNames:'testSelector'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnit'
+	category:'SUnit-Base'
 !
 
 !TestCase class methodsFor:'initialization'!
@@ -27,13 +27,16 @@
 !TestCase class methodsFor:'Instance Creation'!
 
 debug: aSymbol
-	^(self selector: aSymbol) debug!
+	^(self selector: aSymbol) debug
+!
 
 run: aSymbol
-	^(self selector: aSymbol) run!
+	^(self selector: aSymbol) run
+!
 
 selector: aSymbol
-	^self new setTestSelector: aSymbol!
+	^self new setTestSelector: aSymbol
+!
 
 suite
 	| testSelectors result |
@@ -100,10 +103,12 @@
 !TestCase methodsFor:'Dependencies'!
 
 addDependentToHierachy: anObject 
-	"an empty method. for Composite compability with TestSuite"!
+	"an empty method. for Composite compability with TestSuite"
+!
 
 removeDependentFromHierachy: anObject 
-	"an empty method. for Composite compability with TestSuite"! !
+	"an empty method. for Composite compability with TestSuite"
+! !
 
 !TestCase methodsFor:'Printing'!
 
@@ -129,15 +134,18 @@
 !
 
 setTestSelector: aSymbol
-	testSelector := aSymbol! !
+	testSelector := aSymbol
+! !
 
 !TestCase methodsFor:'Running'!
 
 debug
-	(self class selector: testSelector) runCase!
+	(self class selector: testSelector) runCase
+!
 
 debugAsFailure
-	(self class selector: testSelector) runCaseAsFailure!
+	(self class selector: testSelector) runCaseAsFailure
+!
 
 openDebuggerOnFailingTestMethod
         "SUnit has halted one step in front of the failing test method. 
@@ -147,16 +155,19 @@
         "/ self halt.
         self perform: testSelector sunitAsSymbol
 
-    "Modified: / 21.6.2000 / 10:03:37 / Sames"!
+    "Modified: / 21.6.2000 / 10:03:37 / Sames"
+!
 
 run
 	| result |
 	result := TestResult new.
 	self run: result.
-	^result!
+	^result
+!
 
 run: aResult
-	aResult runCase: self!
+	aResult runCase: self
+!
 
 runCase
 	self setUp.
@@ -172,8 +183,10 @@
     "Modified: / 21.6.2000 / 10:04:33 / Sames"
 !
 
-setUp!
+setUp
+!
 
-tearDown! !
+tearDown
+! !
 
 TestCase initialize!
--- a/TestFailure.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestFailure.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,11 +1,9 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:10:54 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 Exception subclass:#TestFailure
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitPreload'
+	category:'SUnit-Preload'
 !
 
--- a/TestResult.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestResult.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,12 +1,10 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:10:32 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 Object subclass:#TestResult
 	instanceVariableNames:'runCount failures errors'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnit'
+	category:'SUnit-Base'
 !
 
 !TestResult class methodsFor:'Exceptions'!
@@ -65,11 +63,13 @@
 !
 
 errorCount
-	^self errors size!
+	^self errors size
+!
 
 errors
 	errors isNil ifTrue: [errors := OrderedCollection new].
-	^errors!
+	^errors
+!
 
 failureCount
 	^self failures size
@@ -79,15 +79,18 @@
 
 failures
 	failures isNil ifTrue: [failures := OrderedCollection new].
-	^failures!
+	^failures
+!
 
 runCount
-	^runCount! !
+	^runCount
+! !
 
 !TestResult methodsFor:'Init / Release'!
 
 initialize
-	runCount := 0! !
+	runCount := 0
+! !
 
 !TestResult methodsFor:'Printing'!
 
@@ -127,8 +130,10 @@
 !TestResult methodsFor:'Testing'!
 
 hasPassed
-	^self runCount = self correctCount!
+	^self runCount = self correctCount
+!
 
 isFailure: aTestCase
-	^self failures includes: aTestCase! !
+	^self failures includes: aTestCase
+! !
 
--- a/TestRunner.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestRunner.st	Wed Dec 06 16:25:04 2000 +0100
@@ -5,7 +5,7 @@
 		scriptModel script'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitUI'
+	category:'SUnit-UI'
 !
 
 !TestRunner class methodsFor:'interface specs'!
@@ -27,78 +27,85 @@
 
     ^ 
      #(#FullSpec
-	#name: #windowSpec
-	#window: 
+        #name: #windowSpec
+        #window: 
        #(#WindowSpec
-	  #label: 'SUnit Camp Smalltalk 2.7 TestRunner'
-	  #name: 'SUnit Camp Smalltalk 2.7 TestRunner'
-	  #min: #(#Point 362 122)
-	  #bounds: #(#Rectangle 16 46 509 221)
-	)
-	#component: 
+          #label: 'SUnit Camp Smalltalk 2.7b TestRunner'
+          #name: 'SUnit Camp Smalltalk 2.7b TestRunner'
+          #min: #(#Point 362 122)
+          #bounds: #(#Rectangle 16 46 509 221)
+        )
+        #component: 
        #(#SpecCollection
-	  #collection: #(
-	   #(#ActionButtonSpec
-	      #label: 'Refresh'
-	      #name: 'Button3'
-	      #layout: #(#LayoutFrame 0 0 0 0 75 0 24 0)
-	      #model: #refreshSuites
-	    )
-	   #(#MenuButtonSpec
-	      #label: 'ExampleSetTest'
-	      #name: #tests
-	      #layout: #(#LayoutFrame 76 0 0 0 -146 1 24 0)
-	      #model: #script
-	      #menu: #scriptModel
-	      #useIndex: true
-	    )
-	   #(#ActionButtonSpec
-	      #label: 'Run'
-	      #name: 'Button1'
-	      #layout: #(#LayoutFrame -145 1 0 0 -77 1 24 0)
-	      #model: #runTests
-	      #enableChannel: #enableRunButton
-	    )
-	   #(#ActionButtonSpec
-	      #label: 'RunAll'
-	      #name: 'Button2'
-	      #layout: #(#LayoutFrame -76 1 0 0 0 1 24 0)
-	      #model: #runAllTests
-	    )
-	   #(#LabelSpec
-	      #label: 'N/A'
-	      #name: 'mode'
-	      #layout: #(#LayoutFrame 0 0 25 0 0 1 0 0.5)
-	      #style: #(#FontDescription #Arial #bold #roman 14)
-	      #labelChannel: #mode
-	    )
-	   #(#LabelSpec
-	      #label: '...'
-	      #name: 'details'
-	      #layout: #(#LayoutFrame 0 0 0 0.5 0 1 -24 1)
-	      #labelChannel: #details
-	    )
-	   #(#MenuButtonSpec
-	      #name: #defects
-	      #layout: #(#LayoutFrame 0 0 -24 1 -75 1 0 1)
-	      #isOpaque: true
-	      #flags: 40
-	      #model: #selectionHolder
-	      #initiallyDisabled: true
-	      #enableChannel: #enableDefectsList
-	      #menu: #defectMenu
-	    )
-	   #(#ActionButtonSpec
-	      #label: 'Debug'
-	      #name: 'Button4'
-	      #layout: #(#LayoutFrame -75 1 -24 1 0 1 0 1)
-	      #model: #debugSelectedFailure
-	      #initiallyDisabled: true
-	      #enableChannel: #enableDebugButton
-	    )
-	   )
+          #collection: #(
+           #(#ActionButtonSpec
+              #label: 'Refresh'
+              #name: 'Button3'
+              #layout: #(#LayoutFrame 0 0 0 0 75 0 24 0)
+              #model: #refreshSuites
+            )
+           #(#MenuButtonSpec
+              #label: 'ExampleSetTest'
+              #name: #tests
+              #layout: #(#LayoutFrame 76 0 0 0 -216 1 24 0)
+              #model: #script
+              #menu: #scriptModel
+              #useIndex: true
+            )
+           #(#ActionButtonSpec
+              #label: 'Run'
+              #name: 'Button1'
+              #layout: #(#LayoutFrame -215 1 0 0 -160 1 24 0)
+              #model: #runTests
+              #enableChannel: #enableRunButton
+            )
+           #(#ActionButtonSpec
+              #label: 'ReRun Defects'
+              #name: 'Button5'
+              #layout: #(#LayoutFrame -159 1 0 0 -57 1 24 0)
+              #model: #runDefects
+              #enableChannel: #enableRunDefectsButton
+            )
+           #(#ActionButtonSpec
+              #label: 'Run All'
+              #name: 'Button2'
+              #layout: #(#LayoutFrame -56 1 0 0 0 1 24 0)
+              #model: #runAllTests
+            )
+           #(#LabelSpec
+              #label: 'N/A'
+              #name: 'mode'
+              #layout: #(#LayoutFrame 0 0 25 0 0 1 0 0.5)
+              #style: #(#FontDescription #Arial #bold #roman 14)
+              #labelChannel: #mode
+            )
+           #(#LabelSpec
+              #label: '...'
+              #name: 'details'
+              #layout: #(#LayoutFrame 0 0 0 0.5 0 1 -24 1)
+              #labelChannel: #details
+            )
+           #(#MenuButtonSpec
+              #name: #defects
+              #layout: #(#LayoutFrame 0 0 -24 1 -75 1 0 1)
+              #isOpaque: true
+              #flags: 40
+              #model: #selectionHolder
+              #initiallyDisabled: true
+              #enableChannel: #enableDefectsList
+              #menu: #defectMenu
+            )
+           #(#ActionButtonSpec
+              #label: 'Debug'
+              #name: 'Button4'
+              #layout: #(#LayoutFrame -75 1 -24 1 0 1 0 1)
+              #model: #debugSelectedFailure
+              #initiallyDisabled: true
+              #enableChannel: #enableDebugButton
+            )
+           )
          
-	)
+        )
       )
 ! !
 
@@ -106,7 +113,8 @@
 
 open
 
-	^super open!
+	^super open
+!
 
 openOnTestCase:aTestCaseSubclass
     |runner idx|
@@ -136,7 +144,7 @@
      (if this app is embedded in a subCanvas)."
 
     ^ #(
-	#script
+        #script
       ).
 
 ! !
@@ -174,7 +182,8 @@
 		ifTrue:
 			[details := '...' asValue]
 		ifFalse:
-			[details]!
+			[details]
+!
 
 mode
 	"This method was generated by UIDefiner.  Any edits made here
@@ -186,7 +195,8 @@
 		ifTrue:
 			[mode := 'N/A' asValue]
 		ifFalse:
-			[mode]!
+			[mode]
+!
 
 script
     "automatically generated by UIPainter ..."
@@ -353,19 +363,51 @@
     "Created: / 21.6.2000 / 10:47:34 / Sames"
 !
 
+enableRunDefectsButton
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+
+    |holder|
+
+    (holder := builder bindingAt:#enableRunDefectsButton) isNil ifTrue:[
+        holder := true asValue.
+        builder aspectAt:#enableRunDefectsButton put:holder.
+"/        holder addDependent:self.
+    ].
+    ^ holder.
+!
+
 refreshSuites
-	self scriptModel value: (TestCase allSubclasses collect: [:each | each name]).
-	self tests selection: 0.
-	self defects selection: 0.
-	result := TestResult new.
-	self displayRefresh
+        self scriptModel value: (TestCase allSubclasses collect: [:each | each name]).
+        self script value:nil.
+        self tests selection: 0.
+        self defects selection: 0.
+        result := TestResult new.
+        self displayRefresh
 
     "Created: / 21.6.2000 / 10:58:34 / Sames"
     "Modified: / 21.6.2000 / 12:19:54 / Sames"
 !
 
 runAllTests
-	self runSuite: self allTestSuite!
+	self runSuite: self allTestSuite
+!
+
+runDefectTests
+        | testSuite |
+        (testSuite := self defectTestSuite) notNil ifTrue:
+                [self runSuite: testSuite]
+!
+
+runDefects
+    allDefects size > 0 ifTrue:[
+        ^ self runDefectTests
+    ].
+    self runTests
+!
 
 runSuite: aTestSuite 
 	Cursor wait
@@ -374,7 +416,8 @@
 			aTestSuite addDependentToHierachy: self.
 			[result := aTestSuite run]
 				ensure: [aTestSuite removeDependentFromHierachy: self].
-			self updateWindow]!
+			self updateWindow]
+!
 
 runTests
 	| testSuite |
@@ -393,7 +436,10 @@
 !
 
 suiteSelectionChanged
-	self enableRunButton value: self freshTestSuite notNil
+    |ok|
+
+    self enableRunButton value:(ok := self freshTestSuite notNil).
+    self enableRunDefectsButton value:(ok and:[allDefects size > 0]).
 
     "Created: / 21.6.2000 / 11:31:25 / Sames"
     "Modified: / 21.6.2000 / 11:32:54 / Sames"
@@ -407,12 +453,25 @@
 				copyWithout: 'SUnitTest* '.
 	stream := WriteStream on: String new.
 	tokens do: [:each | stream nextPutAll: each].
-	^TestSuitesScripter run: stream contents!
+	^TestSuitesScripter run: stream contents
+!
+
+defectTestSuite
+        |suite|
+
+        suite := TestSuite new.
+        allDefects keysAndValuesDo:[:nm :test |
+            suite addTest:test.
+        ].
+        ^suite
+
+!
 
 formatTime: aTime 
 	aTime hours > 0 ifTrue: [^aTime hours printString , 'h'].
 	aTime minutes > 0 ifTrue: [^aTime minutes printString , 'min'].
-	^aTime seconds printString , ' sec'!
+	^aTime seconds printString , ' sec'
+!
 
 freshTestSuite
 
@@ -462,11 +521,16 @@
 displayDefects: aCollection 
     | menuButton |
     menuButton := self builder componentAt: #defects.
-    aCollection isEmpty ifTrue: [^menuButton disable].
+    aCollection isEmpty ifTrue: [
+        menuButton disable.
+        self enableRunDefectsButton value:false.
+        ^ self
+    ].
     allDefects := Dictionary new.
     aCollection do: [:each | allDefects at: each printString put: each].
     self defectMenu value: allDefects keys asOrderedCollection.
-    menuButton enable
+    menuButton enable.
+    self enableRunDefectsButton value:(allDefects size > 0).
 
     "Modified: / 4.4.2000 / 20:11:06 / Sames"
 !
@@ -480,10 +544,12 @@
 displayFail
 	self displayRed.
 	self displayMode: 'Fail'.
-	self displayDetails: result printString.!
+	self displayDetails: result printString.
+!
 
 displayGreen
-	self displayColor: ColorValue green!
+	self displayColor: ColorValue green
+!
 
 displayMode: aString 
 	self mode value: aString
@@ -501,13 +567,15 @@
 !
 
 displayRed
-	self displayColor: ColorValue red.!
+	self displayColor: ColorValue red.
+!
 
 displayRefresh
     self displayMode: 'N/A'.
     self displayDetails:'...'.
     self updateDefects.
     self enableRunButton value: false.
+    self enableRunDefectsButton value: false.
     self enableDebugButton value: false.
     self displayDefault
 
@@ -518,22 +586,27 @@
 displayRunning
 	self displayYellow.
 	self displayMode: 'running'. 
-	self displayDetails: '...'.!
+	self displayDetails: '...'.
+!
 
 displayYellow
-	self displayColor: ColorValue yellow!
+	self displayColor: ColorValue yellow
+!
 
 update: anObject 
 	(anObject isKindOf: TestCase)
 		ifTrue: [self displayDetails: anObject printString]
-		ifFalse: [super update: anObject]!
+		ifFalse: [super update: anObject]
+!
 
 updateDefects
-	self displayDefects: result defects!
+	self displayDefects: result defects
+!
 
 updateWindow
 	result hasPassed
 		ifTrue: [self displayPass]
 		ifFalse: [self displayFail].
-	self updateDefects! !
+	self updateDefects
+! !
 
--- a/TestSuite.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestSuite.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,25 +1,26 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:10:32 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 Object subclass:#TestSuite
 	instanceVariableNames:'tests'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnit'
+	category:'SUnit-Base'
 !
 
 !TestSuite methodsFor:'Accessing'!
 
 addTest: aTest
-	self tests add: aTest!
+	self tests add: aTest
+!
 
 addTests: aCollection 
-	aCollection do: [:eachTest | self addTest: eachTest]!
+	aCollection do: [:eachTest | self addTest: eachTest]
+!
 
 tests
 	tests isNil ifTrue: [tests := OrderedCollection new].
-	^tests! !
+	^tests
+! !
 
 !TestSuite methodsFor:'Dependencies'!
 
@@ -43,7 +44,8 @@
 	| result |
 	result := TestResult new.
 	self run: result.
-	^result!
+	^result
+!
 
 run: aResult 
 	self tests do: 
--- a/TestSuitesCompoundScriptTest.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestSuitesCompoundScriptTest.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,16 +1,15 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:11:03 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 TestSuitesHierarchyScriptTest subclass:#TestSuitesCompoundScriptTest
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitTests'
+	category:'SUnit-Tests'
 !
 
 !TestSuitesCompoundScriptTest methodsFor:'Testing'!
 
 testRan
-	super testRan! !
+	super testRan
+! !
 
--- a/TestSuitesHierarchyScriptTest.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestSuitesHierarchyScriptTest.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,12 +1,10 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:11:03 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 SUnitTest subclass:#TestSuitesHierarchyScriptTest
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitTests'
+	category:'SUnit-Tests'
 !
 
 !TestSuitesHierarchyScriptTest methodsFor:'Testing'!
--- a/TestSuitesScriptTest.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestSuitesScriptTest.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,18 +1,17 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:11:03 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 SUnitTest subclass:#TestSuitesScriptTest
 	instanceVariableNames:'scripter suite'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnitTests'
+	category:'SUnit-Tests'
 !
 
 !TestSuitesScriptTest methodsFor:'Running'!
 
 setUp
-	scripter := TestSuitesScripter new.! !
+	scripter := TestSuitesScripter new.
+! !
 
 !TestSuitesScriptTest methodsFor:'Testing'!
 
--- a/TestSuitesScripter.st	Tue Oct 31 15:27:31 2000 +0100
+++ b/TestSuitesScripter.st	Wed Dec 06 16:25:04 2000 +0100
@@ -1,12 +1,10 @@
-'From Smalltalk/X, Version:4.1.1 on 24-oct-2000 at 08:10:32 pm'                 !
-
 "{ Package: 'stx:goodies/sunit' }"
 
 Object subclass:#TestSuitesScripter
 	instanceVariableNames:'script stream'
 	classVariableNames:''
 	poolDictionaries:''
-	category:'SUnit'
+	category:'SUnit-Base'
 !
 
 !TestSuitesScripter class methodsFor:'Example'!
@@ -20,10 +18,12 @@
 !TestSuitesScripter class methodsFor:'Init / Release'!
 
 run: aString
-	^self new run: aString!
+	^self new run: aString
+!
 
 script: aString
-	^self new setScript: aString! !
+	^self new setScript: aString
+! !
 
 !TestSuitesScripter methodsFor:'Printing'!
 
@@ -76,7 +76,8 @@
 !
 
 setScript: aString
-	script := aString!
+	script := aString
+!
 
 skipComment
 	| token inComment |
@@ -108,5 +109,6 @@
 !
 
 value
-	^self run: script! !
+	^self run: script
+! !