Browse Source

Added String>>trimBoth, trimLeft etc and trim chunks in ChunkExporter to remove trailing whitespace etc.

Göran Krampe 13 years ago
parent
commit
6c9d71e3df
11 changed files with 128 additions and 572 deletions
  1. 4 4
      js/Compiler.js
  2. 90 0
      js/Kernel.js
  3. 3 3
      js/Parser.js
  4. 1 74
      st/Canvas.st
  5. 1 79
      st/Compiler.st
  6. 0 4
      st/Examples.st
  7. 0 111
      st/IDE.st
  8. 1 51
      st/JQuery.st
  9. 26 160
      st/Kernel.st
  10. 2 82
      st/Parser.st
  11. 0 4
      st/SUnit.st

+ 4 - 4
js/Compiler.js

@@ -1554,11 +1554,11 @@ selector: 'doIt',
 category: '',
 fn: function (){
 var self=this;
-return smalltalk.send((function(){return smalltalk.send(smalltalk.send(smalltalk.ChunkExporter, "_new", []), "_exportCategory_", ["Parser"]);}), "_value", []);
+return smalltalk.send((function(){return smalltalk.send("abc", "_trimLeft_", ["az"]);}), "_value", []);
 return self;},
-source: unescape('doIt%20%5E%5BChunkExporter%20new%20exportCategory%3A%20%27Parser%27%20%5D%20value'),
-messageSends: ["value", "exportCategory:", "new"],
-referencedClasses: [smalltalk.ChunkExporter]
+source: unescape('doIt%20%5E%5B%27abc%27%20trimLeft%3A%20%27az%27%5D%20value'),
+messageSends: ["value", "trimLeft:"],
+referencedClasses: []
 }),
 smalltalk.DoIt);
 

+ 90 - 0
js/Kernel.js

@@ -4263,6 +4263,96 @@ referencedClasses: []
 }),
 smalltalk.String);
 
+smalltalk.addMethod(
+'_trimLeft_',
+smalltalk.method({
+selector: 'trimLeft:',
+category: 'regular expressions',
+fn: function (separators){
+var self=this;
+return smalltalk.send(self, "_replaceRegexp_with_", [smalltalk.send(smalltalk.RegularExpression, "_fromString_flag_", [smalltalk.send(smalltalk.send(unescape("%5E%5B"), "__comma", [separators]), "__comma", [unescape("%5D+")]), "g"]), ""]);
+return self;},
+source: unescape('trimLeft%3A%20separators%0A%0A%20%20%20%20%09%5Eself%20replaceRegexp%3A%20%28RegularExpression%20fromString%3A%20%27%5E%5B%27%2C%20separators%2C%20%27%5D+%27%20flag%3A%20%27g%27%29%20with%3A%20%27%27%0A'),
+messageSends: ["replaceRegexp:with:", "fromString:flag:", unescape("%2C")],
+referencedClasses: [smalltalk.RegularExpression]
+}),
+smalltalk.String);
+
+smalltalk.addMethod(
+'_trimRight_',
+smalltalk.method({
+selector: 'trimRight:',
+category: 'regular expressions',
+fn: function (separators){
+var self=this;
+return smalltalk.send(self, "_replaceRegexp_with_", [smalltalk.send(smalltalk.RegularExpression, "_fromString_flag_", [smalltalk.send(smalltalk.send(unescape("%5B"), "__comma", [separators]), "__comma", [unescape("%5D+%24")]), "g"]), ""]);
+return self;},
+source: unescape('trimRight%3A%20separators%0A%0A%20%20%20%20%09%5Eself%20replaceRegexp%3A%20%28RegularExpression%20fromString%3A%20%27%5B%27%2C%20separators%2C%20%27%5D+%24%27%20flag%3A%20%27g%27%29%20with%3A%20%27%27%0A'),
+messageSends: ["replaceRegexp:with:", "fromString:flag:", unescape("%2C")],
+referencedClasses: [smalltalk.RegularExpression]
+}),
+smalltalk.String);
+
+smalltalk.addMethod(
+'_trimLeft',
+smalltalk.method({
+selector: 'trimLeft',
+category: 'regular expressions',
+fn: function (){
+var self=this;
+return smalltalk.send(self, "_trimLeft_", [unescape("%5Cs")]);
+return self;},
+source: unescape('trimLeft%0A%09%5Eself%20trimLeft%3A%20%27%5Cs%27'),
+messageSends: ["trimLeft:"],
+referencedClasses: []
+}),
+smalltalk.String);
+
+smalltalk.addMethod(
+'_trimRight',
+smalltalk.method({
+selector: 'trimRight',
+category: 'regular expressions',
+fn: function (){
+var self=this;
+return smalltalk.send(self, "_trimRight_", [unescape("%5Cs")]);
+return self;},
+source: unescape('trimRight%0A%09%5Eself%20trimRight%3A%20%27%5Cs%27'),
+messageSends: ["trimRight:"],
+referencedClasses: []
+}),
+smalltalk.String);
+
+smalltalk.addMethod(
+'_trimBoth',
+smalltalk.method({
+selector: 'trimBoth',
+category: 'regular expressions',
+fn: function (){
+var self=this;
+return smalltalk.send(self, "_trimBoth_", [unescape("%5Cs")]);
+return self;},
+source: unescape('trimBoth%0A%09%5Eself%20trimBoth%3A%20%27%5Cs%27'),
+messageSends: ["trimBoth:"],
+referencedClasses: []
+}),
+smalltalk.String);
+
+smalltalk.addMethod(
+'_trimBoth_',
+smalltalk.method({
+selector: 'trimBoth:',
+category: 'regular expressions',
+fn: function (separators){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_trimLeft_", [separators]), "_trimRight_", [separators]);
+return self;},
+source: unescape('trimBoth%3A%20separators%0A%0A%20%20%20%20%09%5E%28self%20trimLeft%3A%20separators%29%20trimRight%3A%20separators%0A'),
+messageSends: ["trimRight:", "trimLeft:"],
+referencedClasses: []
+}),
+smalltalk.String);
+
 
 smalltalk.addMethod(
 '_streamClass',

+ 3 - 3
js/Parser.js

@@ -1560,10 +1560,10 @@ selector: 'chunkEscape:',
 category: 'not yet classified',
 fn: function (aString){
 var self=this;
-return smalltalk.send(aString, "_replace_with_", [unescape("%21"), unescape("%21%21")]);
+return smalltalk.send(smalltalk.send(aString, "_replace_with_", [unescape("%21"), unescape("%21%21")]), "_trimBoth", []);
 return self;},
-source: unescape('chunkEscape%3A%20aString%0A%09%22Replace%20all%20occurrences%20of%20%21%20with%20%21%21%22%0A%0A%09%5EaString%20replace%3A%20%27%21%27%20with%3A%20%27%21%21%27%0A'),
-messageSends: ["replace:with:"],
+source: unescape('chunkEscape%3A%20aString%0A%09%22Replace%20all%20occurrences%20of%20%21%20with%20%21%21%20and%20trim%20at%20both%20ends.%22%0A%0A%09%5E%28aString%20replace%3A%20%27%21%27%20with%3A%20%27%21%21%27%29%20trimBoth%0A'),
+messageSends: ["trimBoth", "replace:with:"],
 referencedClasses: []
 }),
 smalltalk.ChunkExporter);

+ 1 - 74
st/Canvas.st

@@ -5,7 +5,7 @@ Object subclass: #CanvasRenderingContext
 !CanvasRenderingContext methodsFor: 'drawing arcs'!
 
 arcTo: aPoint radius: aNumber startAngle: aNumber2 endAngle: aNumber3 anticlockwise: aBoolean
-	{'self.arc(aPoint._x(), aPoint._y(), aNumber, aNumber2, aNumber3, aBoolean)'} 
+	{'self.arc(aPoint._x(), aPoint._y(), aNumber, aNumber2, aNumber3, aBoolean)'}
 !
 
 arcTo: aPoint radius: aNumber
@@ -78,19 +78,16 @@ Object subclass: #HTMLCanvas
 
 root: aTagBrush
     root := aTagBrush
-
 !
 
 root
     ^root
-
 ! !
 
 !HTMLCanvas methodsFor: 'adding'!
 
 with: anObject
     ^self root with: anObject
-
 ! !
 
 !HTMLCanvas methodsFor: 'initialization'!
@@ -98,144 +95,116 @@ with: anObject
 initialize
     super initialize.
     root := TagBrush fromString: 'div' canvas: self
-
 ! !
 
 !HTMLCanvas methodsFor: 'tags'!
 
 newTag: aString
     ^TagBrush fromString: aString canvas: self
-
 !
 
 tag: aString
     ^root addBrush: (self newTag: aString)
-
 !
 
 h1
     ^self tag: 'h1'
-
 !
 
 h2
     ^self tag: 'h2'
-
 !
 
 h3
     ^self tag: 'h3'
-
 !
 
 h4
     ^self tag: 'h4'
-
 !
 
 h5
     ^self tag: 'h5'
-
 !
 
 h6
     ^self tag: 'h6'
-
 !
 
 p
     ^self tag: 'p'
-
 !
 
 div
     ^self tag: 'div'
-
 !
 
 span
     ^self tag: 'span'
-
 !
 
 img
     ^self tag: 'img'
-
 !
 
 ul
     ^self tag: 'ul'
-
 !
 
 ol
     ^self tag: 'ol'
-
 !
 
 li
     ^self tag: 'li'
-
 !
 
 table
     ^self tag: 'table'
-
 !
 
 tr
     ^self tag: 'tr'
-
 !
 
 td 
     ^self tag: 'td'
-
 !
 
 th
     ^self tag: 'th'
-
 !
 
 form
     ^self tag: 'form'
-
 !
 
 input
     ^self tag: 'input'
-
 !
 
 button
     ^self tag: 'button'
-
 !
 
 select
     ^self tag: 'select'
-
 !
 
 option
     ^self tag: 'option'
-
 !
 
 textarea
     ^self tag: 'textarea'
-
 !
 
 a
     ^self tag: 'a'
-
 !
 
 canvas
 	^self tag: 'canvas'
-
 ! !
 
 Object subclass: #TagBrush
@@ -246,7 +215,6 @@ Object subclass: #TagBrush
 
 element
     ^element
-
 ! !
 
 !TagBrush methodsFor: 'adding'!
@@ -254,28 +222,23 @@ element
 contents: anObject
     self asJQuery empty.
     self append: anObject
-
 !
 
 addBrush: aTagBrush
     self appendChild: aTagBrush element.
     ^aTagBrush
-
 !
 
 with: anObject
     self append: anObject
-
 !
 
 append: anObject
     anObject appendToBrush: self
-
 !
 
 appendToBrush: aTagBrush
     aTagBrush addBrush: self
-
 !
 
 appendBlock: aBlock
@@ -284,108 +247,88 @@ appendBlock: aBlock
     canvas root: self.
     aBlock value: canvas.
     canvas root: root
-
 !
 
 appendChild: anElement
     {'self[''@element''].appendChild(anElement)'}
-
 !
 
 appendString: aString
     self appendChild: (self createTextNodeFor: aString)
-
 ! !
 
 !TagBrush methodsFor: 'attributes'!
 
 at: aString put: aValue
     {'self[''@element''].setAttribute(aString, aValue)'}
-
 !
 
 removeAt: aString
     {'self[''@element''].removeAttribute(aString)'}
-
 !
 
 class: aString
     self at: 'class' put: aString
-
 !
 
 id: aString
     self at: 'id' put: aString
-
 !
 
 src: aString
     self  at: 'src' put: aString
-
 !
 
 href: aString
     self at: 'href' put: aString
-
 !
 
 title: aString
     self at: 'title' put: aString
-
 !
 
 style: aString
     self at: 'style' put: aString
-
 ! !
 
 !TagBrush methodsFor: 'converting'!
 
 asJQuery
 	{'return smalltalk.JQuery._from_(jQuery(self[''@element'']))'}
-
 !
 
 asJQueryDo: aBlock
     aBlock value: self asJQuery
-
 ! !
 
 !TagBrush methodsFor: 'events'!
 
 onKeyDown: aBlock
     self asJQuery on: 'keydown' do: aBlock
-
 !
 
 onKeyPress: aBlock
     self asJQuery on: 'keypress' do: aBlock
-
 !
 
 onKeyUp: aBlock
     self asJQuery on: 'keyup' do: aBlock
-
 !
 
 onFocus: aBlock
     self asJQuery on: 'focus' do: aBlock
-
 !
 
 onBlur: aBlock
     self asJQuery on: 'blur' do: aBlock
-
 !
 
 onChange: aBlock
     self asJQuery on: 'change' do: aBlock
-
 !
 
 onClick: aBlock
     self asJQuery on: 'click' do: aBlock
-
 ! !
 
 !TagBrush methodsFor: 'initialization'!
@@ -393,19 +336,16 @@ onClick: aBlock
 initializeFromString: aString canvas: aCanvas
     element := self createElementFor: aString.
     canvas := aCanvas
-
 ! !
 
 !TagBrush methodsFor: 'private'!
 
 createElementFor: aString
 	{'return document.createElement(String(aString))'}
-
 !
 
 createTextNodeFor: aString
 	{'return document.createTextNode(String(aString))'}
-
 ! !
 
 !TagBrush class methodsFor: 'instance creation'!
@@ -414,7 +354,6 @@ fromString: aString canvas: aCanvas
     ^self new
 	initializeFromString: aString canvas: aCanvas;
 	yourself
-
 ! !
 
 Object subclass: #Widget
@@ -425,29 +364,24 @@ Object subclass: #Widget
 
 root
     ^root
-
 ! !
 
 !Widget methodsFor: 'actions'!
 
 alert: aString
     {'alert(aString)'}
-
 !
 
 confirm: aString
     {'return window.confirm(aString)'}
-
 !
 
 prompt: aString
     ^self prompt: aString default: ''
-
 !
 
 prompt: aString default: anotherString
     {'return window.prompt(aString, anotherString)'}
-
 !
 
 update
@@ -456,20 +390,17 @@ update
     canvas root: self root.
     self root asJQuery empty.
     self renderOn: canvas
-
 ! !
 
 !Widget methodsFor: 'adding'!
 
 appendToBrush: aTagBrush
     self appendToJQuery: aTagBrush asJQuery
-
 !
 
 appendToJQuery: aJQuery
     self render.
     aJQuery append: self root asJQuery
-
 ! !
 
 !Widget methodsFor: 'rendering'!
@@ -479,12 +410,10 @@ render
     canvas := HTMLCanvas new.
     root := canvas root.
     self renderOn: canvas
-
 !
 
 renderOn: html
     self
-
 ! !
 
 TagBrush subclass: #CanvasBrush
@@ -515,7 +444,6 @@ canvas: aCanvas
 
 appendToBrush: aTagBrush
     aTagBrush append: self asString
-
 ! !
 
 !BlockClosure methodsFor: '*Canvas'!
@@ -528,6 +456,5 @@ appendToBrush: aTagBrush
 
 appendToBrush: aTagBrush
     aTagBrush appendString: self
-
 ! !
 

+ 1 - 79
st/Compiler.st

@@ -6,26 +6,22 @@ Object subclass: #Node
 
 nodes
 	^nodes ifNil: [nodes := Array new]
-
 !
 
 addNode: aNode
 	self nodes add: aNode
-
 ! !
 
 !Node methodsFor: 'building'!
 
 nodes: aCollection
 	nodes := aCollection
-
 ! !
 
 !Node methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitNode: self
-
 ! !
 
 Node subclass: #MethodNode
@@ -36,39 +32,32 @@ Node subclass: #MethodNode
 
 selector
 	^selector
-
 !
 
 selector: aString
 	selector := aString
-
 !
 
 arguments
 	^arguments ifNil: [#()]
-
 !
 
 arguments: aCollection
 	arguments := aCollection
-
 !
 
 source
 	^source
-
 !
 
 source: aString
 	source := aString
-
 ! !
 
 !MethodNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitMethodNode: self
-
 ! !
 
 Node subclass: #SendNode
@@ -79,32 +68,26 @@ Node subclass: #SendNode
 
 selector
 	^selector
-
 !
 
 selector: aString
 	selector := aString
-
 !
 
 arguments
 	^arguments ifNil: [arguments := #()]
-
 !
 
 arguments: aCollection
 	arguments := aCollection
-
 !
 
 receiver
 	^receiver
-
 !
 
 receiver: aNode
 	receiver := aNode
-
 !
 
 valueForReceiver: anObject
@@ -115,7 +98,6 @@ valueForReceiver: anObject
 	    selector: self selector;
 	    arguments: self arguments;
 	    yourself
-
 !
 
 cascadeNodeWithMessages: aCollection
@@ -128,14 +110,12 @@ cascadeNodeWithMessages: aCollection
 	    receiver: self receiver;
 	    nodes: (Array with: first), aCollection;
 	    yourself
-
 ! !
 
 !SendNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitSendNode: self
-
 ! !
 
 Node subclass: #CascadeNode
@@ -146,19 +126,16 @@ Node subclass: #CascadeNode
 
 receiver
 	^receiver
-
 !
 
 receiver: aNode
 	receiver := aNode
-
 ! !
 
 !CascadeNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitCascadeNode: self
-
 ! !
 
 Node subclass: #AssignmentNode
@@ -169,29 +146,24 @@ Node subclass: #AssignmentNode
 
 left
 	^left
-
 !
 
 left: aNode
 	left := aNode
-
 !
 
 right
 	^right
-
 !
 
 right: aNode
 	right := aNode
-
 ! !
 
 !AssignmentNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitAssignmentNode: self
-
 ! !
 
 Node subclass: #BlockNode
@@ -202,19 +174,16 @@ Node subclass: #BlockNode
 
 parameters
 	^parameters ifNil: [parameters := Array new]
-
 !
 
 parameters: aCollection
 	parameters := aCollection
-
 ! !
 
 !BlockNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitBlockNode: self
-
 ! !
 
 Node subclass: #SequenceNode
@@ -225,12 +194,10 @@ Node subclass: #SequenceNode
 
 temps
 	^temps ifNil: [#()]
-
 !
 
 temps: aCollection
 	temps := aCollection
-
 ! !
 
 !SequenceNode methodsFor: 'testing'!
@@ -240,14 +207,12 @@ asBlockSequenceNode
 	    nodes: self nodes;
 	    temps: self temps;
 	    yourself
-
 ! !
 
 !SequenceNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitSequenceNode: self
-
 ! !
 
 SequenceNode subclass: #BlockSequenceNode
@@ -258,7 +223,6 @@ SequenceNode subclass: #BlockSequenceNode
 
 accept: aVisitor
 	aVisitor visitBlockSequenceNode: self
-
 ! !
 
 Node subclass: #ReturnNode
@@ -269,7 +233,6 @@ Node subclass: #ReturnNode
 
 accept: aVisitor
 	aVisitor visitReturnNode: self
-
 ! !
 
 Node subclass: #ValueNode
@@ -280,19 +243,16 @@ Node subclass: #ValueNode
 
 value
 	^value
-
 !
 
 value: anObject
 	value := anObject
-
 ! !
 
 !ValueNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitValueNode: self
-
 ! !
 
 ValueNode subclass: #VariableNode
@@ -303,7 +263,6 @@ ValueNode subclass: #VariableNode
 
 accept: aVisitor
 	aVisitor visitVariableNode: self
-
 ! !
 
 VariableNode subclass: #ClassReferenceNode
@@ -314,7 +273,6 @@ VariableNode subclass: #ClassReferenceNode
 
 accept: aVisitor
 	aVisitor visitClassReferenceNode: self
-
 ! !
 
 Node subclass: #JSStatementNode
@@ -325,19 +283,16 @@ Node subclass: #JSStatementNode
 
 source
 	^source ifNil: ['']
-
 !
 
 source: aString
 	source := aString
-
 ! !
 
 !JSStatementNode methodsFor: 'visiting'!
 
 accept: aVisitor
 	aVisitor visitJSStatementNode: self
-
 ! !
 
 Object subclass: #NodeVisitor
@@ -348,67 +303,54 @@ Object subclass: #NodeVisitor
 
 visit: aNode
 	aNode accept: self
-
 !
 
 visitNode: aNode
-
 !
 
 visitMethodNode: aNode
 	self visitNode: aNode
-
 !
 
 visitSequenceNode: aNode
 	self visitNode: aNode
-
 !
 
 visitBlockSequenceNode: aNode
 	self visitSequenceNode: aNode
-
 !
 
 visitBlockNode: aNode
 	self visitNode: aNode
-
 !
 
 visitReturnNode: aNode
 	self visitNode: aNode
-
 !
 
 visitSendNode: aNode
 	self visitNode: aNode
-
 !
 
 visitCascadeNode: aNode
 	self visitNode: aNode
-
 !
 
 visitValueNode: aNode
 	self visitNode: aNode
-
 !
 
 visitVariableNode: aNode
-
 !
 
 visitAssignmentNode: aNode
 	self visitNode: aNode
-
 !
 
 visitClassReferenceNode: aNode
 	self 
 	    nextPutAll: 'smalltalk.';
 	    nextPutAll: aNode value
-
 !
 
 visitJSStatementNode: aNode
@@ -416,7 +358,6 @@ visitJSStatementNode: aNode
 	    nextPutAll: 'function(){';
 	    nextPutAll: aNode source;
 	    nextPutAll: '})()'
-
 ! !
 
 NodeVisitor subclass: #Compiler
@@ -427,17 +368,14 @@ NodeVisitor subclass: #Compiler
 
 parser
 	^SmalltalkParser new
-
 !
 
 currentClass
 	^currentClass
-
 !
 
 currentClass: aClass
 	currentClass := aClass
-
 !
 
 unknownVariables
@@ -472,12 +410,10 @@ classNameFor: aClass
 loadExpression: aString
 	DoIt addCompiledMethod: (self eval: (self compileExpression: aString)).
 	^DoIt new doIt
-
 !
 
 load: aString forClass: aClass
 	^self eval: (self compile: aString forClass: aClass)
-
 !
 
 compile: aString forClass: aClass
@@ -488,7 +424,6 @@ compile: aString forClass: aClass
 compileExpression: aString
 	self currentClass: DoIt.
 	^self compileNode: (self parseExpression: aString)
-
 !
 
 eval: aString
@@ -497,24 +432,20 @@ eval: aString
 
 compile: aString
 	^self compileNode: (self parse: aString)
-
 !
 
 compileNode: aNode
 	stream := '' writeStream.
 	self visit: aNode.
 	^stream contents
-
 !
 
 parse: aString
     ^self parser parse: aString readStream
-
 !
 
 parseExpression: aString
     ^self parse: 'doIt ^[', aString, '] value'
-
 !
 
 recompile: aClass
@@ -539,14 +470,12 @@ initialize
 	tempVariables := #().
 	messageSends := #().
 	classReferenced := #()
-
 ! !
 
 !Compiler methodsFor: 'visiting'!
 
 visit: aNode
 	aNode accept: self
-
 !
 
 visitMethodNode: aNode
@@ -608,7 +537,6 @@ visitBlockNode: aNode
 	stream nextPutAll: '){'.
 	aNode nodes do: [:each | self visit: each].
 	stream nextPutAll: '})'
-
 !
 
 visitSequenceNode: aNode
@@ -619,7 +547,6 @@ visitSequenceNode: aNode
 	    self visit: each.
 	    stream nextPutAll: ';']
 	    separatedBy: [stream lf]
-
 !
 
 visitBlockSequenceNode: aNode
@@ -640,7 +567,6 @@ visitBlockSequenceNode: aNode
 		    self visit: each.
 		    stream nextPutAll: ';']].
 	nestedBlocks := nestedBlocks - 1
-
 !
 
 visitReturnNode: aNode
@@ -698,19 +624,16 @@ visitCascadeNode: aNode
 	stream nextPutAll: '})('.
 	self visit: aNode receiver.
 	stream nextPutAll: ')'
-
 !
 
 visitValueNode: aNode
 	stream nextPutAll: aNode value asJavascript
-
 !
 
 visitAssignmentNode: aNode
 	self visit: aNode left.
 	stream nextPutAll: '='.
 	self visit: aNode right
-
 !
 
 visitClassReferenceNode: aNode
@@ -729,7 +652,6 @@ visitVariableNode: aNode
 			(self knownVariables includes: aNode value) ifFalse: [
 				unknownVariables add: aNode value].
 			stream nextPutAll: aNode value]
-
 !
 
 visitJSStatementNode: aNode
@@ -761,6 +683,6 @@ Object subclass: #DoIt
 
 !DoIt methodsFor: ''!
 
-doIt ^[ChunkExporter new exportCategory: 'Parser' ] value
+doIt ^['abc' trimLeft: 'az'] value
 ! !
 

+ 0 - 4
st/Examples.st

@@ -19,7 +19,6 @@ decrease
 initialize
     super initialize.
     count := 0
-
 ! !
 
 !Counter methodsFor: 'rendering'!
@@ -34,7 +33,6 @@ renderOn: html
     html button
 	with: '--';
 	onClick: [self decrease]
-
 ! !
 
 Widget subclass: #Tetris
@@ -57,7 +55,6 @@ squares
 
 gluePiece: aPiece
 	aPiece glueOn: self
-	
 !
 
 rows
@@ -83,7 +80,6 @@ nextStep
 		ifTrue: [movingPiece position: movingPiece position + (0@1)]
 		ifFalse: [self newPiece].
 	self redraw
-	
 !
 
 redraw

+ 0 - 111
st/IDE.st

@@ -6,29 +6,24 @@ Widget subclass: #TabManager
 
 tabs
     ^tabs ifNil: [tabs := Array new]
-
 ! !
 
 !TabManager methodsFor: 'actions'!
 
 updateBodyMargin
     self setBodyMargin: '#jtalk' asJQuery height + 27
-
 !
 
 updatePosition
     {'jQuery(''#jtalk'').css(''top'', '''''').css(''bottom'', ''27px'');'}
-
 !
 
 removeBodyMargin
     self setBodyMargin: 0
-
 !
 
 setBodyMargin: anInteger
     '.jtalkBody' asJQuery cssAt: 'margin-bottom' put: anInteger asString, 'px'
-
 !
 
 onResize: aBlock
@@ -37,12 +32,10 @@ onResize: aBlock
 	resize: aBlock,
 	minHeight: 230
 });'}
-
 !
 
 onWindowResize: aBlock
     {'jQuery(window).resize(aBlock)'}
-
 !
 
 open
@@ -53,7 +46,6 @@ open
 	self updateBodyMargin.
 	selectedTab root asJQuery show.
 	opened := true]
-
 !
 
 close
@@ -63,12 +55,10 @@ close
 	self removeBodyMargin.
 	'body' asJQuery removeClass: 'jtalkBody'.
 	opened := false]
-
 !
 
 newBrowserTab
     Browser open
-
 !
 
 selectTab: aWidget
@@ -78,7 +68,6 @@ selectTab: aWidget
 	each root asJQuery hide].
     aWidget root asJQuery show.
     self update
-
 !
 
 closeTab: aWidget
@@ -86,7 +75,6 @@ closeTab: aWidget
     self selectTab: self tabs last.
     aWidget root asJQuery remove.
     self update
-
 ! !
 
 !TabManager methodsFor: 'adding/Removing'!
@@ -95,13 +83,11 @@ addTab: aWidget
     self tabs add: aWidget.
     '#jtalk' asJQuery append: aWidget.
     aWidget root asJQuery hide
-
 !
 
 removeTab: aWidget
     self tabs remove: aWidget.
     self update
-
 ! !
 
 !TabManager methodsFor: 'initialization'!
@@ -120,7 +106,6 @@ initialize
     self 
 	onResize: [self updateBodyMargin; updatePosition];
 	onWindowResize: [self updatePosition]
-
 ! !
 
 !TabManager methodsFor: 'rendering'!
@@ -139,7 +124,6 @@ renderOn: html
 		class: 'newtab';
 		with: ' + ';
 		onClick: [self newBrowserTab]]
-
 !
 
 renderTabFor: aWidget on: html
@@ -156,7 +140,6 @@ renderTabFor: aWidget on: html
 		class: 'close';
 		with: 'x';
 		onClick: [self closeTab: aWidget]]]
-
 ! !
 
 TabManager class instanceVariableNames: 'current'!
@@ -165,12 +148,10 @@ TabManager class instanceVariableNames: 'current'!
 
 current
     ^current ifNil: [current := super new]
-
 !
 
 new
     self shouldNotImplement
-
 ! !
 
 Widget subclass: #TabWidget
@@ -181,7 +162,6 @@ Widget subclass: #TabWidget
 
 label
     self subclassResponsibility
-
 ! !
 
 !TabWidget methodsFor: 'actions'!
@@ -190,7 +170,6 @@ open
     TabManager current
 	addTab: self;
 	selectTab: self
-
 ! !
 
 !TabWidget methodsFor: 'rendering'!
@@ -205,29 +184,24 @@ renderOn: html
 	    html div
 		class: 'jt_buttons';
 		with: [self renderButtonsOn: html]]
-
 !
 
 renderBoxOn: html
-
 !
 
 renderButtonsOn: html
-
 ! !
 
 !TabWidget methodsFor: 'testing'!
 
 canBeClosed
     ^false
-
 ! !
 
 !TabWidget class methodsFor: 'instance creation'!
 
 open
     ^self new open
-
 ! !
 
 TabWidget subclass: #Workspace
@@ -238,32 +212,26 @@ TabWidget subclass: #Workspace
 
 label
     ^'[Workspace]'
-
 !
 
 selection
     {'return document.selection'}
-
 !
 
 selectionStart
     {'return jQuery(''.jt_workspace'')[0].selectionStart'}
-
 !
 
 selectionEnd
     {'return jQuery(''.jt_workspace'')[0].selectionEnd'}
-
 !
 
 selectionStart: anInteger
     {'jQuery(''.jt_workspace'')[0].selectionStart = anInteger'}
-
 !
 
 selectionEnd: anInteger
     {'jQuery(''.jt_workspace'')[0].selectionEnd = anInteger'}
-
 !
 
 currentLine
@@ -276,7 +244,6 @@ currentLine
 	endLine >= self selectionStart ifTrue: [
 	    self selectionEnd: endLine.
 	    ^each]]
-
 ! !
 
 !Workspace methodsFor: 'actions'!
@@ -299,12 +266,10 @@ handleKeyDown: anEvent
 			return false;
 		}
 	}'}
-
 !
 
 clearWorkspace
     textarea asJQuery val: ''
-
 !
 
 doIt
@@ -319,7 +284,6 @@ doIt
 
 printIt
     self print: self doIt printString
-
 !
 
 print: aString
@@ -331,7 +295,6 @@ print: aString
 	(textarea asJQuery val copyFrom: start + 1 to: textarea asJQuery val size)).
     self selectionStart: start.
     self selectionEnd: start + aString size + 2
-
 !
 
 eval: aString
@@ -341,12 +304,10 @@ eval: aString
     node isParseFailure ifTrue: [
 	^self alert: node reason, ', position: ', node position].
     ^compiler loadExpression: aString
-
 !
 
 inspectIt
     self doIt inspect
-
 ! !
 
 !Workspace methodsFor: 'rendering'!
@@ -358,7 +319,6 @@ renderBoxOn: html
     textarea 
 	class: 'jt_workspace';
 	at: 'spellcheck' put: 'false'
-
 !
 
 renderButtonsOn: html
@@ -377,7 +337,6 @@ renderButtonsOn: html
     html button
 	with: 'Clear workspace';
 	onClick: [self clearWorkspace]
-
 ! !
 
 TabWidget subclass: #Transcript
@@ -388,25 +347,20 @@ TabWidget subclass: #Transcript
 
 label
     ^'[Transcript]'
-
 ! !
 
 !Transcript methodsFor: 'actions'!
 
 show: anObject
     textarea asJQuery val: textarea asJQuery val, anObject asString.
-
-
 !
 
 cr
     textarea asJQuery val: textarea asJQuery val, String cr.
-
 !
 
 clear
     textarea asJQuery val: ''
-
 ! !
 
 !Transcript methodsFor: 'rendering'!
@@ -417,14 +371,12 @@ renderBoxOn: html
     textarea 
 	class: 'jt_transcript';
 	at: 'spellcheck' put: 'false'
-
 !
 
 renderButtonsOn: html
     html button
 	with: 'Clear transcript';
 	onClick: [self clear]
-
 ! !
 
 Transcript class instanceVariableNames: 'current'!
@@ -433,34 +385,28 @@ Transcript class instanceVariableNames: 'current'!
 
 open
     self current open
-
 !
 
 new
     self shouldNotImplement
-
 !
 
 current
     ^current ifNil: [current := super new]
-
 ! !
 
 !Transcript class methodsFor: 'printing'!
 
 show: anObject
     self current show: anObject
-
 !
 
 cr
     self current show: String cr
-
 !
 
 clear
     self current clear
-
 ! !
 
 TabWidget subclass: #Browser
@@ -473,7 +419,6 @@ label
     ^selectedClass 
 	ifNil: ['Browser (nil)']
 	ifNotNil: [selectedClass name]
-
 !
 
 categories
@@ -483,14 +428,12 @@ categories
 	(categories includes: each category) ifFalse: [
 	    categories add: each category]].
     ^categories sort
-
 !
 
 classes
     ^(Smalltalk current classes 
 	select: [:each | each category = selectedCategory])
 	sort: [:a :b | a name > b name]
-
 !
 
 protocols
@@ -521,7 +464,6 @@ methods
 	ifNotNil: [
 	    klass methodDictionary values select: [:each |
 		each category = selectedProtocol]]) sort: [:a :b | a selector > b selector]
-
 !
 
 source
@@ -532,14 +474,12 @@ source
     ^selectedClass
 	ifNil: ['']
 	ifNotNil: [self classCommentSource]
-
 !
 
 methodSource
     ^selectedMethod
 	ifNil: [self dummyMethodSource]
 	ifNotNil: [selectedMethod source]
-
 !
 
 dummyMethodSource
@@ -548,14 +488,12 @@ dummyMethodSource
 
 	| temporary variable names |
 	statements'
-
 !
 
 declarationSource
     ^selectedTab = #instance
 	ifTrue: [self classDeclarationSource]
 	ifFalse: [self metaclassDeclarationSource]
-
 !
 
 classDeclarationSource
@@ -577,7 +515,6 @@ classDeclarationSource
 	    nextPutAll: selectedClass category;
 	    nextPutAll: ''''].
     ^stream contents
-
 !
 
 metaclassDeclarationSource
@@ -593,12 +530,10 @@ metaclassDeclarationSource
 	    separatedBy: [stream nextPutAll: ' '].
 	stream nextPutAll: ''''].
     ^stream contents
-
 !
 
 classCommentSource
     ^selectedClass comment
-
 ! !
 
 !Browser methodsFor: 'actions'!
@@ -606,34 +541,28 @@ classCommentSource
 enableSaveButton
     saveButton removeAt: 'disabled'.
     unsavedChanges := true
-
 !
 
 disableSaveButton
     saveButton ifNotNil: [
 	saveButton at: 'disabled' put: true].
     unsavedChanges := false
-
 !
 
 hideClassButtons
     classButtons asJQuery hide
-
 !
 
 showClassButtons
     classButtons asJQuery show
-
 !
 
 hideMethodButtons
     methodButtons asJQuery hide
-
 !
 
 showMethodButtons
     methodButtons asJQuery show
-
 !
 
 compile
@@ -644,19 +573,16 @@ compile
     (selectedProtocol notNil or: [selectedMethod notNil])
 	ifFalse: [self compileDefinition]
 	ifTrue: [self compileMethodDefinition]
-
 !
 
 compileClassComment
     selectedClass comment: sourceTextarea asJQuery val
-
 !
 
 compileMethodDefinition
     selectedTab = #instance
 	ifTrue: [self compileMethodDefinitionFor: selectedClass]
 	ifFalse: [self compileMethodDefinitionFor: selectedClass class]
-
 !
 
 compileMethodDefinitionFor: aClass
@@ -677,7 +603,6 @@ compileMethodDefinitionFor: aClass
     aClass addCompiledMethod: method.
     self updateMethodsList.
     self selectMethod: method
-
 !
 
 compileDefinition
@@ -686,7 +611,6 @@ compileDefinition
     self 
 	updateCategoriesList;
 	updateClassesList
-
 !
 
 commitCategory
@@ -701,14 +625,12 @@ commitCategory
 	    at: 'data' put: (ChunkExporter new exportCategory: selectedCategory);
 	    at: 'error' put: [self alert: 'Commit failed!!'];
 	    send]
-
 !
 
 cancelChanges
     ^unsavedChanges 
 	ifTrue: [self confirm: 'Cancel changes?']
 	ifFalse: [true]
-
 !
 
 removeClass
@@ -716,7 +638,6 @@ removeClass
 	ifTrue: [
 	    Smalltalk current basicDelete: selectedClass name.
 	    self selectClass: nil]
-
 !
 
 removeMethod
@@ -727,7 +648,6 @@ removeMethod
 			ifTrue: [selectedClass removeCompiledMethod: selectedMethod]
 			ifFalse: [selectedClass class removeCompiledMethod: selectedMethod].
 		self selectMethod: nil]]
-
 !
 
 setMethodProtocol: aString
@@ -742,7 +662,6 @@ setMethodProtocol: aString
 		    updateProtocolsList;
 		    updateMethodsList;
 		    updateSourceAndButtons]]
-
 !
 
 addNewProtocol
@@ -751,7 +670,6 @@ addNewProtocol
     newProtocol notEmpty ifTrue: [
 	selectedMethod category: newProtocol.
 	self setMethodProtocol: newProtocol]
-
 !
 
 selectCategory: aCategory
@@ -764,7 +682,6 @@ selectCategory: aCategory
 	    updateProtocolsList;
 	    updateMethodsList;
 	    updateSourceAndButtons]
-
 !
 
 selectClass: aClass
@@ -776,7 +693,6 @@ selectClass: aClass
 	    updateProtocolsList;
 	    updateMethodsList;
 	    updateSourceAndButtons]
-
 !
 
 selectProtocol: aString
@@ -787,7 +703,6 @@ selectProtocol: aString
 	    updateProtocolsList;
 	    updateMethodsList;
 	    updateSourceAndButtons]
-
 !
 
 selectMethod: aMethod
@@ -797,7 +712,6 @@ selectMethod: aMethod
 	    updateProtocolsList;
 	    updateMethodsList;
 	    updateSourceAndButtons]
-
 !
 
 selectTab: aString
@@ -805,7 +719,6 @@ selectTab: aString
 	selectedTab := aString.
 	self selectProtocol: nil.
 	self updateTabsList]
-
 !
 
 renameClass
@@ -816,7 +729,6 @@ renameClass
 	self 
 		updateClassesList;
 		updateSourceAndButtons]
-
 !
 
 addInstanceVariableNamed: aString toClass: aClass
@@ -838,7 +750,6 @@ initialize
     super initialize.
     selectedTab := #instance.
     unsavedChanges := false
-
 ! !
 
 !Browser methodsFor: 'rendering'!
@@ -848,7 +759,6 @@ renderBoxOn: html
 	renderTopPanelOn: html;
 	renderTabsOn: html;
 	renderBottomPanelOn: html
-
 !
 
 renderTopPanelOn: html
@@ -870,13 +780,11 @@ renderTopPanelOn: html
 		updateProtocolsList;
 		updateMethodsList.
 	    html div class: 'jt_clear']
-
 !
 
 renderTabsOn: html
     tabsList := html ul class: 'jt_tabs'.
     self updateTabsList.
-
 !
 
 renderBottomPanelOn: html
@@ -888,7 +796,6 @@ renderBottomPanelOn: html
 		class: 'source';
 		at: 'spellcheck' put: 'false'.
 	    sourceTextarea asJQuery call: 'tabby']
-
 !
 
 renderButtonsOn: html
@@ -899,14 +806,12 @@ renderButtonsOn: html
     methodButtons := html span.
     classButtons := html span.
     self updateSourceAndButtons
-
 ! !
 
 !Browser methodsFor: 'testing'!
 
 canBeClosed
     ^true
-
 ! !
 
 !Browser methodsFor: 'updating'!
@@ -923,7 +828,6 @@ updateCategoriesList
 	    li
 		with: label;
 		onClick: [self selectCategory: each]]]
-
 !
 
 updateClassesList
@@ -936,7 +840,6 @@ updateClassesList
 	    li
 		with: each name;
 		onClick: [self selectClass: each]]]
-
 !
 
 updateProtocolsList
@@ -948,7 +851,6 @@ updateProtocolsList
 	    li 
 		with: each;
 		onClick: [self selectProtocol: each]]]
-
 !
 
 updateMethodsList
@@ -960,7 +862,6 @@ updateMethodsList
 	    li
 		with: each selector;
 		onClick: [self selectMethod: each]]]
-
 !
 
 updateTabsList
@@ -980,7 +881,6 @@ updateTabsList
 	li
 	    with: 'Comment';
 	    onClick: [self selectTab: #comment]]
-
 !
 
 updateSourceAndButtons
@@ -1032,7 +932,6 @@ updateSourceAndButtons
 	    		self hideClassButtons.
 	    		self showMethodButtons].
     	sourceTextarea asJQuery val: self source
-
 ! !
 
 !Browser class methodsFor: 'accessing'!
@@ -1052,12 +951,10 @@ openOn: aClass
 	open;
 	selectCategory: aClass category;
 	selectClass: aClass
-
 !
 
 open
     self new open
-
 ! !
 
 TabWidget subclass: #Inspector
@@ -1127,7 +1024,6 @@ renderTopPanelOn: html
 		updateVariablesList;
 		updateValueTextarea.
 	    html div class: 'jt_clear']
-
 !
 
 renderBottomPanelOn: html
@@ -1138,7 +1034,6 @@ renderBottomPanelOn: html
 		class: 'source';
 		at: 'spellcheck' put: 'false'.
 	    workspaceTextarea asJQuery call: 'tabby']
-
 !
 
 renderButtonsOn: html
@@ -1149,7 +1044,6 @@ renderButtonsOn: html
 		with: 'Dive'; 
 		onClick: [self dive].
 	self updateButtons
-	
 ! !
 
 !Inspector methodsFor: 'testing'!
@@ -1189,7 +1083,6 @@ updateButtons
 	(self selectedVariable notNil and: [(self variables at: self selectedVariable) notNil])
 		ifFalse: [diveButton at: 'disabled' put: true] 
 		ifTrue: [diveButton removeAt: 'disabled']
-		
 ! !
 
 !Inspector class methodsFor: 'instance creation'!
@@ -1394,8 +1287,6 @@ inspectOn: anInspector
 	anInspector 
 		setLabel: self printString;
 		setVariables: variables
-	
-	
 ! !
 
 !Date methodsFor: '*IDE'!
@@ -1414,8 +1305,6 @@ inspectOn: anInspector
 	anInspector 
 		setLabel: self printString;
 		setVariables: variables
-	
-	
 ! !
 
 !Collection methodsFor: '*IDE'!

+ 1 - 51
st/JQuery.st

@@ -7,25 +7,21 @@ Object subclass: #JQuery
 append: anObject
     "Append anObject at the end of the element."
     anObject appendToJQuery: self
-
 !
 
 appendElement: anElement
     "Append anElement at the end of the element.
      Dont't call this method directly, use #append: instead"
     self call: 'append' withArgument: anElement
-
 !
 
 appendToJQuery: aJQuery
     aJQuery appendElement: jquery
-
 !
 
 contents: anObject
     self empty.
     self append: anObject
-
 !
 
 empty
@@ -37,24 +33,20 @@ empty
 removeAttribute: aString
     "Remove an attribute from each element in the set of matched elements."
     ^self call: 'removeAttribute' withArgument: aString
-
 !
 
 attr: aString
     "Get the value of an attribute for the first element in the set of matched elements."
     ^self call: 'attr' withArgument: aString
-
 !
 
 val
     "Get the current value of the first element in the set of matched elements."
     ^self call: 'val'
-
 !
 
 val: aString
     self call: 'val' withArgument: aString
-
 ! !
 
 !JQuery methodsFor: 'css'!
@@ -65,158 +57,131 @@ cssAt: aString
 
 cssAt: aString put: anotherString
     {'self[''@jquery''].css(aString, anotherString)'}
-
 !
 
 addClass: aString
     "Adds the specified class(es) to each of the set of matched elements."
     self call: 'addClass' withArgument: aString
-
 !
 
 removeClass: aString
     "Remove a single class, multiple classes, or all classes from each element in the set of matched elements."
     self call: 'removeClass' withArgument: aString
-
 !
 
 toggleClass: aString
     "Add or remove one or more classes from each element in the set of matched elements, depending on either the class's presence or the value of the switch argument."
     self call: 'toggleClass' withArgument: aString
-
 !
 
 height 
     "Get the current computed height for the first element in the set of matched elements."
     ^self call: 'height'
-
 !
 
 height: anInteger
     self call: 'height' withArgument: anInteger
-
 !
 
 width: anInteger
     self call: 'width' withArgument: anInteger
-
 !
 
 width
     "Get the current computed width for the first element in the set of matched elements."
     ^self call: 'width'
-
 !
 
 innerHeight
     "Get the current computed height for the first element in the set of matched elements, including padding but not border."
     ^self call: 'innerHeight'
-
 !
 
 innerWidth
     "Get the current computed width for the first element in the set of matched elements, including padding but not border."
     ^self call: 'innerWidth'
-
 !
 
 outerHeight
     "Get the current computed height for the first element in the set of matched elements, including padding, border, and optionally margin."
     ^self call: 'outerHeight'
-
 !
 
 outerWidth
     "Get the current computed width for the first element in the set of matched elements, including padding and border."
     ^self call: 'outerWidth'
-
 !
 
 top
     "Get the current y coordinate of the first element in the set of matched elements, relative to the offset parent."
     ^(self call: 'position') basicAt: 'top'
-
 !
 
 left
     "Get the current x coordinate of the first element in the set of matched elements, relative to the offset parent."
     ^(self call: 'position') basicAt: 'left'
-
 !
 
 offsetLeft
     "Get the current coordinates of the first element in the set of matched elements, relative to the document."
     ^(self call: 'offset') basicAt: 'left'
-
 !
 
 offsetTop
     "Get the current coordinates of the first element in the set of matched elements, relative to the document."
     ^(self call: 'offset') basicAt: 'top'
-
 !
 
 scrollLeft
     "Get the current horizontal position of the scroll bar for the first element in the set of matched elements."
     ^self call: 'scrollLeft'
-
 !
 
 scrollTop
     "Get the current vertical position of the scroll bar for the first element in the set of matched elements."
     ^self call: 'scrollTop'
-
 !
 
 scrollLeft: anInteger
     self call: 'scrollLeft' withArgument: anInteger
-
 !
 
 scrollTop: anInteger
     self call: 'scrollTop' withArgument: anInteger
-
 ! !
 
 !JQuery methodsFor: 'events'!
 
 focus
     self call: 'focus'
-
 !
 
 show
     self call: 'show'
-
 !
 
 hide
     self call: 'hide'
-
 !
 
 remove
     self call: 'remove'
-
 !
 
 on: anEventString do: aBlock
     "Attach aBlock for anEventString on the element"
     {'self[''@jquery''].bind(anEventString, function(e){aBlock(e, self)})'}
-
 !
 
 removeEvents: aString
     "Unbind all handlers attached to the event aString"
     self call: 'unbind' withArgument: aString
-
 ! !
 
 !JQuery methodsFor: 'initialization'!
 
 initializeWithJQueryObject: anObject
     jquery := anObject
-
 ! !
 
 !JQuery methodsFor: 'private'!
@@ -234,7 +199,6 @@ call: aString withArgument: anObject
 hasClass: aString
     "Determine whether any of the matched elements are assigned the given class."
     ^self call: 'hasClass' withArgument: aString
-
 ! !
 
 !JQuery class methodsFor: 'instance creation'!
@@ -243,14 +207,12 @@ fromString: aString
     | newJQuery |
     {'newJQuery = jQuery(String(aString))'}.
     ^self from: newJQuery
-
 !
 
 from: anObject
     ^self new
 	initializeWithJQueryObject: anObject;
 	yourself
-
 !
 
 window
@@ -272,36 +234,30 @@ Object subclass: #Ajax
 instance variable names:
 - settings  A set of key/value pairs that configure the Ajax request. All settings are optional.
 
-Full list of settings options at http://api.jquery.com/jQuery.ajax/
-!
+Full list of settings options at http://api.jquery.com/jQuery.ajax/!
 
 !Ajax methodsFor: 'accessing'!
 
 at: aKey
     ^settings at: aKey ifAbsent: [nil]
-
 !
 
 at: aKey put: aValue
     settings at: aKey put: aValue
-
 !
 
 url
     ^self at: 'url'
-
 !
 
 url: aString
     self at: 'url' put: aString
-
 ! !
 
 !Ajax methodsFor: 'actions'!
 
 send
     {'jQuery.ajax(self[''@settings''])'}
-
 ! !
 
 !Ajax methodsFor: 'initialization'!
@@ -309,7 +265,6 @@ send
 initialize
     super initialize.
     settings := Dictionary new
-
 ! !
 
 !Ajax class methodsFor: 'instance creation'!
@@ -318,7 +273,6 @@ url: aString
     ^self new
 	url: aString;
 	yourself
-
 ! !
 
 !BlockClosure methodsFor: '*JQuery'!
@@ -328,25 +282,21 @@ appendToJQuery: aJQuery
 	canvas := HTMLCanvas new.
 	self value: canvas.
 	aJQuery append: canvas
-
 ! !
 
 !String methodsFor: '*JQuery'!
 
 asJQuery
     ^JQuery fromString: self
-
 !
 
 appendToJQuery: aJQuery
     {'aJQuery._appendElement_(String(self))'}
-
 ! !
 
 !HTMLCanvas methodsFor: '*JQuery'!
 
 appendToJQuery: aJQuery
     aJQuery appendElement: root element
-
 ! !
 

File diff suppressed because it is too large
+ 26 - 160
st/Kernel.st


+ 2 - 82
st/Parser.st

@@ -6,61 +6,50 @@ Object subclass: #PPParser
 
 memo
 	^memo
-
 ! !
 
 !PPParser methodsFor: 'initialization'!
 
 initialize
 	memo := Dictionary new
-
 ! !
 
 !PPParser methodsFor: 'operations'!
 
 flatten
 	^PPFlattenParser on: self
-
 !
 
 withSource
 	^PPSourceParser on: self
-
 !
 
 ==> aBlock
 	^PPActionParser on: self block: aBlock
-
 !
 
 , aParser
 	^PPSequenceParser with: self with: aParser
-
 !
 
 / aParser
 	^PPChoiceParser with: self with: aParser
-
 !
 
 plus
 	^PPRepeatingParser on: self min: 1
-
 !
 
 star
 	^PPRepeatingParser on: self min: 0
-
 !
 
 not
 	^PPNotParser on: self
-
 !
 
 optional
 	^self / PPEpsilonParser new
-
 !
 
 memoizedParse: aStream
@@ -75,14 +64,12 @@ memoizedParse: aStream
 		end := aStream position.
 		self memo at: start put: (Array with: node with: end).
 		node]
-
 ! !
 
 !PPParser methodsFor: 'parsing'!
 
 parse: aStream
 	self subclassResponsibility
-
 !
 
 parseAll: aStream
@@ -91,7 +78,6 @@ parseAll: aStream
 	^result isParseFailure 
 	    ifTrue: [self error: (result messageFor: aStream contents)]
 	    ifFalse: [result first]
-
 ! !
 
 PPParser subclass: #PPEOFParser
@@ -105,7 +91,6 @@ parse: aStream
 	    ifFalse: [
 		PPFailure new reason: aStream contents, String lf, '---------------', String lf, 'EOF expected' at: aStream position]
 	    ifTrue: [nil]
-
 ! !
 
 PPParser subclass: #PPAnyParser
@@ -119,7 +104,6 @@ parse: aStream
 	    ifTrue: [PPFailure new
 			 reason: 'did not expect EOF' at: aStream position]
 	    ifFalse: [aStream next]
-
 ! !
 
 PPParser subclass: #PPEpsilonParser
@@ -130,7 +114,6 @@ PPParser subclass: #PPEpsilonParser
 
 parse: aStream
 	^nil
-
 ! !
 
 PPParser subclass: #PPStringParser
@@ -141,12 +124,10 @@ PPParser subclass: #PPStringParser
 
 string
 	^string
-
 !
 
 string: aString
 	string := aString
-
 ! !
 
 !PPStringParser methodsFor: 'parsing'!
@@ -160,7 +141,6 @@ parse: aStream
 	    ifFalse: [
 		aStream position: position.
 		PPFailure new reason: 'Expected ', self string, ' but got ', (result at: position) printString; yourself]
-
 ! !
 
 PPParser subclass: #PPCharacterParser
@@ -171,7 +151,6 @@ PPParser subclass: #PPCharacterParser
 
 string: aString
 	regexp := RegularExpression fromString: '[', aString, ']'
-
 ! !
 
 !PPCharacterParser methodsFor: 'parsing'!
@@ -180,14 +159,12 @@ parse: aStream
 	^(aStream peek notNil and: [self match: aStream peek])
 	    ifTrue: [aStream next]
 	    ifFalse: [PPFailure new reason: 'Could not match' at: aStream position]
-
 ! !
 
 !PPCharacterParser methodsFor: 'private'!
 
 match: aString
 	^aString match: regexp
-
 ! !
 
 PPParser subclass: #PPListParser
@@ -198,19 +175,16 @@ PPParser subclass: #PPListParser
 
 parsers
 	^parsers ifNil: [#()]
-
 !
 
 parsers: aCollection
 	parsers := aCollection
-
 ! !
 
 !PPListParser methodsFor: 'copying'!
 
 copyWith: aParser
 	^self class withAll: (self parsers copyWith: aParser)
-
 ! !
 
 !PPListParser class methodsFor: 'instance creation'!
@@ -219,12 +193,10 @@ withAll: aCollection
 	    ^self new
 		parsers: aCollection;
 		yourself
-
 !
 
 with: aParser with: anotherParser
 	    ^self withAll: (Array with: aParser with: anotherParser)
-
 ! !
 
 PPListParser subclass: #PPSequenceParser
@@ -235,7 +207,6 @@ PPListParser subclass: #PPSequenceParser
 
 , aRule
 	^self copyWith: aRule
-
 ! !
 
 !PPSequenceParser methodsFor: 'parsing'!
@@ -253,7 +224,6 @@ parse: aStream
 	^element isParseFailure
 	    ifFalse: [elements]
 	    ifTrue: [aStream position: start. element]
-
 ! !
 
 PPListParser subclass: #PPChoiceParser
@@ -264,7 +234,6 @@ PPListParser subclass: #PPChoiceParser
 
 / aRule
 	^self copyWith: aRule
-
 ! !
 
 !PPChoiceParser methodsFor: 'parsing'!
@@ -277,7 +246,6 @@ parse: aStream
 		result isParseFailure not]
 	    ifNone: [].
 	^result
-
 ! !
 
 PPParser subclass: #PPDelegateParser
@@ -288,19 +256,16 @@ PPParser subclass: #PPDelegateParser
 
 parser
 	^parser
-
 !
 
 parser: aParser
 	parser := aParser
-
 ! !
 
 !PPDelegateParser methodsFor: 'parsing'!
 
 parse: aStream
 	^self parser memoizedParse: aStream
-
 ! !
 
 !PPDelegateParser class methodsFor: 'instance creation'!
@@ -309,7 +274,6 @@ on: aParser
 	    ^self new
 		parser: aParser;
 		yourself
-
 ! !
 
 PPDelegateParser subclass: #PPAndParser
@@ -320,7 +284,6 @@ PPDelegateParser subclass: #PPAndParser
 
 parse: aStream
 	^self basicParse: aStream
-
 !
 
 basicParse: aStream
@@ -329,7 +292,6 @@ basicParse: aStream
 	element := self parser memoizedParse: aStream.
 	aStream position: position.
 	^element
-
 ! !
 
 PPAndParser subclass: #PPNotParser
@@ -344,7 +306,6 @@ parse: aStream
 	^element isParseFailure 
 	    ifTrue: [nil]
 	    ifFalse: [PPFailure reason: element at: aStream position]
-
 ! !
 
 PPDelegateParser subclass: #PPActionParser
@@ -355,12 +316,10 @@ PPDelegateParser subclass: #PPActionParser
 
 block
 	^block
-
 !
 
 block: aBlock
 	block := aBlock
-
 ! !
 
 !PPActionParser methodsFor: 'parsing'!
@@ -371,7 +330,6 @@ parse: aStream
 	^element isParseFailure
 	    ifFalse: [self block value: element]
 	    ifTrue: [element]
-
 ! !
 
 !PPActionParser class methodsFor: 'instance creation'!
@@ -381,7 +339,6 @@ on: aParser block: aBlock
 		parser: aParser;
 		block: aBlock;
 		yourself
-
 ! !
 
 PPDelegateParser subclass: #PPFlattenParser
@@ -399,7 +356,6 @@ parse: aStream
 	    ifFalse: [aStream collection 
 		copyFrom: start + 1 
 		to: aStream position]
-
 ! !
 
 PPDelegateParser subclass: #PPSourceParser
@@ -416,7 +372,6 @@ parse: aStream
 		ifTrue: [element]
 		ifFalse: [result := aStream collection copyFrom: start + 1 to: aStream position.
 			Array with: element with: result].
-
 ! !
 
 PPDelegateParser subclass: #PPRepeatingParser
@@ -427,12 +382,10 @@ PPDelegateParser subclass: #PPRepeatingParser
 
 min
 	^min
-
 !
 
 min: aNumber
 	min := aNumber
-
 ! !
 
 !PPRepeatingParser methodsFor: 'parsing'!
@@ -455,7 +408,6 @@ parse: aStream
 				ifFalse: [elements addLast: element]].
 				elements]
 		ifNotNil: [failure].
-
 ! !
 
 !PPRepeatingParser class methodsFor: 'instance creation'!
@@ -465,7 +417,6 @@ on: aParser min: aNumber
 		parser: aParser;
 		min: aNumber;
 		yourself
-
 ! !
 
 Object subclass: #PPFailure
@@ -476,29 +427,24 @@ Object subclass: #PPFailure
 
 position
 	^position ifNil: [0]
-
 !
 
 position: aNumber
 	position := aNumber
-
 !
 
 reason
 	^reason ifNil: ['']
-
 !
 
 reason: aString
 	reason := aString
-
 !
 
 reason: aString at: anInteger
 	self 
 	    reason: aString; 
 	    position: anInteger
-
 !
 
 accept: aVisitor
@@ -509,7 +455,6 @@ accept: aVisitor
 
 isParseFailure
 	^true
-
 !
 
 asString
@@ -522,7 +467,6 @@ reason: aString at: anInteger
 	    ^self new
 		reason: aString at: anInteger;
 		yourself
-
 ! !
 
 Object subclass: #SmalltalkParser
@@ -694,14 +638,12 @@ parser
 		    yourself].
 	
 	^method, PPEOFParser new ==> [:node | node first]
-
 ! !
 
 !SmalltalkParser methodsFor: 'parsing'!
 
 parse: aStream
 	^self parser parse: aStream
-
 ! !
 
 !SmalltalkParser class methodsFor: 'instance creation'!
@@ -709,7 +651,6 @@ parse: aStream
 parse: aStream
 	    ^self new
 		parse: aStream
-
 ! !
 
 Object subclass: #Chunk
@@ -720,24 +661,20 @@ Object subclass: #Chunk
 
 contents
 	^contents ifNil: ['']
-
 !
 
 contents: aString
 	contents := aString
-
 ! !
 
 !Chunk methodsFor: 'testing'!
 
 isEmptyChunk
 	^false
-
 !
 
 isInstructionChunk
 	^false
-
 ! !
 
 Chunk subclass: #InstructionChunk
@@ -748,7 +685,6 @@ Chunk subclass: #InstructionChunk
 
 isInstructionChunk
 	^true
-
 ! !
 
 Chunk subclass: #EmptyChunk
@@ -759,7 +695,6 @@ Chunk subclass: #EmptyChunk
 
 isEmptyChunk
 	^true
-
 ! !
 
 Object subclass: #ChunkParser
@@ -772,7 +707,6 @@ instructionChunk
 	^instructionChunk ifNil: [
 	    instructionChunk := self ws, '!!' asParser, self chunk
 	    ==> [:node | InstructionChunk new contents: node last contents]]
-
 ! !
 
 !ChunkParser methodsFor: 'accessing'!
@@ -780,32 +714,26 @@ instructionChunk
 parser
 	^parser ifNil: [
 	    parser := self instructionChunk / self emptyChunk / self chunk / self eof]
-
 !
 
 eof
 	^eof ifNil: [eof := self ws, PPEOFParser new ==> [:node | nil]]
-
 !
 
 separator
 	^separator ifNil: [separator := (String cr, String space, String lf, String tab) asChoiceParser]
-
 !
 
 ws
 	^ws ifNil: [ws := self separator star]
-
 !
 
 chunk
 	^chunk ifNil: [chunk := self ws, ('!!!!' asParser / ('!!' asParser not, PPAnyParser new)) plus flatten, '!!' asParser ==> [:node | Chunk new contents: (node second replace: '!!!!' with: '!!')]]
-
 !
 
 emptyChunk
 	^emptyChunk ifNil: [emptyChunk := self separator plus, '!!' asParser, self ws ==> [:node | EmptyChunk new]]
-
 ! !
 
 Object subclass: #Importer
@@ -816,7 +744,6 @@ Object subclass: #Importer
 
 chunkParser
 	^chunkParser ifNil: [chunkParser := ChunkParser new parser]
-
 ! !
 
 !Importer methodsFor: 'fileIn'!
@@ -831,7 +758,6 @@ import: aStream
 					 scanFrom: aStream]
 		    ifFalse: [Compiler new loadExpression: nextChunk contents].
 		self import: aStream]]
-
 ! !
 
 Object subclass: #Exporter
@@ -858,7 +784,6 @@ export: aClass
 	self exportMetaDefinitionOf: aClass on: stream.
 	self exportMethodsOf: aClass class on: stream.
 	^stream contents
-
 ! !
 
 !Exporter methodsFor: 'private'!
@@ -884,7 +809,6 @@ exportDefinitionOf: aClass on: aStream
 		nextPutAll: '.comment=';
 		nextPutAll: 'unescape(''', aClass comment escaped, ''')'].
 	aStream lf
-
 !
 
 exportMetaDefinitionOf: aClass on: aStream
@@ -896,7 +820,6 @@ exportMetaDefinitionOf: aClass on: aStream
 		do: [:each | aStream nextPutAll: '''', each, '''']
 		separatedBy: [aStream nextPutAll: ','].
 	    aStream nextPutAll: '];', String lf]
-
 !
 
 exportMethodsOf: aClass on: aStream
@@ -913,7 +836,6 @@ classNameFor: aClass
 		aClass isNil
 		    ifTrue: ['nil']
 		    ifFalse: [aClass name]]
-
 !
 
 exportMethod: aMethod of: aClass on: aStream
@@ -968,7 +890,6 @@ exportDefinitionOf: aClass on: aStream
 		nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
 		nextPutAll: (self chunkEscape: aClass comment), '!!';lf].
 	aStream lf
-
 !
 
 exportMethod: aMethod of: aClass on: aStream
@@ -1011,10 +932,9 @@ classNameFor: aClass
 !
 
 chunkEscape: aString
-	"Replace all occurrences of !! with !!!!"
-
-	^aString replace: '!!' with: '!!!!'
+	"Replace all occurrences of !! with !!!! and trim at both ends."
 
+	^(aString replace: '!!' with: '!!!!') trimBoth
 !
 
 exportCategoryExtensions: aString on: aStream

+ 0 - 4
st/SUnit.st

@@ -76,7 +76,6 @@ TestCase subclass: #ExampleTest
 
 testFailure
 	self deny: true
-	
 !
 
 testPasses
@@ -131,7 +130,6 @@ TabWidget subclass: #TestRunner
 
 label
     ^'[Test runner]'
-
 !
 
 categories
@@ -274,7 +272,6 @@ renderButtonsOn: html
     html button
 	with: 'Run selected';
 	onClick: [self run: (self selectedClasses collect: [:each | each new])]
-
 !
 
 renderCategoriesOn: html
@@ -313,7 +310,6 @@ renderErrorsOn: html
 
 canBeClosed
     ^true
-
 !
 
 isSelectedClass: aClass

Some files were not shown because too many files changed in this diff