category renames (lower case)
authorClaus Gittinger <cg@exept.de>
Tue, 26 Feb 2002 11:30:47 +0100
changeset 68 9fd111438d60
parent 67 7861684195ec
child 69 c5bff082e12f
category renames (lower case)
ExampleSetTest.st
ExampleTestResource.st
SUnitDelay.st
SUnitNameResolver.st
SUnitTest.st
TestCase.st
TestFailure.st
TestResource.st
TestResult.st
TestRunner.st
TestSuite.st
TestSuitesCompoundScriptTest.st
TestSuitesHierarchyScriptTest.st
TestSuitesScriptTest.st
TestSuitesScripter.st
--- a/ExampleSetTest.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/ExampleSetTest.st	Tue Feb 26 11:30:47 2002 +0100
@@ -15,14 +15,14 @@
 None should fail.'
 ! !
 
-!ExampleSetTest methodsFor:'Running'!
+!ExampleSetTest methodsFor:'running'!
 
 setUp
 	empty := Set new.
 	full := Set with: 5 with: #abc
 ! !
 
-!ExampleSetTest methodsFor:'Testing'!
+!ExampleSetTest methodsFor:'testing'!
 
 testAdd
 	empty add: 5.
@@ -64,5 +64,5 @@
 !ExampleSetTest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/ExampleSetTest.st,v 1.5 2001-12-08 01:55:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/ExampleSetTest.st,v 1.6 2002-02-26 10:30:22 cg Exp $'
 ! !
--- a/ExampleTestResource.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/ExampleTestResource.st	Tue Feb 26 11:30:47 2002 +0100
@@ -8,14 +8,14 @@
 !
 
 
-!ExampleTestResource class methodsFor:'Testing'!
+!ExampleTestResource class methodsFor:'testing'!
 
 isAvailable
 
 	^super isAvailable and: [self current isStarted]
 ! !
 
-!ExampleTestResource methodsFor:'Accessing'!
+!ExampleTestResource methodsFor:'accessing'!
 
 runningState
 
@@ -27,7 +27,7 @@
 	runningState := aSymbol
 ! !
 
-!ExampleTestResource methodsFor:'Constants'!
+!ExampleTestResource methodsFor:'constants'!
 
 startedStateSymbol
 
@@ -39,7 +39,7 @@
 	^#stopped
 ! !
 
-!ExampleTestResource methodsFor:'Running'!
+!ExampleTestResource methodsFor:'running'!
 
 setUp
 	
@@ -51,7 +51,7 @@
 	self runningState: self stoppedStateSymbol
 ! !
 
-!ExampleTestResource methodsFor:'Testing'!
+!ExampleTestResource methodsFor:'testing'!
 
 isAvailable
 	
@@ -71,5 +71,5 @@
 !ExampleTestResource class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/ExampleTestResource.st,v 1.1 2001-12-13 21:47:44 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/ExampleTestResource.st,v 1.2 2002-02-26 10:30:30 cg Exp $'
 ! !
--- a/SUnitDelay.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/SUnitDelay.st	Tue Feb 26 11:30:47 2002 +0100
@@ -11,5 +11,5 @@
 !SUnitDelay class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/SUnitDelay.st,v 1.3 2000-12-10 13:22:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/SUnitDelay.st,v 1.4 2002-02-26 10:30:32 cg Exp $'
 ! !
--- a/SUnitNameResolver.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/SUnitNameResolver.st	Tue Feb 26 11:30:47 2002 +0100
@@ -20,5 +20,5 @@
 !SUnitNameResolver class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/SUnitNameResolver.st,v 1.3 2000-12-10 13:20:57 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/SUnitNameResolver.st,v 1.4 2002-02-26 10:30:47 cg Exp $'
 ! !
--- a/SUnitTest.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/SUnitTest.st	Tue Feb 26 11:30:47 2002 +0100
@@ -14,7 +14,7 @@
 Two tests should fail.'
 ! !
 
-!SUnitTest class methodsFor:'Testing'!
+!SUnitTest class methodsFor:'testing'!
 
 shouldInheritSelectors
 	"answer true to inherit selectors from superclasses"
@@ -22,7 +22,7 @@
 	^false
 ! !
 
-!SUnitTest methodsFor:'Accessing'!
+!SUnitTest methodsFor:'accessing'!
 
 hasRun
 	^hasRun
@@ -32,7 +32,7 @@
 	^hasSetup
 ! !
 
-!SUnitTest methodsFor:'Private'!
+!SUnitTest methodsFor:'private'!
 
 assertForTestResult: aResult runCount: aRunCount passed: aPassedCount failed: aFailureCount errors: anErrorCount
 
@@ -61,13 +61,13 @@
 	hasRun := true
 ! !
 
-!SUnitTest methodsFor:'Running'!
+!SUnitTest methodsFor:'running'!
 
 setUp
 	hasSetup := true
 ! !
 
-!SUnitTest methodsFor:'Testing'!
+!SUnitTest methodsFor:'testing'!
 
 testAssert
 	self assert: true.
@@ -200,5 +200,5 @@
 !SUnitTest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/SUnitTest.st,v 1.7 2001-12-13 23:40:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/SUnitTest.st,v 1.8 2002-02-26 10:30:34 cg Exp $'
 ! !
--- a/TestCase.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestCase.st	Tue Feb 26 11:30:47 2002 +0100
@@ -25,47 +25,7 @@
     "
 ! !
 
-!TestCase class methodsFor:'Building Suites'!
-
-buildSuite
-
-	| suite |
-	^self isAbstract 
-		ifTrue: 
-			[suite := TestSuite new.
-			suite name: self name asString.
-			self allSubclasses do: [:each | each isAbstract ifFalse: [suite addTest: each buildSuiteFromSelectors]].
-			suite]
-		ifFalse: [self buildSuiteFromSelectors]
-!
-
-buildSuiteFromAllSelectors
-	^self buildSuiteFromMethods: self allTestSelectors
-!
-
-buildSuiteFromLocalSelectors
-	^self buildSuiteFromMethods: self testSelectors
-!
-
-buildSuiteFromMethods: testMethods 
-	^testMethods 
-		inject: ((TestSuite new)
-				name: self name asString;
-				yourself)
-		into: 
-			[:suite :selector | 
-			suite
-				addTest: (self selector: selector);
-				yourself]
-!
-
-buildSuiteFromSelectors
-	^self shouldInheritSelectors
-		ifTrue: [self buildSuiteFromAllSelectors]
-		ifFalse: [self buildSuiteFromLocalSelectors]
-! !
-
-!TestCase class methodsFor:'Instance Creation'!
+!TestCase class methodsFor:'instance creation'!
 
 debug: aSymbol
 	^(self selector: aSymbol) debug
@@ -106,6 +66,46 @@
         ^self sunitSelectors select: [:each | 'test*' match: each]
 ! !
 
+!TestCase class methodsFor:'building Suites'!
+
+buildSuite
+
+	| suite |
+	^self isAbstract 
+		ifTrue: 
+			[suite := TestSuite new.
+			suite name: self name asString.
+			self allSubclasses do: [:each | each isAbstract ifFalse: [suite addTest: each buildSuiteFromSelectors]].
+			suite]
+		ifFalse: [self buildSuiteFromSelectors]
+!
+
+buildSuiteFromAllSelectors
+	^self buildSuiteFromMethods: self allTestSelectors
+!
+
+buildSuiteFromLocalSelectors
+	^self buildSuiteFromMethods: self testSelectors
+!
+
+buildSuiteFromMethods: testMethods 
+	^testMethods 
+		inject: ((TestSuite new)
+				name: self name asString;
+				yourself)
+		into: 
+			[:suite :selector | 
+			suite
+				addTest: (self selector: selector);
+				yourself]
+!
+
+buildSuiteFromSelectors
+	^self shouldInheritSelectors
+		ifTrue: [self buildSuiteFromAllSelectors]
+		ifFalse: [self buildSuiteFromLocalSelectors]
+! !
+
 !TestCase class methodsFor:'testing'!
 
 isAbstract
@@ -323,6 +323,6 @@
 !TestCase class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestCase.st,v 1.21 2002-02-26 10:13:44 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestCase.st,v 1.22 2002-02-26 10:30:20 cg Exp $'
 ! !
 TestCase initialize!
--- a/TestFailure.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestFailure.st	Tue Feb 26 11:30:47 2002 +0100
@@ -11,5 +11,5 @@
 !TestFailure class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestFailure.st,v 1.3 2000-12-10 13:22:12 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestFailure.st,v 1.4 2002-02-26 10:30:28 cg Exp $'
 ! !
--- a/TestResource.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestResource.st	Tue Feb 26 11:30:47 2002 +0100
@@ -15,7 +15,7 @@
 !
 
 
-!TestResource class methodsFor:'Accessing'!
+!TestResource class methodsFor:'accessing'!
 
 current
 	current isNil ifTrue: [current := self new].
@@ -26,7 +26,7 @@
 	current := aTestResource
 ! !
 
-!TestResource class methodsFor:'Creation'!
+!TestResource class methodsFor:'creation'!
 
 new
 	^super new initialize
@@ -38,7 +38,7 @@
 		current := nil]
 ! !
 
-!TestResource class methodsFor:'Testing'!
+!TestResource class methodsFor:'testing'!
 
 isAbstract
 	"Override to true if a TestCase subclass is Abstract and should not have
@@ -54,7 +54,7 @@
 	^self isAvailable not
 ! !
 
-!TestResource methodsFor:'Accessing'!
+!TestResource methodsFor:'accessing'!
 
 description
 	description isNil ifTrue: [^''].
@@ -74,18 +74,18 @@
 	name := aString
 ! !
 
-!TestResource methodsFor:'Init / Release'!
+!TestResource methodsFor:'init / release'!
 
 initialize
 ! !
 
-!TestResource methodsFor:'Printing'!
+!TestResource methodsFor:'printing'!
 
 printOn: aStream
 	aStream nextPutAll: self class printString
 ! !
 
-!TestResource methodsFor:'Running'!
+!TestResource methodsFor:'running'!
 
 setUp
 	"Does nothing. Subclasses should override this
@@ -97,7 +97,7 @@
 	to tear down their resource"
 ! !
 
-!TestResource methodsFor:'Testing'!
+!TestResource methodsFor:'testing'!
 
 isAvailable
 	"override to provide information on the readiness of the resource"
@@ -112,5 +112,5 @@
 !TestResource class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestResource.st,v 1.1 2001-12-13 21:25:37 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestResource.st,v 1.2 2002-02-26 10:30:15 cg Exp $'
 ! !
--- a/TestResult.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestResult.st	Tue Feb 26 11:30:47 2002 +0100
@@ -8,7 +8,7 @@
 !
 
 
-!TestResult class methodsFor:'Exceptions'!
+!TestResult class methodsFor:'exceptions'!
 
 error
        ^self exError
@@ -41,7 +41,7 @@
     "Modified: / 21.6.2000 / 10:11:20 / Sames"
 ! !
 
-!TestResult class methodsFor:'Init / Release'!
+!TestResult class methodsFor:'init / release'!
 
 new
 	^super new initialize
@@ -49,7 +49,7 @@
     "Modified: / 21.6.2000 / 10:11:50 / Sames"
 ! !
 
-!TestResult methodsFor:'Accessing'!
+!TestResult methodsFor:'accessing'!
 
 correctCount
         "depreciated - use #passedCount"
@@ -113,13 +113,13 @@
 		yourself
 ! !
 
-!TestResult methodsFor:'Init / Release'!
+!TestResult methodsFor:'init / release'!
 
 initialize
 	runCount := 0
 ! !
 
-!TestResult methodsFor:'Printing'!
+!TestResult methodsFor:'printing'!
 
 printOn: aStream
 	aStream
@@ -135,7 +135,7 @@
 		ifTrue: [aStream nextPut: $s].
 ! !
 
-!TestResult methodsFor:'Running'!
+!TestResult methodsFor:'running'!
 
 runCase: aTestCase
         |testCasePassed|
@@ -161,7 +161,7 @@
     "Modified: / 21.6.2000 / 10:10:06 / Sames"
 ! !
 
-!TestResult methodsFor:'Testing'!
+!TestResult methodsFor:'testing'!
 
 hasErrors
 
@@ -195,5 +195,5 @@
 !TestResult class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestResult.st,v 1.8 2001-12-13 23:08:20 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestResult.st,v 1.9 2002-02-26 10:30:45 cg Exp $'
 ! !
--- a/TestRunner.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestRunner.st	Tue Feb 26 11:30:47 2002 +0100
@@ -266,7 +266,7 @@
 
 ! !
 
-!TestRunner methodsFor:'Accessing'!
+!TestRunner methodsFor:'accessing'!
 
 category
     |holder|
@@ -435,7 +435,7 @@
     "Created: / 4.4.2000 / 19:57:37 / Sames"
 ! !
 
-!TestRunner methodsFor:'Actions'!
+!TestRunner methodsFor:'actions'!
 
 browseSelectedTestCase
     |testCaseName testCase browser|
@@ -772,7 +772,7 @@
         self scriptModel value: suites.
 ! !
 
-!TestRunner methodsFor:'Private'!
+!TestRunner methodsFor:'private'!
 
 allTestSuite
         "generate and return a suite for all tests, except SUnitTests"
@@ -878,7 +878,7 @@
     "Modified: / 3.4.2000 / 19:17:11 / Sames"
 ! !
 
-!TestRunner methodsFor:'Updating'!
+!TestRunner methodsFor:'updating'!
 
 displayColor: aColorValue
 
@@ -1067,5 +1067,5 @@
 !TestRunner class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestRunner.st,v 1.31 2002-02-25 20:01:09 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestRunner.st,v 1.32 2002-02-26 10:30:40 cg Exp $'
 ! !
--- a/TestSuite.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestSuite.st	Tue Feb 26 11:30:47 2002 +0100
@@ -8,7 +8,7 @@
 !
 
 
-!TestSuite class methodsFor:'Creation'!
+!TestSuite class methodsFor:'creation'!
 
 named: aString
 
@@ -17,7 +17,7 @@
 		yourself
 ! !
 
-!TestSuite methodsFor:'Accessing'!
+!TestSuite methodsFor:'accessing'!
 
 addTest: aTest
 	self tests add: aTest
@@ -59,7 +59,7 @@
 	^tests
 ! !
 
-!TestSuite methodsFor:'Dependencies'!
+!TestSuite methodsFor:'dependencies'!
 
 addDependentToHierachy: anObject
         self addDependent: anObject.
@@ -75,7 +75,7 @@
     "Modified: / 21.6.2000 / 10:13:27 / Sames"
 ! !
 
-!TestSuite methodsFor:'Running'!
+!TestSuite methodsFor:'running'!
 
 run
         | result |
@@ -116,7 +116,7 @@
                 ]
 ! !
 
-!TestSuite methodsFor:'Testing'!
+!TestSuite methodsFor:'testing'!
 
 areAllResourcesAvailable
 	^self resources 
@@ -127,5 +127,5 @@
 !TestSuite class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuite.st,v 1.10 2001-12-21 14:25:38 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuite.st,v 1.11 2002-02-26 10:30:26 cg Exp $'
 ! !
--- a/TestSuitesCompoundScriptTest.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestSuitesCompoundScriptTest.st	Tue Feb 26 11:30:47 2002 +0100
@@ -8,7 +8,7 @@
 !
 
 
-!TestSuitesCompoundScriptTest methodsFor:'Testing'!
+!TestSuitesCompoundScriptTest methodsFor:'testing'!
 
 testRan
 	super testRan
@@ -17,5 +17,5 @@
 !TestSuitesCompoundScriptTest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesCompoundScriptTest.st,v 1.3 2000-12-10 13:21:47 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesCompoundScriptTest.st,v 1.4 2002-02-26 10:30:38 cg Exp $'
 ! !
--- a/TestSuitesHierarchyScriptTest.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestSuitesHierarchyScriptTest.st	Tue Feb 26 11:30:47 2002 +0100
@@ -8,7 +8,7 @@
 !
 
 
-!TestSuitesHierarchyScriptTest methodsFor:'Testing'!
+!TestSuitesHierarchyScriptTest methodsFor:'testing'!
 
 testRan
 	self setRun
@@ -19,5 +19,5 @@
 !TestSuitesHierarchyScriptTest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesHierarchyScriptTest.st,v 1.3 2000-12-10 13:21:40 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesHierarchyScriptTest.st,v 1.4 2002-02-26 10:30:43 cg Exp $'
 ! !
--- a/TestSuitesScriptTest.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestSuitesScriptTest.st	Tue Feb 26 11:30:47 2002 +0100
@@ -8,13 +8,13 @@
 !
 
 
-!TestSuitesScriptTest methodsFor:'Running'!
+!TestSuitesScriptTest methodsFor:'running'!
 
 setUp
 	scripter := TestSuitesScripter new.
 ! !
 
-!TestSuitesScriptTest methodsFor:'Testing'!
+!TestSuitesScriptTest methodsFor:'testing'!
 
 testCompoundScript
 	| allTestCaseClasses superCase subCase |
@@ -104,5 +104,5 @@
 !TestSuitesScriptTest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesScriptTest.st,v 1.3 2000-12-10 13:21:12 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesScriptTest.st,v 1.4 2002-02-26 10:30:36 cg Exp $'
 ! !
--- a/TestSuitesScripter.st	Tue Feb 26 11:13:44 2002 +0100
+++ b/TestSuitesScripter.st	Tue Feb 26 11:30:47 2002 +0100
@@ -8,7 +8,7 @@
 !
 
 
-!TestSuitesScripter class methodsFor:'Example'!
+!TestSuitesScripter class methodsFor:'example'!
 
 exampleScripting
 	^(TestSuitesScripter script: ' "scratch suite 3" ExampleSetTest SUnitTest* ') value
@@ -16,7 +16,7 @@
     "Modified: / 21.6.2000 / 10:18:08 / Sames"
 ! !
 
-!TestSuitesScripter class methodsFor:'Init / Release'!
+!TestSuitesScripter class methodsFor:'init / release'!
 
 run: testClassNameString
         ^self new run: testClassNameString
@@ -26,7 +26,7 @@
 	^self new setScript: aString
 ! !
 
-!TestSuitesScripter methodsFor:'Printing'!
+!TestSuitesScripter methodsFor:'printing'!
 
 printOn: aStream
 	aStream nextPutAll: (script isNil 
@@ -36,7 +36,7 @@
     "Created: / 21.6.2000 / 10:15:29 / Sames"
 ! !
 
-!TestSuitesScripter methodsFor:'Private'!
+!TestSuitesScripter methodsFor:'private'!
 
 executeSingleSuiteScript: aString 
         | useHierachy realName testCase |
@@ -94,7 +94,7 @@
     "Modified: / 21.6.2000 / 10:16:47 / Sames"
 ! !
 
-!TestSuitesScripter methodsFor:'Scripting'!
+!TestSuitesScripter methodsFor:'scripting'!
 
 run: testClassNameString
         | suite subSuite token |
@@ -119,5 +119,5 @@
 !TestSuitesScripter class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesScripter.st,v 1.6 2001-12-13 23:13:18 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/goodies/sunit/TestSuitesScripter.st,v 1.7 2002-02-26 10:30:24 cg Exp $'
 ! !