Explorar o código

Another tab/space strange combos out.

Herbert Vojčík %!s(int64=11) %!d(string=hai) anos
pai
achega
39f372af29

+ 2 - 2
st/Compiler-IR.st

@@ -231,7 +231,7 @@ visitSendNode: aNode
 
 
 visitSequenceNode: aNode
 visitSequenceNode: aNode
 	^ self
 	^ self
-		withSequence: IRSequence new	
+		withSequence: IRSequence new
 		do: [
 		do: [
 			aNode nodes do: [ :each | | instruction |
 			aNode nodes do: [ :each | | instruction |
 				instruction := self visit: each.
 				instruction := self visit: each.
@@ -1056,7 +1056,7 @@ nextPutBlockContextFor: anIRClosure during: aBlock
 	
 	
 	self
 	self
 		nextPutAll: '},';
 		nextPutAll: '},';
-		nextPutAll:	 anIRClosure method scope alias, ')})'
+		nextPutAll: anIRClosure method scope alias, ')})'
 !
 !
 
 
 nextPutClosureWith: aBlock arguments: anArray
 nextPutClosureWith: aBlock arguments: anArray

+ 1 - 1
st/Compiler-Inlining.st

@@ -185,7 +185,7 @@ sendInliner
 
 
 shouldInlineAssignment: anIRAssignment
 shouldInlineAssignment: anIRAssignment
 	^ anIRAssignment isInlined not and: [
 	^ anIRAssignment isInlined not and: [
-		anIRAssignment instructions last isSend and: [	
+		anIRAssignment instructions last isSend and: [
 			self shouldInlineSend: (anIRAssignment instructions last) ]]
 			self shouldInlineSend: (anIRAssignment instructions last) ]]
 !
 !
 
 

+ 2 - 2
st/Compiler-Interpreter.st

@@ -239,7 +239,7 @@ interpret: aNode continue: aBlock
 	shouldReturn ifTrue: [ ^ self ].
 	shouldReturn ifTrue: [ ^ self ].
 
 
 	aNode isNode
 	aNode isNode
-		ifTrue: [	
+		ifTrue: [
 			currentNode := aNode.
 			currentNode := aNode.
 			self interpretNode: aNode continue: [ :value |
 			self interpretNode: aNode continue: [ :value |
 				self continue: aBlock value: value ] ]
 				self continue: aBlock value: value ] ]
@@ -295,7 +295,7 @@ interpretDynamicDictionaryNode: aNode continue: aBlock
 	self interpretAll: aNode nodes continue: [ :array | | hashedCollection |
 	self interpretAll: aNode nodes continue: [ :array | | hashedCollection |
 		hashedCollection := HashedCollection new.
 		hashedCollection := HashedCollection new.
 		array do: [ :each | hashedCollection add: each ].
 		array do: [ :each | hashedCollection add: each ].
-		self	
+		self
 			continue: aBlock
 			continue: aBlock
 			value: hashedCollection ]
 			value: hashedCollection ]
 !
 !

+ 1 - 1
st/Compiler-Semantic.st

@@ -203,7 +203,7 @@ Object subclass: #ScopeVar
 	instanceVariableNames: 'scope name'
 	instanceVariableNames: 'scope name'
 	package: 'Compiler-Semantic'!
 	package: 'Compiler-Semantic'!
 !ScopeVar commentStamp!
 !ScopeVar commentStamp!
-I am an entry in a LexicalScope that gets associated with variable nodes of the same name.	
+I am an entry in a LexicalScope that gets associated with variable nodes of the same name.
 There are 4 different subclasses of vars: temp vars, local vars, args, and unknown/global vars.!
 There are 4 different subclasses of vars: temp vars, local vars, args, and unknown/global vars.!
 
 
 !ScopeVar methodsFor: 'accessing'!
 !ScopeVar methodsFor: 'accessing'!

+ 1 - 1
st/Compiler-Tests.st

@@ -173,7 +173,7 @@ testMessageSend
 	"SendNode"
 	"SendNode"
 	self interpreter step.
 	self interpreter step.
 	
 	
-	 "ValueNode"
+	"ValueNode"
 	self interpreter step.
 	self interpreter step.
 	self assert: self interpreter currentNode value equals: 1.
 	self assert: self interpreter currentNode value equals: 1.
 	
 	

+ 14 - 14
st/IDE.st

@@ -75,7 +75,7 @@ renderOn: html
 		onClick: [self browser selectClass: self theClass].
 		onClick: [self browser selectClass: self theClass].
 	li asJQuery html: self label.
 	li asJQuery html: self label.
 
 
-	self browser selectedClass = self theClass ifTrue:	[
+	self browser selectedClass = self theClass ifTrue: [
 		cssClass := cssClass, ' selected'].
 		cssClass := cssClass, ' selected'].
 
 
 	self theClass comment isEmpty ifFalse: [
 	self theClass comment isEmpty ifFalse: [
@@ -242,7 +242,7 @@ doIt
 !
 !
 
 
 eval: aString
 eval: aString
-	| compiler	|
+	| compiler |
 	compiler := Compiler new.
 	compiler := Compiler new.
 	[ compiler parseExpression: aString ] on: Error do: [:ex |
 	[ compiler parseExpression: aString ] on: Error do: [:ex |
 		^window alert: ex messageText].
 		^window alert: ex messageText].
@@ -783,7 +783,7 @@ addNewClass
 	className := window prompt: 'New class'.
 	className := window prompt: 'New class'.
 	(className notNil and: [className notEmpty]) ifTrue: [
 	(className notNil and: [className notEmpty]) ifTrue: [
 		Object subclass: className instanceVariableNames: '' package: self selectedPackage.
 		Object subclass: className instanceVariableNames: '' package: self selectedPackage.
-			 self
+			self
 			resetClassesList;
 			resetClassesList;
 			updateClassesList.
 			updateClassesList.
 		self selectClass: (Smalltalk current at: className)]
 		self selectClass: (Smalltalk current at: className)]
@@ -806,12 +806,12 @@ cancelChanges
 commitPackage
 commitPackage
 	selectedPackage ifNotNil: [ |package|
 	selectedPackage ifNotNil: [ |package|
 		package := Package named: selectedPackage.
 		package := Package named: selectedPackage.
-		{	Exporter		 -> (package commitPathJs, '/', selectedPackage, '.js').
+		{ Exporter -> (package commitPathJs, '/', selectedPackage, '.js').
 			StrippedExporter -> (package commitPathJs, '/', selectedPackage, '.deploy.js').
 			StrippedExporter -> (package commitPathJs, '/', selectedPackage, '.deploy.js').
-			ChunkExporter	 -> (package commitPathSt, '/', selectedPackage, '.st')
+			ChunkExporter -> (package commitPathSt, '/', selectedPackage, '.st')
 		} do: [:commitStrategy| |fileContents|
 		} do: [:commitStrategy| |fileContents|
 			fileContents := (commitStrategy key new exportPackage: selectedPackage).
 			fileContents := (commitStrategy key new exportPackage: selectedPackage).
-			self ajaxPutAt: commitStrategy value data:	fileContents
+			self ajaxPutAt: commitStrategy value data: fileContents
 		]
 		]
 	]
 	]
 !
 !
@@ -863,8 +863,8 @@ compileMethodDefinitionFor: aClass
 	compiler currentClass: aClass.
 	compiler currentClass: aClass.
 	method := compiler eval: (compiler compileNode: node).
 	method := compiler eval: (compiler compileNode: node).
 	compiler unknownVariables do: [:each |
 	compiler unknownVariables do: [:each |
-		 "Do not try to redeclare javascript's objects"
-		 (window at: each) ifNil: [
+		"Do not try to redeclare javascript's objects"
+		(window at: each) ifNil: [
 		(window confirm: 'Declare ''', each, ''' as instance variable?') ifTrue: [
 		(window confirm: 'Declare ''', each, ''' as instance variable?') ifTrue: [
 			self addInstanceVariableNamed: each toClass: aClass.
 			self addInstanceVariableNamed: each toClass: aClass.
 			^self compileMethodDefinitionFor: aClass]]].
 			^self compileMethodDefinitionFor: aClass]]].
@@ -878,7 +878,7 @@ copyClass
 	className := window prompt: 'Copy class'.
 	className := window prompt: 'Copy class'.
 	(className notNil and: [className notEmpty]) ifTrue: [
 	(className notNil and: [className notEmpty]) ifTrue: [
 		ClassBuilder new copyClass: self selectedClass named: className.
 		ClassBuilder new copyClass: self selectedClass named: className.
-			 self
+			self
 			resetClassesList;
 			resetClassesList;
 			updateClassesList.
 			updateClassesList.
 		self selectClass: (Smalltalk current at: className)]
 		self selectClass: (Smalltalk current at: className)]
@@ -891,7 +891,7 @@ disableSaveButton
 !
 !
 
 
 handleSourceAreaKeyDown: anEvent
 handleSourceAreaKeyDown: anEvent
-	 <if(anEvent.ctrlKey) {
+	<if(anEvent.ctrlKey) {
 		if(anEvent.keyCode === 83) { //ctrl+s
 		if(anEvent.keyCode === 83) { //ctrl+s
 			self._compile();
 			self._compile();
 			anEvent.preventDefault();
 			anEvent.preventDefault();
@@ -974,7 +974,7 @@ searchReferencesOf: aString
 selectCategory: aCategory
 selectCategory: aCategory
 	self cancelChanges ifTrue: [
 	self cancelChanges ifTrue: [
 	selectedPackage := aCategory.
 	selectedPackage := aCategory.
-	selectedClass := selectedProtocol := selectedMethod :=	nil.
+	selectedClass := selectedProtocol := selectedMethod := nil.
 	self resetClassesList.
 	self resetClassesList.
 	self
 	self
 		updateCategoriesList;
 		updateCategoriesList;
@@ -1056,7 +1056,7 @@ initialize
 
 
 ajaxPutAt: aURL data: aString
 ajaxPutAt: aURL data: aString
 	jQuery
 	jQuery
-		ajax: aURL	options: #{ 'type' -> 'PUT'.
+		ajax: aURL options: #{ 'type' -> 'PUT'.
 								'data' -> aString.
 								'data' -> aString.
 								'contentType' -> 'text/plain;charset=UTF-8'.
 								'contentType' -> 'text/plain;charset=UTF-8'.
 								'error' -> [:xhr | window alert: 'Commiting ' , aURL , ' failed with reason: "' , (xhr responseText) , '"'] }
 								'error' -> [:xhr | window alert: 'Commiting ' , aURL , ' failed with reason: "' , (xhr responseText) , '"'] }
@@ -1444,7 +1444,7 @@ renderButtonsOn: html
 		class: 'amber_button debugger inspect';
 		class: 'amber_button debugger inspect';
 		with: 'Inspect';
 		with: 'Inspect';
 		onClick: [self inspectSelectedVariable].
 		onClick: [self inspectSelectedVariable].
-	 self
+	self
 		updateSourceArea;
 		updateSourceArea;
 		updateStatus;
 		updateStatus;
 		updateVariablesList;
 		updateVariablesList;
@@ -1493,7 +1493,7 @@ updateInspector
 !
 !
 
 
 updateSourceArea
 updateSourceArea
-	 sourceArea val: self source
+	sourceArea val: self source
 !
 !
 
 
 updateStatus
 updateStatus

+ 10 - 10
st/Importer-Exporter.st

@@ -26,11 +26,11 @@ nextChunk
 	result := '' writeStream.
 	result := '' writeStream.
 		[char := stream next.
 		[char := stream next.
 		char notNil] whileTrue: [
 		char notNil] whileTrue: [
-				 char = '!!' ifTrue: [
-						 stream peek = '!!'
+				char = '!!' ifTrue: [
+						stream peek = '!!'
 								ifTrue: [stream next "skipping the escape double"]
 								ifTrue: [stream next "skipping the escape double"]
-								ifFalse: [^result contents trimBoth	 "chunk end marker found"]].
-				 result nextPut: char].
+								ifFalse: [^result contents trimBoth "chunk end marker found"]].
+				result nextPut: char].
 	^nil "a chunk needs to end with !!"
 	^nil "a chunk needs to end with !!"
 ! !
 ! !
 
 
@@ -198,13 +198,13 @@ exportDefinitionOf: aClass on: aStream
 	aStream
 	aStream
 		nextPutAll: (self classNameFor: aClass superclass);
 		nextPutAll: (self classNameFor: aClass superclass);
 		nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
 		nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
-		nextPutAll: '	instanceVariableNames: '''.
+		nextPutAll: ' instanceVariableNames: '''.
 	aClass instanceVariableNames
 	aClass instanceVariableNames
 		do: [:each | aStream nextPutAll: each]
 		do: [:each | aStream nextPutAll: each]
 		separatedBy: [aStream nextPutAll: ' '].
 		separatedBy: [aStream nextPutAll: ' '].
 	aStream
 	aStream
 		nextPutAll: ''''; lf;
 		nextPutAll: ''''; lf;
-		nextPutAll: '	package: ''', aClass category, '''!!'; lf.
+		nextPutAll: ' package: ''', aClass category, '''!!'; lf.
 	aClass comment notEmpty ifTrue: [
 	aClass comment notEmpty ifTrue: [
 		aStream
 		aStream
 		nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
 		nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
@@ -281,7 +281,7 @@ exportPackageExtensionsOf: package on: aStream
 			aClass protocolsDo: [:category :methods |
 			aClass protocolsDo: [:category :methods |
 				(category match: '^\*', name) ifTrue: [ map at: category put: methods ]].
 				(category match: '^\*', name) ifTrue: [ map at: category put: methods ]].
 			(map keys sorted: [:a :b | a <= b ]) do: [:category | | methods |
 			(map keys sorted: [:a :b | a <= b ]) do: [:category | | methods |
-				methods := map at: category.	
+				methods := map at: category.
 				self exportMethods: methods category: category of: aClass on: aStream ]]]
 				self exportMethods: methods category: category of: aClass on: aStream ]]]
 ! !
 ! !
 
 
@@ -331,7 +331,7 @@ import: aStream
 	parser := ChunkParser on: aStream.
 	parser := ChunkParser on: aStream.
 	lastEmpty := false.
 	lastEmpty := false.
 	[chunk := parser nextChunk.
 	[chunk := parser nextChunk.
-	 chunk isNil] whileFalse: [
+	chunk isNil] whileFalse: [
 		chunk isEmpty
 		chunk isEmpty
 			ifTrue: [lastEmpty := true]
 			ifTrue: [lastEmpty := true]
 			ifFalse: [
 			ifFalse: [
@@ -356,7 +356,7 @@ initializePackageNamed: packageName prefix: aString
 		commitPathSt: '/', aString, '/st'
 		commitPathSt: '/', aString, '/st'
 !
 !
 
 
-loadPackage: packageName prefix: aString	
+loadPackage: packageName prefix: aString
 	| url |
 	| url |
 	url := '/', aString, '/js/', packageName, '.js'.
 	url := '/', aString, '/js/', packageName, '.js'.
 	jQuery
 	jQuery
@@ -367,7 +367,7 @@ loadPackage: packageName prefix: aString
 			'complete' -> [ :jqXHR :textStatus |
 			'complete' -> [ :jqXHR :textStatus |
 				jqXHR readyState = 4
 				jqXHR readyState = 4
 					ifTrue: [ self initializePackageNamed: packageName prefix: aString ] ].
 					ifTrue: [ self initializePackageNamed: packageName prefix: aString ] ].
-			'error' -> [ window alert: 'Could not load package at:	', url ]
+			'error' -> [ window alert: 'Could not load package at: ', url ]
 		}
 		}
 !
 !
 
 

+ 3 - 3
st/Kernel-Collections.st

@@ -818,7 +818,7 @@ removeLast
 	(self class = aCollection class and: [
 	(self class = aCollection class and: [
 		self size = aCollection size]) ifFalse: [^false].
 		self size = aCollection size]) ifFalse: [^false].
 	self withIndexDo: [:each :i |
 	self withIndexDo: [:each :i |
-				 (aCollection at: i) = each ifFalse: [^false]].
+				(aCollection at: i) = each ifFalse: [^false]].
 	^true
 	^true
 ! !
 ! !
 
 
@@ -933,7 +933,7 @@ removeFrom: aNumber to: anotherNumber
 !Array methodsFor: 'converting'!
 !Array methodsFor: 'converting'!
 
 
 asJavascript
 asJavascript
-	^'[', ((self collect: [:each | each asJavascript]) join: ', '),	 ']'
+	^'[', ((self collect: [:each | each asJavascript]) join: ', '), ']'
 !
 !
 
 
 reversed
 reversed
@@ -997,7 +997,7 @@ withAll: aCollection
 	| instance index |
 	| instance index |
 	index := 1.
 	index := 1.
 	instance := self new: aCollection size.
 	instance := self new: aCollection size.
-	aCollection do: [:each	|
+	aCollection do: [:each |
 		instance at: index put: each.
 		instance at: index put: each.
 		index := index + 1].
 		index := index + 1].
 	^instance
 	^instance

+ 1 - 1
st/Kernel-Exceptions.st

@@ -8,7 +8,7 @@ From the ANSI standard:
 This protocol describes the behavior of instances of class `Error`.
 This protocol describes the behavior of instances of class `Error`.
 These are used to represent error conditions that prevent the normal continuation of processing.
 These are used to represent error conditions that prevent the normal continuation of processing.
 Actual error exceptions used by an application may be subclasses of this class.
 Actual error exceptions used by an application may be subclasses of this class.
-As `Error` is explicitly specified	to be subclassable, conforming implementations must implement its behavior in a non-fragile manner.!
+As `Error` is explicitly specified to be subclassable, conforming implementations must implement its behavior in a non-fragile manner.!
 
 
 !Error methodsFor: 'accessing'!
 !Error methodsFor: 'accessing'!
 
 

+ 6 - 6
st/Kernel-Methods.st

@@ -70,8 +70,8 @@ on: anErrorClass do: aBlock
 	^self try: self catch: [ :error | | smalltalkError |
 	^self try: self catch: [ :error | | smalltalkError |
 		smalltalkError := Smalltalk current asSmalltalkException: error.
 		smalltalkError := Smalltalk current asSmalltalkException: error.
 		(smalltalkError isKindOf: anErrorClass)
 		(smalltalkError isKindOf: anErrorClass)
-		 ifTrue: [ aBlock value: smalltalkError ]
-		 ifFalse: [ smalltalkError signal ] ]
+		ifTrue: [ aBlock value: smalltalkError ]
+		ifFalse: [ smalltalkError signal ] ]
 ! !
 ! !
 
 
 !BlockClosure methodsFor: 'evaluating'!
 !BlockClosure methodsFor: 'evaluating'!
@@ -178,7 +178,7 @@ See referenced classes:
 
 
 or messages sent from this method:
 or messages sent from this method:
 	
 	
-	(String methodAt: 'lines')	messageSends!
+	(String methodAt: 'lines') messageSends!
 
 
 !CompiledMethod methodsFor: 'accessing'!
 !CompiledMethod methodsFor: 'accessing'!
 
 
@@ -332,7 +332,7 @@ Generally, the system does not use instances of Message for efficiency reasons.
 However, when a message is not understood by its receiver, the interpreter will make up an instance of it in order to capture the information involved in an actual message transmission.
 However, when a message is not understood by its receiver, the interpreter will make up an instance of it in order to capture the information involved in an actual message transmission.
 This instance is sent it as an argument with the message `doesNotUnderstand:` to the receiver.
 This instance is sent it as an argument with the message `doesNotUnderstand:` to the receiver.
 
 
-See boot.js, `messageNotUnderstood`	 and its counterpart `Object>>doesNotUnderstand:`!
+See boot.js, `messageNotUnderstood` and its counterpart `Object>>doesNotUnderstand:`!
 
 
 !Message methodsFor: 'accessing'!
 !Message methodsFor: 'accessing'!
 
 
@@ -355,12 +355,12 @@ selector: aString
 !Message methodsFor: 'printing'!
 !Message methodsFor: 'printing'!
 
 
 printString
 printString
-	^ String streamContents: [:aStream| 
+	^ String streamContents: [:aStream|
 												aStream
 												aStream
 													nextPutAll: super printString;
 													nextPutAll: super printString;
 													nextPutAll: '(';
 													nextPutAll: '(';
 													nextPutAll: selector;
 													nextPutAll: selector;
-													nextPutAll: ')'					]
+													nextPutAll: ')' ]
 !
 !
 
 
 sendTo: anObject
 sendTo: anObject

+ 4 - 4
st/Kernel-Objects.st

@@ -30,7 +30,7 @@ The hook method `#postCopy` can be overriden in subclasses to copy fields as nec
 
 
 ##Comparison
 ##Comparison
 
 
-Objects understand equality	 `#=` and identity `#==` comparison.
+Objects understand equality `#=` and identity `#==` comparison.
 
 
 ##Error handling
 ##Error handling
 
 
@@ -144,7 +144,7 @@ copy
 !
 !
 
 
 deepCopy
 deepCopy
-	<	
+	<
 		var copy = self.klass._new();
 		var copy = self.klass._new();
 		for(var i in self) {
 		for(var i in self) {
 		if(/^@.+/.test(i)) {
 		if(/^@.+/.test(i)) {
@@ -238,7 +238,7 @@ perform: aSymbol withArguments: aCollection
 log: aString block: aBlock
 log: aString block: aBlock
 
 
 	| result |
 	| result |
-	console log: aString,	' time: ', (Date millisecondsToRun: [result := aBlock value]) printString.
+	console log: aString, ' time: ', (Date millisecondsToRun: [result := aBlock value]) printString.
 	^result
 	^result
 !
 !
 
 
@@ -771,7 +771,7 @@ Object subclass: #Number
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	package: 'Kernel-Objects'!
 	package: 'Kernel-Objects'!
 !Number commentStamp!
 !Number commentStamp!
-Number holds the most general methods for dealing with numbers. 
+Number holds the most general methods for dealing with numbers.
 Number is directly mapped to JavaScript Number.
 Number is directly mapped to JavaScript Number.
 
 
 Most arithmetic methods like `#+` `#/` `#-` `#max:` are directly inlined into javascript.
 Most arithmetic methods like `#+` `#/` `#-` `#max:` are directly inlined into javascript.

+ 5 - 5
st/Kernel-Tests.st

@@ -244,7 +244,7 @@ testClassMigration
 	| instance oldClass |
 	| instance oldClass |
 	
 	
 	oldClass := builder copyClass: ObjectMock named: 'ObjectMock2'.
 	oldClass := builder copyClass: ObjectMock named: 'ObjectMock2'.
-	instance := (Smalltalk	current at: 'ObjectMock2') new.
+	instance := (Smalltalk current at: 'ObjectMock2') new.
 	
 	
 	"Change the superclass of ObjectMock2"
 	"Change the superclass of ObjectMock2"
 	ObjectMock subclass: (Smalltalk current at: 'ObjectMock2')
 	ObjectMock subclass: (Smalltalk current at: 'ObjectMock2')
@@ -928,7 +928,7 @@ testIdentity
 	self assert: #hello == #hello.
 	self assert: #hello == #hello.
 	self deny: #hello == #world.
 	self deny: #hello == #world.
 
 
-	self assert: #hello	 = #hello yourself.
+	self assert: #hello = #hello yourself.
 	self assert: #hello yourself = #hello asString asSymbol
 	self assert: #hello yourself = #hello asString asSymbol
 !
 !
 
 
@@ -1018,7 +1018,7 @@ testPropertyThatReturnsUndefined
 	| object |
 	| object |
 
 
 	object := self jsObject.
 	object := self jsObject.
-	self shouldnt: [ object e ]	 raise: MessageNotUnderstood.
+	self shouldnt: [ object e ] raise: MessageNotUnderstood.
 	self assert: object e isNil
 	self assert: object e isNil
 !
 !
 
 
@@ -1301,7 +1301,7 @@ testBasicAccess
 testBasicPerform
 testBasicPerform
 	| o |
 	| o |
 	o := Object new.
 	o := Object new.
-	o basicAt: 'func' put: ['hello'].	
+	o basicAt: 'func' put: ['hello'].
 	o basicAt: 'func2' put: [:a | a + 1].
 	o basicAt: 'func2' put: [:a | a + 1].
 
 
 	self assert: (o basicPerform: 'func') equals: 'hello'.
 	self assert: (o basicPerform: 'func') equals: 'hello'.
@@ -1396,7 +1396,7 @@ setUp
 !
 !
 
 
 tearDown
 tearDown
-	 Package
+	Package
 		defaultCommitPathJs: backUpCommitPathJs;
 		defaultCommitPathJs: backUpCommitPathJs;
 		defaultCommitPathSt: backUpCommitPathSt
 		defaultCommitPathSt: backUpCommitPathSt
 ! !
 ! !

+ 4 - 4
st/SUnit.st

@@ -22,7 +22,7 @@ A TestCase is an implementation of the command pattern to run a test.
 `TestCase` instances are created with the class method `#selector:`,
 `TestCase` instances are created with the class method `#selector:`,
 passing the symbol that names the method to be executed when the test case runs.
 passing the symbol that names the method to be executed when the test case runs.
 
 
-When you discover a new fixture, subclass `TestCase` and create a `#test...` method for the first test. 
+When you discover a new fixture, subclass `TestCase` and create a `#test...` method for the first test.
 As that method develops and more `#test...` methods are added, you will find yourself refactoring temps
 As that method develops and more `#test...` methods are added, you will find yourself refactoring temps
 into instance variables for the objects in the fixture and overriding `#setUp` to initialize these variables.
 into instance variables for the objects in the fixture and overriding `#setUp` to initialize these variables.
 As required, override `#tearDown` to nil references, release objects and deallocate.!
 As required, override `#tearDown` to nil references, release objects and deallocate.!
@@ -60,7 +60,7 @@ timeout: aNumber
 	
 	
 	asyncTimeout ifNotNil: [ asyncTimeout clearTimeout ].
 	asyncTimeout ifNotNil: [ asyncTimeout clearTimeout ].
 	
 	
-	 "to allow #async: message send without throwing an error"
+	"to allow #async: message send without throwing an error"
 	asyncTimeout := 0.
 	asyncTimeout := 0.
 	
 	
 	asyncTimeout := (self async: [
 	asyncTimeout := (self async: [
@@ -294,7 +294,7 @@ Object subclass: #TestResult
 	instanceVariableNames: 'timestamp runs errors failures total'
 	instanceVariableNames: 'timestamp runs errors failures total'
 	package: 'SUnit'!
 	package: 'SUnit'!
 !TestResult commentStamp!
 !TestResult commentStamp!
-A TestResult implements the collecting parameter pattern for running a bunch of tests.	
+A TestResult implements the collecting parameter pattern for running a bunch of tests.
 
 
 A TestResult holds tests that have run, sorted into the result categories of passed, failures and errors.
 A TestResult holds tests that have run, sorted into the result categories of passed, failures and errors.
 
 
@@ -368,7 +368,7 @@ or does nothing if no more runs"
 !
 !
 
 
 runCase: aTestCase
 runCase: aTestCase
-	[[	self increaseRuns.
+	[[ self increaseRuns.
 		aTestCase runCase]
 		aTestCase runCase]
 	on: TestFailure do: [:ex | self addFailure: aTestCase]]
 	on: TestFailure do: [:ex | self addFailure: aTestCase]]
 	on: Error do: [:ex | self addError: aTestCase]
 	on: Error do: [:ex | self addError: aTestCase]