Browse Source

get rid of doubled 19543 character in chunk format

Dale Henrichs 13 years ago
parent
commit
0037fb7154
5 changed files with 398 additions and 398 deletions
  1. 2 2
      js/Compiler.deploy.js
  2. 3 3
      js/Compiler.js
  3. 99 99
      st/Compiler.st
  4. 160 160
      st/IDE.st
  5. 134 134
      st/Kernel-Objects.st

+ 2 - 2
js/Compiler.deploy.js

@@ -233,9 +233,9 @@ smalltalk.method({
 selector: unescape('exportMethods%3Acategory%3Aof%3Aon%3A'),
 selector: unescape('exportMethods%3Acategory%3Aof%3Aon%3A'),
 fn: function (methods, category, aClass, aStream){
 fn: function (methods, category, aClass, aStream){
 var self=this;
 var self=this;
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(unescape("%21%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%20methodsFor%3A%20%27"), "__comma", [category]), "__comma", [unescape("%27%21%21")])]);})(aStream);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%20methodsFor%3A%20%27"), "__comma", [category]), "__comma", [unescape("%27%21")])]);})(aStream);
 smalltalk.send(smalltalk.send(methods, "_sorted_", [(function(a, b){return ((($receiver = smalltalk.send(a, "_selector", [])).klass === smalltalk.Number) ? $receiver <=smalltalk.send(b, "_selector", []) : smalltalk.send($receiver, "__lt_eq", [smalltalk.send(b, "_selector", [])]));})]), "_do_", [(function(each){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);
 smalltalk.send(smalltalk.send(methods, "_sorted_", [(function(a, b){return ((($receiver = smalltalk.send(a, "_selector", [])).klass === smalltalk.Number) ? $receiver <=smalltalk.send(b, "_selector", []) : smalltalk.send($receiver, "__lt_eq", [smalltalk.send(b, "_selector", [])]));})]), "_do_", [(function(each){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%20%21%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%20%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
 return self;}
 return self;}
 }),
 }),
 smalltalk.ChunkExporter);
 smalltalk.ChunkExporter);

+ 3 - 3
js/Compiler.js

@@ -324,12 +324,12 @@ selector: unescape('exportMethods%3Acategory%3Aof%3Aon%3A'),
 category: 'not yet classified',
 category: 'not yet classified',
 fn: function (methods, category, aClass, aStream){
 fn: function (methods, category, aClass, aStream){
 var self=this;
 var self=this;
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(unescape("%21%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%20methodsFor%3A%20%27"), "__comma", [category]), "__comma", [unescape("%27%21%21")])]);})(aStream);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%20methodsFor%3A%20%27"), "__comma", [category]), "__comma", [unescape("%27%21")])]);})(aStream);
 smalltalk.send(smalltalk.send(methods, "_sorted_", [(function(a, b){return ((($receiver = smalltalk.send(a, "_selector", [])).klass === smalltalk.Number) ? $receiver <=smalltalk.send(b, "_selector", []) : smalltalk.send($receiver, "__lt_eq", [smalltalk.send(b, "_selector", [])]));})]), "_do_", [(function(each){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);
 smalltalk.send(smalltalk.send(methods, "_sorted_", [(function(a, b){return ((($receiver = smalltalk.send(a, "_selector", [])).klass === smalltalk.Number) ? $receiver <=smalltalk.send(b, "_selector", []) : smalltalk.send($receiver, "__lt_eq", [smalltalk.send(b, "_selector", [])]));})]), "_do_", [(function(each){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%20%21%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%20%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
 return self;},
 return self;},
 args: ["methods", "category", "aClass", "aStream"],
 args: ["methods", "category", "aClass", "aStream"],
-source: unescape('exportMethods%3A%20methods%20category%3A%20category%20of%3A%20aClass%20on%3A%20aStream%0A%20%20%20%20%22Issue%20%23143%3A%20sort%20methods%20alphabetically%22%0A%0A%20%20%20%20aStream%0A%20%20%20%20%20%20%20%20nextPutAll%3A%20%27%21%21%27%2C%20%28self%20classNameFor%3A%20aClass%29%3B%0A%20%20%20%20%20%20%20%20nextPutAll%3A%20%27%20methodsFor%3A%20%27%27%27%2C%20category%2C%20%27%27%27%21%21%27.%0A%20%20%20%20%20%20%20%20%28methods%20sorted%3A%20%5B%3Aa%20%3Ab%20%7C%20a%20selector%20%3C%3D%20b%20selector%5D%29%20do%3A%20%5B%3Aeach%20%7C%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20self%20exportMethod%3A%20each%20of%3A%20aClass%20on%3A%20aStream%5D.%0A%20%20%20%20aStream%20nextPutAll%3A%20%27%20%21%21%27%3B%20lf%3B%20lf'),
+source: unescape('exportMethods%3A%20methods%20category%3A%20category%20of%3A%20aClass%20on%3A%20aStream%0A%20%20%20%20%22Issue%20%23143%3A%20sort%20methods%20alphabetically%22%0A%0A%20%20%20%20aStream%0A%20%20%20%20%20%20%20%20nextPutAll%3A%20%27%21%27%2C%20%28self%20classNameFor%3A%20aClass%29%3B%0A%20%20%20%20%20%20%20%20nextPutAll%3A%20%27%20methodsFor%3A%20%27%27%27%2C%20category%2C%20%27%27%27%21%27.%0A%20%20%20%20%20%20%20%20%28methods%20sorted%3A%20%5B%3Aa%20%3Ab%20%7C%20a%20selector%20%3C%3D%20b%20selector%5D%29%20do%3A%20%5B%3Aeach%20%7C%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20self%20exportMethod%3A%20each%20of%3A%20aClass%20on%3A%20aStream%5D.%0A%20%20%20%20aStream%20nextPutAll%3A%20%27%20%21%27%3B%20lf%3B%20lf'),
 messageSends: ["nextPutAll:", unescape("%2C"), "classNameFor:", "do:", "sorted:", unescape("%3C%3D"), "selector", "exportMethod:of:on:", "lf"],
 messageSends: ["nextPutAll:", unescape("%2C"), "classNameFor:", "do:", "sorted:", unescape("%3C%3D"), "selector", "exportMethod:of:on:", "lf"],
 referencedClasses: []
 referencedClasses: []
 }),
 }),

+ 99 - 99
st/Compiler.st

@@ -3,13 +3,13 @@ Object subclass: #ChunkParser
 	instanceVariableNames: 'stream'
 	instanceVariableNames: 'stream'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!ChunkParser methodsFor: 'accessing'!!
+!ChunkParser methodsFor: 'accessing'!
 
 
 stream: aStream
 stream: aStream
 	stream := aStream
 	stream := aStream
-! !!
+! !
 
 
-!!ChunkParser methodsFor: 'reading'!!
+!ChunkParser methodsFor: 'reading'!
 
 
 nextChunk
 nextChunk
 	"The chunk format (Smalltalk Interchange Format or Fileout format)
 	"The chunk format (Smalltalk Interchange Format or Fileout format)
@@ -32,13 +32,13 @@ nextChunk
                                 ifFalse: [^result contents trimBoth  "chunk end marker found"]].
                                 ifFalse: [^result contents trimBoth  "chunk end marker found"]].
                  result nextPut: char].
                  result nextPut: char].
 	^nil "a chunk needs to end with !!"
 	^nil "a chunk needs to end with !!"
-! !!
+! !
 
 
-!!ChunkParser class methodsFor: 'not yet classified'!!
+!ChunkParser class methodsFor: 'not yet classified'!
 
 
 on: aStream
 on: aStream
 	^self new stream: aStream
 	^self new stream: aStream
-! !!
+! !
 
 
 Object subclass: #DoIt
 Object subclass: #DoIt
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -48,7 +48,7 @@ Object subclass: #Exporter
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!Exporter methodsFor: 'fileOut'!!
+!Exporter methodsFor: 'fileOut'!
 
 
 exportAll
 exportAll
     "Export all packages in the system."
     "Export all packages in the system."
@@ -79,9 +79,9 @@ exportPackage: packageName
 	    	package sortedClasses do: [:each |
 	    	package sortedClasses do: [:each |
                         stream nextPutAll: (self exportClass: each)].
                         stream nextPutAll: (self exportClass: each)].
 		self exportPackageExtensionsOf: package on: stream]
 		self exportPackageExtensionsOf: package on: stream]
-! !!
+! !
 
 
-!!Exporter methodsFor: 'private'!!
+!Exporter methodsFor: 'private'!
 
 
 classNameFor: aClass
 classNameFor: aClass
 	^aClass isMetaclass
 	^aClass isMetaclass
@@ -171,13 +171,13 @@ exportPackageExtensionsOf: package on: aStream
             ((aClass methodDictionary values) sorted: [:a :b | a selector <= b selector]) do: [:method |
             ((aClass methodDictionary values) sorted: [:a :b | a selector <= b selector]) do: [:method |
                 (method category match: '^\*', name) ifTrue: [
                 (method category match: '^\*', name) ifTrue: [
                     self exportMethod: method of: each on: aStream ]]]]
                     self exportMethod: method of: each on: aStream ]]]]
-! !!
+! !
 
 
 Exporter subclass: #ChunkExporter
 Exporter subclass: #ChunkExporter
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!ChunkExporter methodsFor: 'not yet classified'!!
+!ChunkExporter methodsFor: 'not yet classified'!
 
 
 chunkEscape: aString
 chunkEscape: aString
 	"Replace all occurrences of !! with !!!! and trim at both ends."
 	"Replace all occurrences of !! with !!!! and trim at both ends."
@@ -237,11 +237,11 @@ exportMethods: methods category: category of: aClass on: aStream
     "Issue #143: sort methods alphabetically"
     "Issue #143: sort methods alphabetically"
 
 
     aStream
     aStream
-        nextPutAll: '!!!!', (self classNameFor: aClass);
-        nextPutAll: ' methodsFor: ''', category, '''!!!!'.
+        nextPutAll: '!!', (self classNameFor: aClass);
+        nextPutAll: ' methodsFor: ''', category, '''!!'.
         (methods sorted: [:a :b | a selector <= b selector]) do: [:each |
         (methods sorted: [:a :b | a selector <= b selector]) do: [:each |
                 self exportMethod: each of: aClass on: aStream].
                 self exportMethod: each of: aClass on: aStream].
-    aStream nextPutAll: ' !!!!'; lf; lf
+    aStream nextPutAll: ' !!'; lf; lf
 !
 !
 
 
 exportMethodsOf: aClass on: aStream
 exportMethodsOf: aClass on: aStream
@@ -285,13 +285,13 @@ exportPackageExtensionsOf: package on: aStream
             (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: each on: aStream ]]]
                 self exportMethods: methods category: category of: each on: aStream ]]]
-! !!
+! !
 
 
 Exporter subclass: #StrippedExporter
 Exporter subclass: #StrippedExporter
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!StrippedExporter methodsFor: 'private'!!
+!StrippedExporter methodsFor: 'private'!
 
 
 exportDefinitionOf: aClass on: aStream
 exportDefinitionOf: aClass on: aStream
 	aStream 
 	aStream 
@@ -319,13 +319,13 @@ exportMethod: aMethod of: aClass on: aStream
 		nextPutAll: '}),';lf;
 		nextPutAll: '}),';lf;
 		nextPutAll: 'smalltalk.', (self classNameFor: aClass);
 		nextPutAll: 'smalltalk.', (self classNameFor: aClass);
 		nextPutAll: ');';lf;lf
 		nextPutAll: ');';lf;lf
-! !!
+! !
 
 
 Object subclass: #Importer
 Object subclass: #Importer
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!Importer methodsFor: 'fileIn'!!
+!Importer methodsFor: 'fileIn'!
 
 
 import: aStream
 import: aStream
     | chunk result parser lastEmpty |
     | chunk result parser lastEmpty |
@@ -341,13 +341,13 @@ import: aStream
             			ifTrue: [
             			ifTrue: [
                                   	lastEmpty := false.
                                   	lastEmpty := false.
                                   	result scanFrom: parser]]]
                                   	result scanFrom: parser]]]
-! !!
+! !
 
 
 Object subclass: #Node
 Object subclass: #Node
 	instanceVariableNames: 'nodes'
 	instanceVariableNames: 'nodes'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!Node methodsFor: 'accessing'!!
+!Node methodsFor: 'accessing'!
 
 
 addNode: aNode
 addNode: aNode
 	self nodes add: aNode
 	self nodes add: aNode
@@ -355,15 +355,15 @@ addNode: aNode
 
 
 nodes
 nodes
 	^nodes ifNil: [nodes := Array new]
 	^nodes ifNil: [nodes := Array new]
-! !!
+! !
 
 
-!!Node methodsFor: 'building'!!
+!Node methodsFor: 'building'!
 
 
 nodes: aCollection
 nodes: aCollection
 	nodes := aCollection
 	nodes := aCollection
-! !!
+! !
 
 
-!!Node methodsFor: 'testing'!!
+!Node methodsFor: 'testing'!
 
 
 isBlockNode
 isBlockNode
 	^false
 	^false
@@ -375,19 +375,19 @@ isBlockSequenceNode
 
 
 isValueNode
 isValueNode
 	^false
 	^false
-! !!
+! !
 
 
-!!Node methodsFor: 'visiting'!!
+!Node methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitNode: self
 	aVisitor visitNode: self
-! !!
+! !
 
 
 Node subclass: #AssignmentNode
 Node subclass: #AssignmentNode
 	instanceVariableNames: 'left right'
 	instanceVariableNames: 'left right'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!AssignmentNode methodsFor: 'accessing'!!
+!AssignmentNode methodsFor: 'accessing'!
 
 
 left
 left
 	^left
 	^left
@@ -404,19 +404,19 @@ right
 
 
 right: aNode
 right: aNode
 	right := aNode
 	right := aNode
-! !!
+! !
 
 
-!!AssignmentNode methodsFor: 'visiting'!!
+!AssignmentNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitAssignmentNode: self
 	aVisitor visitAssignmentNode: self
-! !!
+! !
 
 
 Node subclass: #BlockNode
 Node subclass: #BlockNode
 	instanceVariableNames: 'parameters inlined'
 	instanceVariableNames: 'parameters inlined'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!BlockNode methodsFor: 'accessing'!!
+!BlockNode methodsFor: 'accessing'!
 
 
 inlined
 inlined
 	^inlined ifNil: [false]
 	^inlined ifNil: [false]
@@ -432,25 +432,25 @@ parameters
 
 
 parameters: aCollection
 parameters: aCollection
 	parameters := aCollection
 	parameters := aCollection
-! !!
+! !
 
 
-!!BlockNode methodsFor: 'testing'!!
+!BlockNode methodsFor: 'testing'!
 
 
 isBlockNode
 isBlockNode
 	^true
 	^true
-! !!
+! !
 
 
-!!BlockNode methodsFor: 'visiting'!!
+!BlockNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitBlockNode: self
 	aVisitor visitBlockNode: self
-! !!
+! !
 
 
 Node subclass: #CascadeNode
 Node subclass: #CascadeNode
 	instanceVariableNames: 'receiver'
 	instanceVariableNames: 'receiver'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!CascadeNode methodsFor: 'accessing'!!
+!CascadeNode methodsFor: 'accessing'!
 
 
 receiver
 receiver
 	^receiver
 	^receiver
@@ -458,39 +458,39 @@ receiver
 
 
 receiver: aNode
 receiver: aNode
 	receiver := aNode
 	receiver := aNode
-! !!
+! !
 
 
-!!CascadeNode methodsFor: 'visiting'!!
+!CascadeNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitCascadeNode: self
 	aVisitor visitCascadeNode: self
-! !!
+! !
 
 
 Node subclass: #DynamicArrayNode
 Node subclass: #DynamicArrayNode
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!DynamicArrayNode methodsFor: 'visiting'!!
+!DynamicArrayNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitDynamicArrayNode: self
 	aVisitor visitDynamicArrayNode: self
-! !!
+! !
 
 
 Node subclass: #DynamicDictionaryNode
 Node subclass: #DynamicDictionaryNode
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!DynamicDictionaryNode methodsFor: 'visiting'!!
+!DynamicDictionaryNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitDynamicDictionaryNode: self
 	aVisitor visitDynamicDictionaryNode: self
-! !!
+! !
 
 
 Node subclass: #JSStatementNode
 Node subclass: #JSStatementNode
 	instanceVariableNames: 'source'
 	instanceVariableNames: 'source'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!JSStatementNode methodsFor: 'accessing'!!
+!JSStatementNode methodsFor: 'accessing'!
 
 
 source
 source
 	^source ifNil: ['']
 	^source ifNil: ['']
@@ -498,19 +498,19 @@ source
 
 
 source: aString
 source: aString
 	source := aString
 	source := aString
-! !!
+! !
 
 
-!!JSStatementNode methodsFor: 'visiting'!!
+!JSStatementNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitJSStatementNode: self
 	aVisitor visitJSStatementNode: self
-! !!
+! !
 
 
 Node subclass: #MethodNode
 Node subclass: #MethodNode
 	instanceVariableNames: 'selector arguments source'
 	instanceVariableNames: 'selector arguments source'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!MethodNode methodsFor: 'accessing'!!
+!MethodNode methodsFor: 'accessing'!
 
 
 arguments
 arguments
 	^arguments ifNil: [#()]
 	^arguments ifNil: [#()]
@@ -534,29 +534,29 @@ source
 
 
 source: aString
 source: aString
 	source := aString
 	source := aString
-! !!
+! !
 
 
-!!MethodNode methodsFor: 'visiting'!!
+!MethodNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitMethodNode: self
 	aVisitor visitMethodNode: self
-! !!
+! !
 
 
 Node subclass: #ReturnNode
 Node subclass: #ReturnNode
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!ReturnNode methodsFor: 'visiting'!!
+!ReturnNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitReturnNode: self
 	aVisitor visitReturnNode: self
-! !!
+! !
 
 
 Node subclass: #SendNode
 Node subclass: #SendNode
 	instanceVariableNames: 'selector arguments receiver'
 	instanceVariableNames: 'selector arguments receiver'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!SendNode methodsFor: 'accessing'!!
+!SendNode methodsFor: 'accessing'!
 
 
 arguments
 arguments
 	^arguments ifNil: [arguments := #()]
 	^arguments ifNil: [arguments := #()]
@@ -602,19 +602,19 @@ valueForReceiver: anObject
 	    selector: self selector;
 	    selector: self selector;
 	    arguments: self arguments;
 	    arguments: self arguments;
 	    yourself
 	    yourself
-! !!
+! !
 
 
-!!SendNode methodsFor: 'visiting'!!
+!SendNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitSendNode: self
 	aVisitor visitSendNode: self
-! !!
+! !
 
 
 Node subclass: #SequenceNode
 Node subclass: #SequenceNode
 	instanceVariableNames: 'temps'
 	instanceVariableNames: 'temps'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!SequenceNode methodsFor: 'accessing'!!
+!SequenceNode methodsFor: 'accessing'!
 
 
 temps
 temps
 	^temps ifNil: [#()]
 	^temps ifNil: [#()]
@@ -622,44 +622,44 @@ temps
 
 
 temps: aCollection
 temps: aCollection
 	temps := aCollection
 	temps := aCollection
-! !!
+! !
 
 
-!!SequenceNode methodsFor: 'testing'!!
+!SequenceNode methodsFor: 'testing'!
 
 
 asBlockSequenceNode
 asBlockSequenceNode
 	^BlockSequenceNode new
 	^BlockSequenceNode new
 	    nodes: self nodes;
 	    nodes: self nodes;
 	    temps: self temps;
 	    temps: self temps;
 	    yourself
 	    yourself
-! !!
+! !
 
 
-!!SequenceNode methodsFor: 'visiting'!!
+!SequenceNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitSequenceNode: self
 	aVisitor visitSequenceNode: self
-! !!
+! !
 
 
 SequenceNode subclass: #BlockSequenceNode
 SequenceNode subclass: #BlockSequenceNode
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!BlockSequenceNode methodsFor: 'testing'!!
+!BlockSequenceNode methodsFor: 'testing'!
 
 
 isBlockSequenceNode
 isBlockSequenceNode
 	^true
 	^true
-! !!
+! !
 
 
-!!BlockSequenceNode methodsFor: 'visiting'!!
+!BlockSequenceNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitBlockSequenceNode: self
 	aVisitor visitBlockSequenceNode: self
-! !!
+! !
 
 
 Node subclass: #ValueNode
 Node subclass: #ValueNode
 	instanceVariableNames: 'value'
 	instanceVariableNames: 'value'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!ValueNode methodsFor: 'accessing'!!
+!ValueNode methodsFor: 'accessing'!
 
 
 value
 value
 	^value
 	^value
@@ -667,25 +667,25 @@ value
 
 
 value: anObject
 value: anObject
 	value := anObject
 	value := anObject
-! !!
+! !
 
 
-!!ValueNode methodsFor: 'testing'!!
+!ValueNode methodsFor: 'testing'!
 
 
 isValueNode
 isValueNode
 	^true
 	^true
-! !!
+! !
 
 
-!!ValueNode methodsFor: 'visiting'!!
+!ValueNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitValueNode: self
 	aVisitor visitValueNode: self
-! !!
+! !
 
 
 ValueNode subclass: #VariableNode
 ValueNode subclass: #VariableNode
 	instanceVariableNames: 'assigned'
 	instanceVariableNames: 'assigned'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!VariableNode methodsFor: 'accessing'!!
+!VariableNode methodsFor: 'accessing'!
 
 
 assigned
 assigned
 	^assigned ifNil: [false]
 	^assigned ifNil: [false]
@@ -693,29 +693,29 @@ assigned
 
 
 assigned: aBoolean
 assigned: aBoolean
 	assigned := aBoolean
 	assigned := aBoolean
-! !!
+! !
 
 
-!!VariableNode methodsFor: 'visiting'!!
+!VariableNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitVariableNode: self
 	aVisitor visitVariableNode: self
-! !!
+! !
 
 
 VariableNode subclass: #ClassReferenceNode
 VariableNode subclass: #ClassReferenceNode
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!ClassReferenceNode methodsFor: 'visiting'!!
+!ClassReferenceNode methodsFor: 'visiting'!
 
 
 accept: aVisitor
 accept: aVisitor
 	aVisitor visitClassReferenceNode: self
 	aVisitor visitClassReferenceNode: self
-! !!
+! !
 
 
 Object subclass: #NodeVisitor
 Object subclass: #NodeVisitor
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!NodeVisitor methodsFor: 'visiting'!!
+!NodeVisitor methodsFor: 'visiting'!
 
 
 visit: aNode
 visit: aNode
 	aNode accept: self
 	aNode accept: self
@@ -782,13 +782,13 @@ visitValueNode: aNode
 !
 !
 
 
 visitVariableNode: aNode
 visitVariableNode: aNode
-! !!
+! !
 
 
 NodeVisitor subclass: #Compiler
 NodeVisitor subclass: #Compiler
 	instanceVariableNames: 'stream nestedBlocks earlyReturn currentClass currentSelector unknownVariables tempVariables messageSends referencedClasses classReferenced source argVariables'
 	instanceVariableNames: 'stream nestedBlocks earlyReturn currentClass currentSelector unknownVariables tempVariables messageSends referencedClasses classReferenced source argVariables'
 	category: 'Compiler'!
 	category: 'Compiler'!
 
 
-!!Compiler methodsFor: 'accessing'!!
+!Compiler methodsFor: 'accessing'!
 
 
 argVariables
 argVariables
 	^argVariables copy
 	^argVariables copy
@@ -846,9 +846,9 @@ tempVariables
 
 
 unknownVariables
 unknownVariables
 	^unknownVariables copy
 	^unknownVariables copy
-! !!
+! !
 
 
-!!Compiler methodsFor: 'compiling'!!
+!Compiler methodsFor: 'compiling'!
 
 
 compile: aString
 compile: aString
 	^self compileNode: (self parse: aString)
 	^self compileNode: (self parse: aString)
@@ -915,9 +915,9 @@ recompileAll
 
 
 setupClass: aClass
 setupClass: aClass
 	<smalltalk.init(aClass)>
 	<smalltalk.init(aClass)>
-! !!
+! !
 
 
-!!Compiler methodsFor: 'initialization'!!
+!Compiler methodsFor: 'initialization'!
 
 
 initialize
 initialize
 	super initialize.
 	super initialize.
@@ -927,9 +927,9 @@ initialize
 	argVariables := #().
 	argVariables := #().
 	messageSends := #().
 	messageSends := #().
 	classReferenced := #()
 	classReferenced := #()
-! !!
+! !
 
 
-!!Compiler methodsFor: 'optimizations'!!
+!Compiler methodsFor: 'optimizations'!
 
 
 checkClass: aClassName for: receiver
 checkClass: aClassName for: receiver
         stream nextPutAll: '((($receiver = ', receiver, ').klass === smalltalk.', aClassName, ') ? '
         stream nextPutAll: '((($receiver = ', receiver, ').klass === smalltalk.', aClassName, ') ? '
@@ -1175,15 +1175,15 @@ isNode: aNode ofClass: aClass
 	^aNode isValueNode and: [
 	^aNode isValueNode and: [
           	aNode value class = aClass or: [
           	aNode value class = aClass or: [
           		aNode value = 'self' and: [self currentClass = aClass]]]
           		aNode value = 'self' and: [self currentClass = aClass]]]
-! !!
+! !
 
 
-!!Compiler methodsFor: 'testing'!!
+!Compiler methodsFor: 'testing'!
 
 
 performOptimizations
 performOptimizations
 	^self class performOptimizations
 	^self class performOptimizations
-! !!
+! !
 
 
-!!Compiler methodsFor: 'visiting'!!
+!Compiler methodsFor: 'visiting'!
 
 
 send: aSelector to: aReceiver arguments: aCollection superSend: aBoolean
 send: aSelector to: aReceiver arguments: aCollection superSend: aBoolean
 	^String streamContents: [:str || tmp |
 	^String streamContents: [:str || tmp |
@@ -1412,11 +1412,11 @@ visitVariableNode: aNode
                                   	aNode value = 'thisContext'
                                   	aNode value = 'thisContext'
                                   		ifTrue: [stream nextPutAll: '(smalltalk.getThisContext())']
                                   		ifTrue: [stream nextPutAll: '(smalltalk.getThisContext())']
                 				ifFalse: [stream nextPutAll: varName]]]
                 				ifFalse: [stream nextPutAll: varName]]]
-! !!
+! !
 
 
 Compiler class instanceVariableNames: 'performOptimizations'!
 Compiler class instanceVariableNames: 'performOptimizations'!
 
 
-!!Compiler class methodsFor: 'accessing'!!
+!Compiler class methodsFor: 'accessing'!
 
 
 performOptimizations
 performOptimizations
 	^performOptimizations ifNil: [true]
 	^performOptimizations ifNil: [true]
@@ -1424,9 +1424,9 @@ performOptimizations
 
 
 performOptimizations: aBoolean
 performOptimizations: aBoolean
 	performOptimizations := aBoolean
 	performOptimizations := aBoolean
-! !!
+! !
 
 
-!!Compiler class methodsFor: 'compiling'!!
+!Compiler class methodsFor: 'compiling'!
 
 
 recompile: aClass
 recompile: aClass
 	aClass methodDictionary do: [:each || method |
 	aClass methodDictionary do: [:each || method |
@@ -1439,5 +1439,5 @@ recompile: aClass
 recompileAll
 recompileAll
 	Smalltalk current classes do: [:each |
 	Smalltalk current classes do: [:each |
 		self recompile: each]
 		self recompile: each]
-! !!
+! !
 
 

+ 160 - 160
st/IDE.st

@@ -3,7 +3,7 @@ Widget subclass: #ClassesList
 	instanceVariableNames: 'browser ul nodes'
 	instanceVariableNames: 'browser ul nodes'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!ClassesList methodsFor: 'accessing'!!
+!ClassesList methodsFor: 'accessing'!
 
 
 browser
 browser
 	^browser
 	^browser
@@ -37,9 +37,9 @@ nodes
 
 
 resetNodes
 resetNodes
 	nodes := nil
 	nodes := nil
-! !!
+! !
 
 
-!!ClassesList methodsFor: 'rendering'!!
+!ClassesList methodsFor: 'rendering'!
 
 
 renderOn: html
 renderOn: html
 	ul := html ul
 	ul := html ul
@@ -52,21 +52,21 @@ updateNodes
 	ul contents: [:html |
 	ul contents: [:html |
 		self nodes do: [:each |
 		self nodes do: [:each |
 			each renderOn: html]]
 			each renderOn: html]]
-! !!
+! !
 
 
-!!ClassesList class methodsFor: 'instance creation'!!
+!ClassesList class methodsFor: 'instance creation'!
 
 
 on: aBrowser
 on: aBrowser
 	^self new 
 	^self new 
 		browser: aBrowser; 
 		browser: aBrowser; 
 		yourself
 		yourself
-! !!
+! !
 
 
 Widget subclass: #ClassesListNode
 Widget subclass: #ClassesListNode
 	instanceVariableNames: 'browser theClass level nodes'
 	instanceVariableNames: 'browser theClass level nodes'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!ClassesListNode methodsFor: ''!!
+!ClassesListNode methodsFor: ''!
 
 
 renderOn: html
 renderOn: html
 	| li cssClass |
 	| li cssClass |
@@ -85,9 +85,9 @@ renderOn: html
 
 
 	self nodes do: [:each |
 	self nodes do: [:each |
 		each renderOn: html]
 		each renderOn: html]
-! !!
+! !
 
 
-!!ClassesListNode methodsFor: 'accessing'!!
+!ClassesListNode methodsFor: 'accessing'!
 
 
 browser
 browser
 	^browser
 	^browser
@@ -136,9 +136,9 @@ theClass
 
 
 theClass: aClass
 theClass: aClass
 	theClass := aClass
 	theClass := aClass
-! !!
+! !
 
 
-!!ClassesListNode methodsFor: 'visiting'!!
+!ClassesListNode methodsFor: 'visiting'!
 
 
 traverseClassesWith: aCollection
 traverseClassesWith: aCollection
     "sort classes alphabetically Issue #143"
     "sort classes alphabetically Issue #143"
@@ -146,9 +146,9 @@ traverseClassesWith: aCollection
     aCollection add: self theClass.
     aCollection add: self theClass.
     (self nodes sorted: [:a :b | a theClass name <= b theClass name ]) do: [:aNode |
     (self nodes sorted: [:a :b | a theClass name <= b theClass name ]) do: [:aNode |
         aNode traverseClassesWith: aCollection ].
         aNode traverseClassesWith: aCollection ].
-! !!
+! !
 
 
-!!ClassesListNode class methodsFor: 'instance creation'!!
+!ClassesListNode class methodsFor: 'instance creation'!
 
 
 on: aClass browser: aBrowser classes: aCollection level: anInteger
 on: aClass browser: aBrowser classes: aCollection level: anInteger
 	^self new
 	^self new
@@ -157,32 +157,32 @@ on: aClass browser: aBrowser classes: aCollection level: anInteger
 		level: anInteger;
 		level: anInteger;
 		getNodesFrom: aCollection;
 		getNodesFrom: aCollection;
 		yourself
 		yourself
-! !!
+! !
 
 
 ErrorHandler subclass: #DebugErrorHandler
 ErrorHandler subclass: #DebugErrorHandler
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!DebugErrorHandler methodsFor: 'error handling'!!
+!DebugErrorHandler methodsFor: 'error handling'!
 
 
 handleError: anError
 handleError: anError
 	[Debugger new
 	[Debugger new
 		error: anError;
 		error: anError;
 		open] on: Error do: [:error |
 		open] on: Error do: [:error |
 			ErrorHandler new handleError: error]
 			ErrorHandler new handleError: error]
-! !!
+! !
 
 
-!!DebugErrorHandler class methodsFor: 'initialization'!!
+!DebugErrorHandler class methodsFor: 'initialization'!
 
 
 initialize
 initialize
 	self register
 	self register
-! !!
+! !
 
 
 Widget subclass: #SourceArea
 Widget subclass: #SourceArea
 	instanceVariableNames: 'editor div receiver onDoIt'
 	instanceVariableNames: 'editor div receiver onDoIt'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!SourceArea methodsFor: 'accessing'!!
+!SourceArea methodsFor: 'accessing'!
 
 
 currentLine
 currentLine
     ^editor getLine: (editor getCursor line)
     ^editor getLine: (editor getCursor line)
@@ -250,9 +250,9 @@ val
 
 
 val: aString
 val: aString
     editor setValue: aString
     editor setValue: aString
-! !!
+! !
 
 
-!!SourceArea methodsFor: 'actions'!!
+!SourceArea methodsFor: 'actions'!
 
 
 clear
 clear
       self val: ''
       self val: ''
@@ -316,9 +316,9 @@ print: aString
 
 
 printIt
 printIt
     self print: self doIt printString
     self print: self doIt printString
-! !!
+! !
 
 
-!!SourceArea methodsFor: 'events'!!
+!SourceArea methodsFor: 'events'!
 
 
 onKeyDown: aBlock
 onKeyDown: aBlock
 	div onKeyDown: aBlock
 	div onKeyDown: aBlock
@@ -326,9 +326,9 @@ onKeyDown: aBlock
 
 
 onKeyUp: aBlock
 onKeyUp: aBlock
 	div onKeyUp: aBlock
 	div onKeyUp: aBlock
-! !!
+! !
 
 
-!!SourceArea methodsFor: 'rendering'!!
+!SourceArea methodsFor: 'rendering'!
 
 
 renderOn: html
 renderOn: html
     | textarea |
     | textarea |
@@ -336,13 +336,13 @@ renderOn: html
     div with: [textarea := html textarea].
     div with: [textarea := html textarea].
     self setEditorOn: textarea element.
     self setEditorOn: textarea element.
     div onKeyDown: [:e | self handleKeyDown: e]
     div onKeyDown: [:e | self handleKeyDown: e]
-! !!
+! !
 
 
 Widget subclass: #TabManager
 Widget subclass: #TabManager
 	instanceVariableNames: 'selectedTab tabs opened ul input'
 	instanceVariableNames: 'selectedTab tabs opened ul input'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!TabManager methodsFor: 'accessing'!!
+!TabManager methodsFor: 'accessing'!
 
 
 labelFor: aWidget
 labelFor: aWidget
 	| label maxSize |
 	| label maxSize |
@@ -355,9 +355,9 @@ labelFor: aWidget
 
 
 tabs
 tabs
     ^tabs ifNil: [tabs := Array new]
     ^tabs ifNil: [tabs := Array new]
-! !!
+! !
 
 
-!!TabManager methodsFor: 'actions'!!
+!TabManager methodsFor: 'actions'!
 
 
 close
 close
     opened ifTrue: [
     opened ifTrue: [
@@ -434,9 +434,9 @@ updateBodyMargin
 
 
 updatePosition
 updatePosition
     <jQuery('#jtalk').css('top', '').css('bottom', '0px')>
     <jQuery('#jtalk').css('top', '').css('bottom', '0px')>
-! !!
+! !
 
 
-!!TabManager methodsFor: 'adding/Removing'!!
+!TabManager methodsFor: 'adding/Removing'!
 
 
 addTab: aWidget
 addTab: aWidget
     self tabs add: aWidget.
     self tabs add: aWidget.
@@ -447,9 +447,9 @@ addTab: aWidget
 removeTab: aWidget
 removeTab: aWidget
     self tabs remove: aWidget.
     self tabs remove: aWidget.
     self update
     self update
-! !!
+! !
 
 
-!!TabManager methodsFor: 'initialization'!!
+!TabManager methodsFor: 'initialization'!
 
 
 initialize
 initialize
     super initialize.
     super initialize.
@@ -466,9 +466,9 @@ initialize
     self 
     self 
 	onResize: [self updateBodyMargin; updatePosition];
 	onResize: [self updateBodyMargin; updatePosition];
 	onWindowResize: [self updatePosition]
 	onWindowResize: [self updatePosition]
-! !!
+! !
 
 
-!!TabManager methodsFor: 'rendering'!!
+!TabManager methodsFor: 'rendering'!
 
 
 renderOn: html
 renderOn: html
 	html div id: 'logo'.
 	html div id: 'logo'.
@@ -523,17 +523,17 @@ renderToolbarOn: html
 				event keyCode = 13 ifTrue: [
 				event keyCode = 13 ifTrue: [
 				self search: input asJQuery val]].
 				self search: input asJQuery val]].
 			html div id: 'jt_close'; onClick: [self close]]
 			html div id: 'jt_close'; onClick: [self close]]
-! !!
+! !
 
 
-!!TabManager methodsFor: 'updating'!!
+!TabManager methodsFor: 'updating'!
 
 
 update
 update
 	self renderTabs
 	self renderTabs
-! !!
+! !
 
 
 TabManager class instanceVariableNames: 'current'!
 TabManager class instanceVariableNames: 'current'!
 
 
-!!TabManager class methodsFor: 'instance creation'!!
+!TabManager class methodsFor: 'instance creation'!
 
 
 current
 current
     ^current ifNil: [current := super new]
     ^current ifNil: [current := super new]
@@ -541,19 +541,19 @@ current
 
 
 new
 new
     self shouldNotImplement
     self shouldNotImplement
-! !!
+! !
 
 
 Widget subclass: #TabWidget
 Widget subclass: #TabWidget
 	instanceVariableNames: 'div'
 	instanceVariableNames: 'div'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!TabWidget methodsFor: 'accessing'!!
+!TabWidget methodsFor: 'accessing'!
 
 
 label
 label
     self subclassResponsibility
     self subclassResponsibility
-! !!
+! !
 
 
-!!TabWidget methodsFor: 'actions'!!
+!TabWidget methodsFor: 'actions'!
 
 
 close
 close
     TabManager current closeTab: self
     TabManager current closeTab: self
@@ -574,9 +574,9 @@ remove
 
 
 show
 show
 	div asJQuery show
 	div asJQuery show
-! !!
+! !
 
 
-!!TabWidget methodsFor: 'rendering'!!
+!TabWidget methodsFor: 'rendering'!
 
 
 renderBoxOn: html
 renderBoxOn: html
 !
 !
@@ -603,25 +603,25 @@ renderTab
 
 
 update
 update
 	self renderTab
 	self renderTab
-! !!
+! !
 
 
-!!TabWidget methodsFor: 'testing'!!
+!TabWidget methodsFor: 'testing'!
 
 
 canBeClosed
 canBeClosed
     ^false
     ^false
-! !!
+! !
 
 
-!!TabWidget class methodsFor: 'instance creation'!!
+!TabWidget class methodsFor: 'instance creation'!
 
 
 open
 open
     ^self new open
     ^self new open
-! !!
+! !
 
 
 TabWidget subclass: #Browser
 TabWidget subclass: #Browser
 	instanceVariableNames: 'selectedPackage selectedClass selectedProtocol selectedMethod packagesList classesList protocolsList methodsList sourceArea tabsList selectedTab saveButton classButtons methodButtons unsavedChanges'
 	instanceVariableNames: 'selectedPackage selectedClass selectedProtocol selectedMethod packagesList classesList protocolsList methodsList sourceArea tabsList selectedTab saveButton classButtons methodButtons unsavedChanges'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!Browser methodsFor: 'accessing'!!
+!Browser methodsFor: 'accessing'!
 
 
 classCommentSource
 classCommentSource
     ^selectedClass comment
     ^selectedClass comment
@@ -756,9 +756,9 @@ source
     ^selectedClass
     ^selectedClass
 	ifNil: ['']
 	ifNil: ['']
 	ifNotNil: [self classCommentSource]
 	ifNotNil: [self classCommentSource]
-! !!
+! !
 
 
-!!Browser methodsFor: 'actions'!!
+!Browser methodsFor: 'actions'!
 
 
 addInstanceVariableNamed: aString toClass: aClass
 addInstanceVariableNamed: aString toClass: aClass
 	ClassBuilder new
 	ClassBuilder new
@@ -1030,18 +1030,18 @@ showClassButtons
 
 
 showMethodButtons
 showMethodButtons
     methodButtons asJQuery show
     methodButtons asJQuery show
-! !!
+! !
 
 
-!!Browser methodsFor: 'initialization'!!
+!Browser methodsFor: 'initialization'!
 
 
 initialize
 initialize
     super initialize.
     super initialize.
     selectedTab := #instance.
     selectedTab := #instance.
     selectedPackage := self packages first.
     selectedPackage := self packages first.
     unsavedChanges := false
     unsavedChanges := false
-! !!
+! !
 
 
-!!Browser methodsFor: 'network'!!
+!Browser methodsFor: 'network'!
 
 
 ajaxPutAt: anURL data: aString
 ajaxPutAt: anURL data: aString
 	jQuery 
 	jQuery 
@@ -1049,9 +1049,9 @@ ajaxPutAt: anURL data: aString
 								'data' -> aString.
 								'data' -> aString.
 								'contentType' -> 'text/plain;charset=UTF-8'.
 								'contentType' -> 'text/plain;charset=UTF-8'.
 								'error' -> [window alert: 'PUT request failed at:  ', anURL] }
 								'error' -> [window alert: 'PUT request failed at:  ', anURL] }
-! !!
+! !
 
 
-!!Browser methodsFor: 'rendering'!!
+!Browser methodsFor: 'rendering'!
 
 
 renderBottomPanelOn: html
 renderBottomPanelOn: html
     html div
     html div
@@ -1125,15 +1125,15 @@ renderTopPanelOn: html
 				updateProtocolsList;
 				updateProtocolsList;
 				updateMethodsList.
 				updateMethodsList.
 			html div class: 'jt_clear']
 			html div class: 'jt_clear']
-! !!
+! !
 
 
-!!Browser methodsFor: 'testing'!!
+!Browser methodsFor: 'testing'!
 
 
 canBeClosed
 canBeClosed
 	^true
 	^true
-! !!
+! !
 
 
-!!Browser methodsFor: 'updating'!!
+!Browser methodsFor: 'updating'!
 
 
 resetClassesList
 resetClassesList
 	classesList resetNodes
 	classesList resetNodes
@@ -1279,9 +1279,9 @@ updateTabsList
 		html span class: 'mtab'; with: 'Comment'.
 		html span class: 'mtab'; with: 'Comment'.
 		html span class: 'rtab'];
 		html span class: 'rtab'];
 	    onClick: [self selectTab: #comment]]
 	    onClick: [self selectTab: #comment]]
-! !!
+! !
 
 
-!!Browser class methodsFor: 'accessing'!!
+!Browser class methodsFor: 'accessing'!
 
 
 commitPathJs
 commitPathJs
 	^'js'
 	^'js'
@@ -1289,9 +1289,9 @@ commitPathJs
 
 
 commitPathSt
 commitPathSt
 	^'st'
 	^'st'
-! !!
+! !
 
 
-!!Browser class methodsFor: 'convenience'!!
+!Browser class methodsFor: 'convenience'!
 
 
 open
 open
     self new open
     self new open
@@ -1302,13 +1302,13 @@ openOn: aClass
 	open;
 	open;
 	selectCategory: aClass category;
 	selectCategory: aClass category;
 	selectClass: aClass
 	selectClass: aClass
-! !!
+! !
 
 
 TabWidget subclass: #Debugger
 TabWidget subclass: #Debugger
 	instanceVariableNames: 'error selectedContext sourceArea ul ul2 inspector saveButton unsavedChanges selectedVariable selectedVariableName inspectButton'
 	instanceVariableNames: 'error selectedContext sourceArea ul ul2 inspector saveButton unsavedChanges selectedVariable selectedVariableName inspectButton'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!Debugger methodsFor: 'accessing'!!
+!Debugger methodsFor: 'accessing'!
 
 
 arguments
 arguments
 	^self method 
 	^self method 
@@ -1340,9 +1340,9 @@ source
 	^self method 
 	^self method 
 		ifNil: ['Method doesn''t exist!!']
 		ifNil: ['Method doesn''t exist!!']
 		ifNotNil: [self method source]
 		ifNotNil: [self method source]
-! !!
+! !
 
 
-!!Debugger methodsFor: 'actions'!!
+!Debugger methodsFor: 'actions'!
 
 
 inspectSelectedVariable
 inspectSelectedVariable
 	selectedVariable inspect
 	selectedVariable inspect
@@ -1377,16 +1377,16 @@ selectVariable: anObject named: aString
 	selectedVariableName := aString.
 	selectedVariableName := aString.
 	inspector contents: [:html | html with: anObject printString].
 	inspector contents: [:html | html with: anObject printString].
 	self updateVariablesList
 	self updateVariablesList
-! !!
+! !
 
 
-!!Debugger methodsFor: 'initialization'!!
+!Debugger methodsFor: 'initialization'!
 
 
 initialize
 initialize
 	super initialize.
 	super initialize.
 	unsavedChanges = false
 	unsavedChanges = false
-! !!
+! !
 
 
-!!Debugger methodsFor: 'rendering'!!
+!Debugger methodsFor: 'rendering'!
 
 
 renderBottomPanelOn: html
 renderBottomPanelOn: html
 	html div
 	html div
@@ -1458,15 +1458,15 @@ renderTopPanelOn: html
 			ul := html ul 
 			ul := html ul 
 				class: 'jt_column debugger contexts';
 				class: 'jt_column debugger contexts';
 				with: [self renderContext: self error context on: html]]
 				with: [self renderContext: self error context on: html]]
-! !!
+! !
 
 
-!!Debugger methodsFor: 'testing'!!
+!Debugger methodsFor: 'testing'!
 
 
 canBeClosed
 canBeClosed
     ^true
     ^true
-! !!
+! !
 
 
-!!Debugger methodsFor: 'updating'!!
+!Debugger methodsFor: 'updating'!
 
 
 updateContextsList
 updateContextsList
 	ul contents: [:html |
 	ul contents: [:html |
@@ -1515,19 +1515,19 @@ updateVariablesList
                          selectedVariableName = each ifTrue: [
                          selectedVariableName = each ifTrue: [
 				li class: 'selected']]].
 				li class: 'selected']]].
 	selectedVariable ifNil: [inspectButton at: 'disabled' put: true] ifNotNil: [inspectButton removeAt: 'disabled']
 	selectedVariable ifNil: [inspectButton at: 'disabled' put: true] ifNotNil: [inspectButton removeAt: 'disabled']
-! !!
+! !
 
 
 TabWidget subclass: #IDETranscript
 TabWidget subclass: #IDETranscript
 	instanceVariableNames: 'textarea'
 	instanceVariableNames: 'textarea'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!IDETranscript methodsFor: 'accessing'!!
+!IDETranscript methodsFor: 'accessing'!
 
 
 label
 label
     ^'Transcript'
     ^'Transcript'
-! !!
+! !
 
 
-!!IDETranscript methodsFor: 'actions'!!
+!IDETranscript methodsFor: 'actions'!
 
 
 clear
 clear
     textarea asJQuery val: ''
     textarea asJQuery val: ''
@@ -1546,9 +1546,9 @@ open
 show: anObject
 show: anObject
     textarea ifNil: [self open].
     textarea ifNil: [self open].
     textarea asJQuery val: textarea asJQuery val, anObject asString.
     textarea asJQuery val: textarea asJQuery val, anObject asString.
-! !!
+! !
 
 
-!!IDETranscript methodsFor: 'rendering'!!
+!IDETranscript methodsFor: 'rendering'!
 
 
 renderBoxOn: html
 renderBoxOn: html
     textarea := html textarea.
     textarea := html textarea.
@@ -1561,17 +1561,17 @@ renderButtonsOn: html
     html button
     html button
 	with: 'Clear transcript';
 	with: 'Clear transcript';
 	onClick: [self clear]
 	onClick: [self clear]
-! !!
+! !
 
 
 IDETranscript class instanceVariableNames: 'current'!
 IDETranscript class instanceVariableNames: 'current'!
 
 
-!!IDETranscript class methodsFor: 'initialization'!!
+!IDETranscript class methodsFor: 'initialization'!
 
 
 initialize
 initialize
 	Transcript register: self current
 	Transcript register: self current
-! !!
+! !
 
 
-!!IDETranscript class methodsFor: 'instance creation'!!
+!IDETranscript class methodsFor: 'instance creation'!
 
 
 current
 current
 	^current ifNil: [current := super new]
 	^current ifNil: [current := super new]
@@ -1585,13 +1585,13 @@ open
     TabManager current 
     TabManager current 
 	open;
 	open;
 	selectTab: self current
 	selectTab: self current
-! !!
+! !
 
 
 TabWidget subclass: #Inspector
 TabWidget subclass: #Inspector
 	instanceVariableNames: 'label variables object selectedVariable variablesList valueTextarea diveButton sourceArea'
 	instanceVariableNames: 'label variables object selectedVariable variablesList valueTextarea diveButton sourceArea'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!Inspector methodsFor: 'accessing'!!
+!Inspector methodsFor: 'accessing'!
 
 
 label
 label
 	^label ifNil: ['Inspector (nil)']
 	^label ifNil: ['Inspector (nil)']
@@ -1619,9 +1619,9 @@ sourceArea
 
 
 variables
 variables
 	^variables
 	^variables
-! !!
+! !
 
 
-!!Inspector methodsFor: 'actions'!!
+!Inspector methodsFor: 'actions'!
 
 
 dive
 dive
 	(self variables at: self selectedVariable) inspect
 	(self variables at: self selectedVariable) inspect
@@ -1638,9 +1638,9 @@ refresh
 		inspect: object; 
 		inspect: object; 
 		updateVariablesList;
 		updateVariablesList;
 		updateValueTextarea
 		updateValueTextarea
-! !!
+! !
 
 
-!!Inspector methodsFor: 'rendering'!!
+!Inspector methodsFor: 'rendering'!
 
 
 renderBottomPanelOn: html
 renderBottomPanelOn: html
     html div
     html div
@@ -1691,15 +1691,15 @@ renderTopPanelOn: html
 	self
 	self
 		updateVariablesList;
 		updateVariablesList;
 		updateValueTextarea.
 		updateValueTextarea.
-! !!
+! !
 
 
-!!Inspector methodsFor: 'testing'!!
+!Inspector methodsFor: 'testing'!
 
 
 canBeClosed
 canBeClosed
 	^true
 	^true
-! !!
+! !
 
 
-!!Inspector methodsFor: 'updating'!!
+!Inspector methodsFor: 'updating'!
 
 
 selectVariable: aString
 selectVariable: aString
 	self selectedVariable: aString.
 	self selectedVariable: aString.
@@ -1730,21 +1730,21 @@ updateVariablesList
 				onClick: [self selectVariable: each].
 				onClick: [self selectVariable: each].
 			self selectedVariable = each ifTrue: [
 			self selectedVariable = each ifTrue: [
 				li class: 'selected']]]
 				li class: 'selected']]]
-! !!
+! !
 
 
-!!Inspector class methodsFor: 'instance creation'!!
+!Inspector class methodsFor: 'instance creation'!
 
 
 on: anObject
 on: anObject
 	^self new
 	^self new
 		inspect: anObject;
 		inspect: anObject;
 		yourself
 		yourself
-! !!
+! !
 
 
 TabWidget subclass: #ProgressBar
 TabWidget subclass: #ProgressBar
 	instanceVariableNames: 'percent progressDiv div'
 	instanceVariableNames: 'percent progressDiv div'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!ProgressBar methodsFor: 'accessing'!!
+!ProgressBar methodsFor: 'accessing'!
 
 
 percent
 percent
 	^percent ifNil: [0]
 	^percent ifNil: [0]
@@ -1752,9 +1752,9 @@ percent
 
 
 percent: aNumber
 percent: aNumber
 	percent := aNumber
 	percent := aNumber
-! !!
+! !
 
 
-!!ProgressBar methodsFor: 'rendering'!!
+!ProgressBar methodsFor: 'rendering'!
 
 
 renderOn: html 
 renderOn: html 
 	div := html div 
 	div := html div 
@@ -1768,20 +1768,20 @@ renderProgressBar
 		html div 
 		html div 
 			class: 'progress';
 			class: 'progress';
 			style: 'width:', self percent asString, '%']
 			style: 'width:', self percent asString, '%']
-! !!
+! !
 
 
-!!ProgressBar methodsFor: 'updating'!!
+!ProgressBar methodsFor: 'updating'!
 
 
 updatePercent: aNumber
 updatePercent: aNumber
 	self percent: aNumber.
 	self percent: aNumber.
 	self renderProgressBar
 	self renderProgressBar
-! !!
+! !
 
 
 TabWidget subclass: #ReferencesBrowser
 TabWidget subclass: #ReferencesBrowser
 	instanceVariableNames: 'implementors senders implementorsList input timer selector sendersList referencedClasses referencedClassesList'
 	instanceVariableNames: 'implementors senders implementorsList input timer selector sendersList referencedClasses referencedClassesList'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!ReferencesBrowser methodsFor: 'accessing'!!
+!ReferencesBrowser methodsFor: 'accessing'!
 
 
 classesAndMetaclasses
 classesAndMetaclasses
 	^Smalltalk current classes, (Smalltalk current classes collect: [:each | each class])
 	^Smalltalk current classes, (Smalltalk current classes collect: [:each | each class])
@@ -1805,9 +1805,9 @@ selector
 
 
 senders
 senders
 	^senders ifNil: [senders := Array new]
 	^senders ifNil: [senders := Array new]
-! !!
+! !
 
 
-!!ReferencesBrowser methodsFor: 'actions'!!
+!ReferencesBrowser methodsFor: 'actions'!
 
 
 openBrowserOn: aMethod
 openBrowserOn: aMethod
        | browser |
        | browser |
@@ -1850,24 +1850,24 @@ searchSelectorReferencesFor: aString
 			key = selector ifTrue: [self implementors add: value].
 			key = selector ifTrue: [self implementors add: value].
 			(value messageSends includes: selector) ifTrue: [
 			(value messageSends includes: selector) ifTrue: [
 				self senders add: value]]]
 				self senders add: value]]]
-! !!
+! !
 
 
-!!ReferencesBrowser methodsFor: 'initialization'!!
+!ReferencesBrowser methodsFor: 'initialization'!
 
 
 initialize
 initialize
 	super initialize.
 	super initialize.
 	selector := ''
 	selector := ''
-! !!
+! !
 
 
-!!ReferencesBrowser methodsFor: 'private'!!
+!ReferencesBrowser methodsFor: 'private'!
 
 
 setInputEvents
 setInputEvents
 	input
 	input
 		onKeyUp: [timer := [self search: input asJQuery val] valueWithTimeout: 100];
 		onKeyUp: [timer := [self search: input asJQuery val] valueWithTimeout: 100];
 		onKeyDown: [timer ifNotNil: [timer clearTimeout]]
 		onKeyDown: [timer ifNotNil: [timer clearTimeout]]
-! !!
+! !
 
 
-!!ReferencesBrowser methodsFor: 'rendering'!!
+!ReferencesBrowser methodsFor: 'rendering'!
 
 
 renderBoxOn: html
 renderBoxOn: html
 	self 
 	self 
@@ -1898,15 +1898,15 @@ renderReferencedClassesOn: html
 renderSendersOn: html
 renderSendersOn: html
 	sendersList := html ul class: 'jt_column senders'.
 	sendersList := html ul class: 'jt_column senders'.
 	self updateSendersList
 	self updateSendersList
-! !!
+! !
 
 
-!!ReferencesBrowser methodsFor: 'testing'!!
+!ReferencesBrowser methodsFor: 'testing'!
 
 
 canBeClosed
 canBeClosed
 	^true
 	^true
-! !!
+! !
 
 
-!!ReferencesBrowser methodsFor: 'updating'!!
+!ReferencesBrowser methodsFor: 'updating'!
 
 
 updateImplementorsList
 updateImplementorsList
     implementorsList contents: [:html |
     implementorsList contents: [:html |
@@ -1943,21 +1943,21 @@ updateSendersList
 		html li
 		html li
 			with: (each methodClass asString, ' >> ', each selector);
 			with: (each methodClass asString, ' >> ', each selector);
 			onClick: [self openBrowserOn: each]]]
 			onClick: [self openBrowserOn: each]]]
-! !!
+! !
 
 
-!!ReferencesBrowser class methodsFor: 'instance creation'!!
+!ReferencesBrowser class methodsFor: 'instance creation'!
 
 
 search: aString
 search: aString
 	^self new
 	^self new
 		searchReferencesFor: aString;
 		searchReferencesFor: aString;
 		open
 		open
-! !!
+! !
 
 
 TabWidget subclass: #TestRunner
 TabWidget subclass: #TestRunner
 	instanceVariableNames: 'selectedCategories packagesList selectedClasses classesList selectedMethods progressBar methodsList result statusDiv'
 	instanceVariableNames: 'selectedCategories packagesList selectedClasses classesList selectedMethods progressBar methodsList result statusDiv'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!TestRunner methodsFor: 'accessing'!!
+!TestRunner methodsFor: 'accessing'!
 
 
 allClasses
 allClasses
 	^TestCase allSubclasses
 	^TestCase allSubclasses
@@ -2007,9 +2007,9 @@ testCases
 	testCases := #().
 	testCases := #().
 	self selectedClasses do: [:each | testCases addAll: each buildSuite].
 	self selectedClasses do: [:each | testCases addAll: each buildSuite].
 	^testCases
 	^testCases
-! !!
+! !
 
 
-!!TestRunner methodsFor: 'actions'!!
+!TestRunner methodsFor: 'actions'!
 
 
 performFailure: aTestCase
 performFailure: aTestCase
 	aTestCase perform: aTestCase selector
 	aTestCase perform: aTestCase selector
@@ -2062,16 +2062,16 @@ toggleClass: aClass
 		ifTrue: [selectedClasses remove: aClass].
 		ifTrue: [selectedClasses remove: aClass].
 	self 
 	self 
 	    updateClassesList
 	    updateClassesList
-! !!
+! !
 
 
-!!TestRunner methodsFor: 'initialization'!!
+!TestRunner methodsFor: 'initialization'!
 
 
 initialize
 initialize
 	super initialize.
 	super initialize.
 	result := TestResult new
 	result := TestResult new
-! !!
+! !
 
 
-!!TestRunner methodsFor: 'printing'!!
+!TestRunner methodsFor: 'printing'!
 
 
 printErrors
 printErrors
 	^self result errors size asString , ' errors, '
 	^self result errors size asString , ' errors, '
@@ -2087,9 +2087,9 @@ printPasses
 
 
 printTotal
 printTotal
 	^self result total asString, ' runs, '
 	^self result total asString, ' runs, '
-! !!
+! !
 
 
-!!TestRunner methodsFor: 'rendering'!!
+!TestRunner methodsFor: 'rendering'!
 
 
 renderBoxOn: html
 renderBoxOn: html
     self 
     self 
@@ -2136,9 +2136,9 @@ renderResultsOn: html
 	methodsList := html ul class: 'jt_column sunit results'.
 	methodsList := html ul class: 'jt_column sunit results'.
 	self updateMethodsList.
 	self updateMethodsList.
 	self updateStatusDiv
 	self updateStatusDiv
-! !!
+! !
 
 
-!!TestRunner methodsFor: 'testing'!!
+!TestRunner methodsFor: 'testing'!
 
 
 isSelectedCategory: aCategory
 isSelectedCategory: aCategory
 	^(self selectedCategories includes: aCategory)
 	^(self selectedCategories includes: aCategory)
@@ -2146,9 +2146,9 @@ isSelectedCategory: aCategory
 
 
 isSelectedClass: aClass
 isSelectedClass: aClass
 	^(self selectedClasses includes: aClass)
 	^(self selectedClasses includes: aClass)
-! !!
+! !
 
 
-!!TestRunner methodsFor: 'updating'!!
+!TestRunner methodsFor: 'updating'!
 
 
 updateCategoriesList
 updateCategoriesList
     packagesList contents: [:html |
     packagesList contents: [:html |
@@ -2191,19 +2191,19 @@ updateStatusDiv
 	statusDiv class: 'sunit status ', result status.
 	statusDiv class: 'sunit status ', result status.
 	statusDiv contents: [:html |
 	statusDiv contents: [:html |
 		html span with: self statusInfo]
 		html span with: self statusInfo]
-! !!
+! !
 
 
 TabWidget subclass: #Workspace
 TabWidget subclass: #Workspace
 	instanceVariableNames: 'sourceArea'
 	instanceVariableNames: 'sourceArea'
 	category: 'IDE'!
 	category: 'IDE'!
 
 
-!!Workspace methodsFor: 'accessing'!!
+!Workspace methodsFor: 'accessing'!
 
 
 label
 label
     ^'Workspace'
     ^'Workspace'
-! !!
+! !
 
 
-!!Workspace methodsFor: 'actions'!!
+!Workspace methodsFor: 'actions'!
 
 
 clearWorkspace
 clearWorkspace
     sourceArea clear
     sourceArea clear
@@ -2223,9 +2223,9 @@ inspectIt
 
 
 printIt
 printIt
 	sourceArea printIt
 	sourceArea printIt
-! !!
+! !
 
 
-!!Workspace methodsFor: 'rendering'!!
+!Workspace methodsFor: 'rendering'!
 
 
 renderBoxOn: html
 renderBoxOn: html
     sourceArea := SourceArea new.
     sourceArea := SourceArea new.
@@ -2252,9 +2252,9 @@ renderButtonsOn: html
     html button
     html button
 	with: 'Clear workspace';
 	with: 'Clear workspace';
 	onClick: [self clearWorkspace]
 	onClick: [self clearWorkspace]
-! !!
+! !
 
 
-!!Object methodsFor: '*IDE'!!
+!Object methodsFor: '*IDE'!
 
 
 inspect
 inspect
 	Inspector new 
 	Inspector new 
@@ -2271,9 +2271,9 @@ inspectOn: anInspector
 	anInspector 
 	anInspector 
 		setLabel: self printString;
 		setLabel: self printString;
 		setVariables: variables
 		setVariables: variables
-! !!
+! !
 
 
-!!Collection methodsFor: '*IDE'!!
+!Collection methodsFor: '*IDE'!
 
 
 inspectOn: anInspector
 inspectOn: anInspector
 	| variables |
 	| variables |
@@ -2284,9 +2284,9 @@ inspectOn: anInspector
 	anInspector 
 	anInspector 
 		setLabel: self printString;
 		setLabel: self printString;
 		setVariables: variables
 		setVariables: variables
-! !!
+! !
 
 
-!!HashedCollection methodsFor: '*IDE'!!
+!HashedCollection methodsFor: '*IDE'!
 
 
 inspectOn: anInspector
 inspectOn: anInspector
 	| variables |
 	| variables |
@@ -2298,9 +2298,9 @@ inspectOn: anInspector
 	anInspector 
 	anInspector 
 		setLabel: self printString;
 		setLabel: self printString;
 		setVariables: variables
 		setVariables: variables
-! !!
+! !
 
 
-!!String methodsFor: '*IDE'!!
+!String methodsFor: '*IDE'!
 
 
 inspectOn: anInspector
 inspectOn: anInspector
 	| label |
 	| label |
@@ -2309,9 +2309,9 @@ inspectOn: anInspector
 		ifTrue: [label := (self printString copyFrom: 1 to: 30), '...''']
 		ifTrue: [label := (self printString copyFrom: 1 to: 30), '...''']
 		ifFalse: [label := self printString]. 
 		ifFalse: [label := self printString]. 
 	anInspector setLabel: label
 	anInspector setLabel: label
-! !!
+! !
 
 
-!!Set methodsFor: '*IDE'!!
+!Set methodsFor: '*IDE'!
 
 
 inspectOn: anInspector
 inspectOn: anInspector
 	| variables |
 	| variables |
@@ -2322,9 +2322,9 @@ inspectOn: anInspector
 	anInspector 
 	anInspector 
 		setLabel: self printString;
 		setLabel: self printString;
 		setVariables: variables
 		setVariables: variables
-! !!
+! !
 
 
-!!Date methodsFor: '*IDE'!!
+!Date methodsFor: '*IDE'!
 
 
 inspectOn: anInspector
 inspectOn: anInspector
 	| variables |
 	| variables |
@@ -2340,9 +2340,9 @@ inspectOn: anInspector
 	anInspector 
 	anInspector 
 		setLabel: self printString;
 		setLabel: self printString;
 		setVariables: variables
 		setVariables: variables
-! !!
+! !
 
 
-!!Date methodsFor: '*IDE'!!
+!Date methodsFor: '*IDE'!
 
 
 inspectOn: anInspector
 inspectOn: anInspector
 	| variables |
 	| variables |
@@ -2358,9 +2358,9 @@ inspectOn: anInspector
 	anInspector 
 	anInspector 
 		setLabel: self printString;
 		setLabel: self printString;
 		setVariables: variables
 		setVariables: variables
-! !!
+! !
 
 
-!!MethodContext methodsFor: '*IDE'!!
+!MethodContext methodsFor: '*IDE'!
 
 
 inspectOn: anInspector
 inspectOn: anInspector
 	| variables |
 	| variables |
@@ -2375,5 +2375,5 @@ inspectOn: anInspector
 	anInspector 
 	anInspector 
 		setLabel: self printString;
 		setLabel: self printString;
 		setVariables: variables
 		setVariables: variables
-! !!
+! !
 
 

+ 134 - 134
st/Kernel-Objects.st

@@ -39,7 +39,7 @@ Objects understand equality  `#=` and identity `#==` comparison.
 - `#doesNotUnderstand:` handles the fact that there was an attempt to send the given message to the receiver but the receiver does not understand this message.
 - `#doesNotUnderstand:` handles the fact that there was an attempt to send the given message to the receiver but the receiver does not understand this message.
   Overriding this message can be useful to implement proxies for example.!
   Overriding this message can be useful to implement proxies for example.!
 
 
-!!Object methodsFor: 'accessing'!!
+!Object methodsFor: 'accessing'!
 
 
 basicAt: aString
 basicAt: aString
 	<return self[aString]>
 	<return self[aString]>
@@ -79,9 +79,9 @@ size
 
 
 yourself
 yourself
 	^self
 	^self
-! !!
+! !
 
 
-!!Object methodsFor: 'comparing'!!
+!Object methodsFor: 'comparing'!
 
 
 = anObject
 = anObject
 	^self == anObject
 	^self == anObject
@@ -97,9 +97,9 @@ yourself
 
 
 ~~ anObject
 ~~ anObject
 	^(self == anObject) = false
 	^(self == anObject) = false
-! !!
+! !
 
 
-!!Object methodsFor: 'converting'!!
+!Object methodsFor: 'converting'!
 
 
 -> anObject
 -> anObject
 	^Association key: self value: anObject
 	^Association key: self value: anObject
@@ -123,9 +123,9 @@ asJavascript
 
 
 asString
 asString
 	^self printString
 	^self printString
-! !!
+! !
 
 
-!!Object methodsFor: 'copying'!!
+!Object methodsFor: 'copying'!
 
 
 copy
 copy
 	^self shallowCopy postCopy
 	^self shallowCopy postCopy
@@ -156,9 +156,9 @@ shallowCopy
 	    }
 	    }
 	    return copy;
 	    return copy;
 	>
 	>
-! !!
+! !
 
 
-!!Object methodsFor: 'error handling'!!
+!Object methodsFor: 'error handling'!
 
 
 deprecatedAPI
 deprecatedAPI
 	"Just a simple way to deprecate methods.
 	"Just a simple way to deprecate methods.
@@ -193,14 +193,14 @@ subclassResponsibility
 try: aBlock catch: anotherBlock
 try: aBlock catch: anotherBlock
 	<try{result = aBlock()} catch(e) {result = anotherBlock(e)};
 	<try{result = aBlock()} catch(e) {result = anotherBlock(e)};
 	return result;>
 	return result;>
-! !!
+! !
 
 
-!!Object methodsFor: 'initialization'!!
+!Object methodsFor: 'initialization'!
 
 
 initialize
 initialize
-! !!
+! !
 
 
-!!Object methodsFor: 'message handling'!!
+!Object methodsFor: 'message handling'!
 
 
 basicPerform: aSymbol 
 basicPerform: aSymbol 
 	^self basicPerform: aSymbol withArguments: #()
 	^self basicPerform: aSymbol withArguments: #()
@@ -216,9 +216,9 @@ perform: aSymbol
 
 
 perform: aSymbol withArguments: aCollection
 perform: aSymbol withArguments: aCollection
 	^self basicPerform: aSymbol asSelector withArguments: aCollection
 	^self basicPerform: aSymbol asSelector withArguments: aCollection
-! !!
+! !
 
 
-!!Object methodsFor: 'printing'!!
+!Object methodsFor: 'printing'!
 
 
 log: aString block: aBlock
 log: aString block: aBlock
 
 
@@ -244,9 +244,9 @@ storeString
 	can be reconstructed."
 	can be reconstructed."
 
 
 	^ String streamContents: [:s | self storeOn: s]
 	^ String streamContents: [:s | self storeOn: s]
-! !!
+! !
 
 
-!!Object methodsFor: 'testing'!!
+!Object methodsFor: 'testing'!
 
 
 ifNil: aBlock
 ifNil: aBlock
 	"inlined in the Compiler"
 	"inlined in the Compiler"
@@ -308,13 +308,13 @@ isSymbol
 
 
 notNil
 notNil
 	^self isNil not
 	^self isNil not
-! !!
+! !
 
 
-!!Object class methodsFor: 'initialization'!!
+!Object class methodsFor: 'initialization'!
 
 
 initialize
 initialize
 	"no op"
 	"no op"
-! !!
+! !
 
 
 Object subclass: #Boolean
 Object subclass: #Boolean
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -325,14 +325,14 @@ Boolean wraps the JavaScript `Boolean()` constructor. The `true` and `false` obj
 Boolean defines the protocol for logic testing operations and conditional control structures for the logical values.
 Boolean defines the protocol for logic testing operations and conditional control structures for the logical values.
 Boolean instances are weither `true` or `false`.!
 Boolean instances are weither `true` or `false`.!
 
 
-!!Boolean methodsFor: 'comparing'!!
+!Boolean methodsFor: 'comparing'!
 
 
 = aBoolean
 = aBoolean
 	aBoolean class = self class ifFalse: [^false].
 	aBoolean class = self class ifFalse: [^false].
 	<return Boolean(self == true) == aBoolean>
 	<return Boolean(self == true) == aBoolean>
-! !!
+! !
 
 
-!!Boolean methodsFor: 'controlling'!!
+!Boolean methodsFor: 'controlling'!
 
 
 & aBoolean
 & aBoolean
 	<
 	<
@@ -394,15 +394,15 @@ or: aBlock
 		return aBoolean;
 		return aBoolean;
 	    }
 	    }
 	>
 	>
-! !!
+! !
 
 
-!!Boolean methodsFor: 'converting'!!
+!Boolean methodsFor: 'converting'!
 
 
 asJSON
 asJSON
 	^self
 	^self
-! !!
+! !
 
 
-!!Boolean methodsFor: 'copying'!!
+!Boolean methodsFor: 'copying'!
 
 
 deepCopy
 deepCopy
 	^self
 	^self
@@ -410,13 +410,13 @@ deepCopy
 
 
 shallowCopy
 shallowCopy
 	^self
 	^self
-! !!
+! !
 
 
-!!Boolean methodsFor: 'printing'!!
+!Boolean methodsFor: 'printing'!
 
 
 printString
 printString
 	<return self.toString()>
 	<return self.toString()>
-! !!
+! !
 
 
 Object subclass: #Date
 Object subclass: #Date
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -427,7 +427,7 @@ Amber and answer the same date object.
 
 
 Date wraps the `Date()` JavaScript constructor, and Smalltalk date objects are JavaScript date objects.!
 Date wraps the `Date()` JavaScript constructor, and Smalltalk date objects are JavaScript date objects.!
 
 
-!!Date methodsFor: 'accessing'!!
+!Date methodsFor: 'accessing'!
 
 
 day
 day
 	^self dayOfWeek
 	^self dayOfWeek
@@ -507,9 +507,9 @@ year
 
 
 year: aNumber
 year: aNumber
 	<self.setFullYear(aNumber)>
 	<self.setFullYear(aNumber)>
-! !!
+! !
 
 
-!!Date methodsFor: 'arithmetic'!!
+!Date methodsFor: 'arithmetic'!
 
 
 + aDate
 + aDate
 	<return self + aDate>
 	<return self + aDate>
@@ -517,9 +517,9 @@ year: aNumber
 
 
 - aDate
 - aDate
 	<return self - aDate>
 	<return self - aDate>
-! !!
+! !
 
 
-!!Date methodsFor: 'comparing'!!
+!Date methodsFor: 'comparing'!
 
 
 < aDate
 < aDate
 	<return self < aDate>
 	<return self < aDate>
@@ -535,9 +535,9 @@ year: aNumber
 
 
 >= aDate
 >= aDate
 	<return self >>= aDate>
 	<return self >>= aDate>
-! !!
+! !
 
 
-!!Date methodsFor: 'converting'!!
+!Date methodsFor: 'converting'!
 
 
 asDateString
 asDateString
 	<return self.toDateString()>
 	<return self.toDateString()>
@@ -561,15 +561,15 @@ asString
 
 
 asTimeString
 asTimeString
 	<return self.toTimeString()>
 	<return self.toTimeString()>
-! !!
+! !
 
 
-!!Date methodsFor: 'printing'!!
+!Date methodsFor: 'printing'!
 
 
 printString
 printString
 	^self asString
 	^self asString
-! !!
+! !
 
 
-!!Date class methodsFor: 'instance creation'!!
+!Date class methodsFor: 'instance creation'!
 
 
 fromMilliseconds: aNumber
 fromMilliseconds: aNumber
 	^self new: aNumber
 	^self new: aNumber
@@ -601,7 +601,7 @@ now
 
 
 today
 today
 	^self new
 	^self new
-! !!
+! !
 
 
 Object subclass: #Date
 Object subclass: #Date
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -612,7 +612,7 @@ Amber and answer the same date object.
 
 
 Date wraps the `Date()` JavaScript constructor, and Smalltalk date objects are JavaScript date objects.!
 Date wraps the `Date()` JavaScript constructor, and Smalltalk date objects are JavaScript date objects.!
 
 
-!!Date methodsFor: 'accessing'!!
+!Date methodsFor: 'accessing'!
 
 
 day
 day
 	^self dayOfWeek
 	^self dayOfWeek
@@ -692,9 +692,9 @@ year
 
 
 year: aNumber
 year: aNumber
 	<self.setFullYear(aNumber)>
 	<self.setFullYear(aNumber)>
-! !!
+! !
 
 
-!!Date methodsFor: 'arithmetic'!!
+!Date methodsFor: 'arithmetic'!
 
 
 + aDate
 + aDate
 	<return self + aDate>
 	<return self + aDate>
@@ -702,9 +702,9 @@ year: aNumber
 
 
 - aDate
 - aDate
 	<return self - aDate>
 	<return self - aDate>
-! !!
+! !
 
 
-!!Date methodsFor: 'comparing'!!
+!Date methodsFor: 'comparing'!
 
 
 < aDate
 < aDate
 	<return self < aDate>
 	<return self < aDate>
@@ -720,9 +720,9 @@ year: aNumber
 
 
 >= aDate
 >= aDate
 	<return self >>= aDate>
 	<return self >>= aDate>
-! !!
+! !
 
 
-!!Date methodsFor: 'converting'!!
+!Date methodsFor: 'converting'!
 
 
 asDateString
 asDateString
 	<return self.toDateString()>
 	<return self.toDateString()>
@@ -746,15 +746,15 @@ asString
 
 
 asTimeString
 asTimeString
 	<return self.toTimeString()>
 	<return self.toTimeString()>
-! !!
+! !
 
 
-!!Date methodsFor: 'printing'!!
+!Date methodsFor: 'printing'!
 
 
 printString
 printString
 	^self asString
 	^self asString
-! !!
+! !
 
 
-!!Date class methodsFor: 'instance creation'!!
+!Date class methodsFor: 'instance creation'!
 
 
 fromMilliseconds: aNumber
 fromMilliseconds: aNumber
 	^self new: aNumber
 	^self new: aNumber
@@ -786,7 +786,7 @@ now
 
 
 today
 today
 	^self new
 	^self new
-! !!
+! !
 
 
 Object subclass: #JSObjectProxy
 Object subclass: #JSObjectProxy
 	instanceVariableNames: 'jsObject'
 	instanceVariableNames: 'jsObject'
@@ -814,7 +814,7 @@ Smalltalk messages sends are converted to JavaScript function calls or object pr
 
 
 __Note:__ For keyword-based messages, only the first keyword is kept: `window foo: 1 bar: 2` is equivalent to `window foo: 1 baz: 2`.!
 __Note:__ For keyword-based messages, only the first keyword is kept: `window foo: 1 bar: 2` is equivalent to `window foo: 1 baz: 2`.!
 
 
-!!JSObjectProxy methodsFor: 'accessing'!!
+!JSObjectProxy methodsFor: 'accessing'!
 
 
 at: aSymbol
 at: aSymbol
 	| attr |
 	| attr |
@@ -834,9 +834,9 @@ jsObject
 
 
 jsObject: aJSObject
 jsObject: aJSObject
 	jsObject := aJSObject
 	jsObject := aJSObject
-! !!
+! !
 
 
-!!JSObjectProxy methodsFor: 'proxy'!!
+!JSObjectProxy methodsFor: 'proxy'!
 
 
 doesNotUnderstand: aMessage
 doesNotUnderstand: aMessage
 	| obj selector jsSelector arguments |
 	| obj selector jsSelector arguments |
@@ -861,15 +861,15 @@ inspectOn: anInspector
 
 
 printString
 printString
 	^self jsObject toString
 	^self jsObject toString
-! !!
+! !
 
 
-!!JSObjectProxy class methodsFor: 'instance creation'!!
+!JSObjectProxy class methodsFor: 'instance creation'!
 
 
 on: aJSObject
 on: aJSObject
 	^self new
 	^self new
 		jsObject: aJSObject;
 		jsObject: aJSObject;
 		yourself
 		yourself
-! !!
+! !
 
 
 Object subclass: #Number
 Object subclass: #Number
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -889,13 +889,13 @@ A Number can be used to evaluate a Block a fixed number of times:
 	
 	
 	1 to: 10 by: 2 do: [:aNumber| Transcript show: aNumber asString; cr].!
 	1 to: 10 by: 2 do: [:aNumber| Transcript show: aNumber asString; cr].!
 
 
-!!Number methodsFor: 'accessing'!!
+!Number methodsFor: 'accessing'!
 
 
 identityHash
 identityHash
 	^self asString, 'n'
 	^self asString, 'n'
-! !!
+! !
 
 
-!!Number methodsFor: 'arithmetic'!!
+!Number methodsFor: 'arithmetic'!
 
 
 * aNumber
 * aNumber
 	"Inlined in the Compiler"
 	"Inlined in the Compiler"
@@ -939,9 +939,9 @@ sqrt
 
 
 squared
 squared
 	^self * self
 	^self * self
-! !!
+! !
 
 
-!!Number methodsFor: 'comparing'!!
+!Number methodsFor: 'comparing'!
 
 
 < aNumber
 < aNumber
 	"Inlined in the Compiler"
 	"Inlined in the Compiler"
@@ -966,9 +966,9 @@ squared
 >= aNumber
 >= aNumber
 	"Inlined in the Compiler"
 	"Inlined in the Compiler"
 	<return self >>= aNumber>
 	<return self >>= aNumber>
-! !!
+! !
 
 
-!!Number methodsFor: 'converting'!!
+!Number methodsFor: 'converting'!
 
 
 @ aNumber
 @ aNumber
 	^Point x: self y: aNumber
 	^Point x: self y: aNumber
@@ -1037,9 +1037,9 @@ truncated
         ifFalse: [<result = (Math.floor(self * (-1)) * (-1));>].
         ifFalse: [<result = (Math.floor(self * (-1)) * (-1));>].
 
 
     ^ result
     ^ result
-! !!
+! !
 
 
-!!Number methodsFor: 'copying'!!
+!Number methodsFor: 'copying'!
 
 
 copy
 copy
 	^self
 	^self
@@ -1047,9 +1047,9 @@ copy
 
 
 deepCopy
 deepCopy
 	^self copy
 	^self copy
-! !!
+! !
 
 
-!!Number methodsFor: 'enumerating'!!
+!Number methodsFor: 'enumerating'!
 
 
 timesRepeat: aBlock
 timesRepeat: aBlock
 	| integer count |
 	| integer count |
@@ -1081,9 +1081,9 @@ to: stop do: aBlock
 		whileTrue: 
 		whileTrue: 
 			[aBlock value: nextValue.
 			[aBlock value: nextValue.
 			nextValue := nextValue + 1]
 			nextValue := nextValue + 1]
-! !!
+! !
 
 
-!!Number methodsFor: 'printing'!!
+!Number methodsFor: 'printing'!
 
 
 printShowingDecimalPlaces: placesDesired
 printShowingDecimalPlaces: placesDesired
 	<return self.toFixed(placesDesired)>
 	<return self.toFixed(placesDesired)>
@@ -1091,9 +1091,9 @@ printShowingDecimalPlaces: placesDesired
 
 
 printString
 printString
 	<return String(self)>
 	<return String(self)>
-! !!
+! !
 
 
-!!Number methodsFor: 'testing'!!
+!Number methodsFor: 'testing'!
 
 
 even
 even
 	^ 0 = (self \\ 2)
 	^ 0 = (self \\ 2)
@@ -1121,9 +1121,9 @@ positive
 	"Answer whether the receiver is positive or equal to 0. (ST-80 protocol)."
 	"Answer whether the receiver is positive or equal to 0. (ST-80 protocol)."
 
 
 	^ self >= 0
 	^ self >= 0
-! !!
+! !
 
 
-!!Number methodsFor: 'timeouts/intervals'!!
+!Number methodsFor: 'timeouts/intervals'!
 
 
 clearInterval
 clearInterval
 	<clearInterval(Number(self))>
 	<clearInterval(Number(self))>
@@ -1131,13 +1131,13 @@ clearInterval
 
 
 clearTimeout
 clearTimeout
 	<clearTimeout(Number(self))>
 	<clearTimeout(Number(self))>
-! !!
+! !
 
 
-!!Number class methodsFor: 'instance creation'!!
+!Number class methodsFor: 'instance creation'!
 
 
 pi
 pi
 	<return Math.PI>
 	<return Math.PI>
-! !!
+! !
 
 
 Object subclass: #Package
 Object subclass: #Package
 	instanceVariableNames: 'commitPathJs commitPathSt'
 	instanceVariableNames: 'commitPathJs commitPathSt'
@@ -1162,7 +1162,7 @@ You can fetch a package from the server:
 
 
 	Package fetch: 'Additional-Examples'!
 	Package fetch: 'Additional-Examples'!
 
 
-!!Package methodsFor: 'accessing'!!
+!Package methodsFor: 'accessing'!
 
 
 commitPathJs
 commitPathJs
 	^ commitPathJs ifNil: [self class defaultCommitPathJs]
 	^ commitPathJs ifNil: [self class defaultCommitPathJs]
@@ -1209,9 +1209,9 @@ properties: aDict
 		<object[key] = value>.
 		<object[key] = value>.
 	].
 	].
 	<return self.properties = object>
 	<return self.properties = object>
-! !!
+! !
 
 
-!!Package methodsFor: 'classes'!!
+!Package methodsFor: 'classes'!
 
 
 classes
 classes
 	"We need to do a reverse scan."
 	"We need to do a reverse scan."
@@ -1222,15 +1222,15 @@ sortedClasses
     "Answer all classes in the receiver, sorted by superclass/subclasses and by class name for common subclasses (Issue #143)"
     "Answer all classes in the receiver, sorted by superclass/subclasses and by class name for common subclasses (Issue #143)"
 
 
     ^self class sortedClasses: self classes
     ^self class sortedClasses: self classes
-! !!
+! !
 
 
-!!Package methodsFor: 'printing'!!
+!Package methodsFor: 'printing'!
 
 
 printString
 printString
 	^self name
 	^self name
-! !!
+! !
 
 
-!!Package methodsFor: 'private'!!
+!Package methodsFor: 'private'!
 
 
 jsProperties
 jsProperties
 	<return self.properties>
 	<return self.properties>
@@ -1242,9 +1242,9 @@ jsProperties: aJSObject
 
 
 propertiesAsJSON
 propertiesAsJSON
 	<return JSON.stringify(self.properties)>
 	<return JSON.stringify(self.properties)>
-! !!
+! !
 
 
-!!Package methodsFor: 'properties'!!
+!Package methodsFor: 'properties'!
 
 
 propertyAt: key
 propertyAt: key
 
 
@@ -1259,11 +1259,11 @@ propertyAt: key ifAbsent: block
 propertyAt: key put: value
 propertyAt: key put: value
 
 
 	<return self.properties[key] = value>
 	<return self.properties[key] = value>
-! !!
+! !
 
 
 Package class instanceVariableNames: 'defaultCommitPathJs defaultCommitPathSt'!
 Package class instanceVariableNames: 'defaultCommitPathJs defaultCommitPathSt'!
 
 
-!!Package class methodsFor: 'commit paths'!!
+!Package class methodsFor: 'commit paths'!
 
 
 defaultCommitPathJs
 defaultCommitPathJs
 	^ defaultCommitPathJs ifNil: [ defaultCommitPathJs := 'js']
 	^ defaultCommitPathJs ifNil: [ defaultCommitPathJs := 'js']
@@ -1284,9 +1284,9 @@ defaultCommitPathSt: aString
 resetCommitPaths
 resetCommitPaths
         defaultCommitPathJs := nil.
         defaultCommitPathJs := nil.
         defaultCommitPathSt := nil.
         defaultCommitPathSt := nil.
-! !!
+! !
 
 
-!!Package class methodsFor: 'loading-storing'!!
+!Package class methodsFor: 'loading-storing'!
 
 
 commitToLocalStorage: aPackageName
 commitToLocalStorage: aPackageName
 	| key sourceCode |
 	| key sourceCode |
@@ -1307,9 +1307,9 @@ init: aPackageName
 	(smalltalk classes select: [ :each | <each.pkg.pkgName == aPackageName> ])
 	(smalltalk classes select: [ :each | <each.pkg.pkgName == aPackageName> ])
 		do: [ :each | <smalltalk.init(each)> ];
 		do: [ :each | <smalltalk.init(each)> ];
 		do: [ :each | each initialize ]
 		do: [ :each | each initialize ]
-! !!
+! !
 
 
-!!Package class methodsFor: 'not yet classified'!!
+!Package class methodsFor: 'not yet classified'!
 
 
 named: aPackageName
 named: aPackageName
 
 
@@ -1319,9 +1319,9 @@ named: aPackageName
 named: aPackageName ifAbsent: aBlock
 named: aPackageName ifAbsent: aBlock
 
 
 	^Smalltalk current packageAt: aPackageName ifAbsent: aBlock
 	^Smalltalk current packageAt: aPackageName ifAbsent: aBlock
-! !!
+! !
 
 
-!!Package class methodsFor: 'sorting'!!
+!Package class methodsFor: 'sorting'!
 
 
 sortedClasses: classes
 sortedClasses: classes
     "Answer classes, sorted by superclass/subclasses and by class name for common subclasses (Issue #143)"
     "Answer classes, sorted by superclass/subclasses and by class name for common subclasses (Issue #143)"
@@ -1340,7 +1340,7 @@ sortedClasses: classes
     nodes do: [:aNode |
     nodes do: [:aNode |
         aNode traverseClassesWith: expandedClasses].
         aNode traverseClassesWith: expandedClasses].
     ^expandedClasses
     ^expandedClasses
-! !!
+! !
 
 
 Object subclass: #Point
 Object subclass: #Point
 	instanceVariableNames: 'x y'
 	instanceVariableNames: 'x y'
@@ -1365,7 +1365,7 @@ Points can then be arithmetically manipulated:
 
 
 Amber does not have much behavior in this class out-of-the-box.!
 Amber does not have much behavior in this class out-of-the-box.!
 
 
-!!Point methodsFor: 'accessing'!!
+!Point methodsFor: 'accessing'!
 
 
 x
 x
 	^x
 	^x
@@ -1381,9 +1381,9 @@ y
 
 
 y: aNumber
 y: aNumber
 	y := aNumber
 	y := aNumber
-! !!
+! !
 
 
-!!Point methodsFor: 'arithmetic'!!
+!Point methodsFor: 'arithmetic'!
 
 
 * aPoint
 * aPoint
 	^Point x: self x * aPoint asPoint x y: self y * aPoint asPoint y
 	^Point x: self x * aPoint asPoint x y: self y * aPoint asPoint y
@@ -1404,15 +1404,15 @@ y: aNumber
 = aPoint
 = aPoint
 	^aPoint class = self class and: [
 	^aPoint class = self class and: [
 		(aPoint x = self x) & (aPoint y = self y)]
 		(aPoint x = self x) & (aPoint y = self y)]
-! !!
+! !
 
 
-!!Point methodsFor: 'converting'!!
+!Point methodsFor: 'converting'!
 
 
 asPoint
 asPoint
 	^self
 	^self
-! !!
+! !
 
 
-!!Point methodsFor: 'printing'!!
+!Point methodsFor: 'printing'!
 
 
 printString
 printString
 	"Print receiver in classic x@y notation."
 	"Print receiver in classic x@y notation."
@@ -1424,23 +1424,23 @@ printString
 				"Avoid ambiguous @- construct"
 				"Avoid ambiguous @- construct"
 				stream space].
 				stream space].
 		stream nextPutAll: y printString]
 		stream nextPutAll: y printString]
-! !!
+! !
 
 
-!!Point methodsFor: 'transforming'!!
+!Point methodsFor: 'transforming'!
 
 
 translateBy: delta 
 translateBy: delta 
 	"Answer a Point translated by delta (an instance of Point)."
 	"Answer a Point translated by delta (an instance of Point)."
 	^(delta x + x) @ (delta y + y)
 	^(delta x + x) @ (delta y + y)
-! !!
+! !
 
 
-!!Point class methodsFor: 'instance creation'!!
+!Point class methodsFor: 'instance creation'!
 
 
 x: aNumber y: anotherNumber
 x: aNumber y: anotherNumber
 	^self new
 	^self new
 		x: aNumber;
 		x: aNumber;
 		y: anotherNumber;
 		y: anotherNumber;
 		yourself
 		yourself
-! !!
+! !
 
 
 Object subclass: #Random
 Object subclass: #Random
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -1472,7 +1472,7 @@ Since `#atRandom` is implemented in `SequencableCollection` you can easy pick an
 
 
 Since Amber does not have Characters this will return a `String` of length 1 like for example `'b'`.!
 Since Amber does not have Characters this will return a `String` of length 1 like for example `'b'`.!
 
 
-!!Random methodsFor: 'accessing'!!
+!Random methodsFor: 'accessing'!
 
 
 next
 next
 	<return Math.random()>
 	<return Math.random()>
@@ -1480,7 +1480,7 @@ next
 
 
 next: anInteger
 next: anInteger
     ^(1 to: anInteger) collect: [:each | self next]
     ^(1 to: anInteger) collect: [:each | self next]
-! !!
+! !
 
 
 Object subclass: #Smalltalk
 Object subclass: #Smalltalk
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -1512,7 +1512,7 @@ __note:__ classes and packages are accessed using strings, not symbols
 The `#parse:` method is used to parse Smalltalk source code. 
 The `#parse:` method is used to parse Smalltalk source code. 
 It requires the `Compiler` package and the `js/parser.js` parser file in order to work!
 It requires the `Compiler` package and the `js/parser.js` parser file in order to work!
 
 
-!!Smalltalk methodsFor: 'accessing'!!
+!Smalltalk methodsFor: 'accessing'!
 
 
 at: aString
 at: aString
 	<return self[aString]>
 	<return self[aString]>
@@ -1560,9 +1560,9 @@ send: aSelector to: anObject arguments: aCollection
 	| selector |
 	| selector |
 	selector := aSelector asString asSelector.
 	selector := aSelector asString asSelector.
 	<self.send(anObject, selector, aCollection)>
 	<self.send(anObject, selector, aCollection)>
-! !!
+! !
 
 
-!!Smalltalk methodsFor: 'classes'!!
+!Smalltalk methodsFor: 'classes'!
 
 
 removeClass: aClass
 removeClass: aClass
 	aClass isMetaclass ifTrue: [self error: aClass asString, ' is a Metaclass and cannot be removed!!'].
 	aClass isMetaclass ifTrue: [self error: aClass asString, ' is a Metaclass and cannot be removed!!'].
@@ -1571,9 +1571,9 @@ removeClass: aClass
 	aClass class methodDictionary values do: [:each |
 	aClass class methodDictionary values do: [:each |
 		aClass class removeCompiledMethod: each].
 		aClass class removeCompiledMethod: each].
 	self basicDelete: aClass name
 	self basicDelete: aClass name
-! !!
+! !
 
 
-!!Smalltalk methodsFor: 'packages'!!
+!Smalltalk methodsFor: 'packages'!
 
 
 packageAt: packageName
 packageAt: packageName
        <return self.packages[packageName]>
        <return self.packages[packageName]>
@@ -1608,9 +1608,9 @@ renamePackage: packageName to: newName
 	<smalltalk.packages[newName] = smalltalk.packages[packageName]>.
 	<smalltalk.packages[newName] = smalltalk.packages[packageName]>.
 	pkg name: newName.
 	pkg name: newName.
 	self deletePackage: packageName.
 	self deletePackage: packageName.
-! !!
+! !
 
 
-!!Smalltalk methodsFor: 'private'!!
+!Smalltalk methodsFor: 'private'!
 
 
 createPackage: packageName
 createPackage: packageName
 	"Create and bind a new package with given name and return it."
 	"Create and bind a new package with given name and return it."
@@ -1634,15 +1634,15 @@ deletePackage: packageName
 	To remove a package, use #removePackage instead."
 	To remove a package, use #removePackage instead."
 
 
        <delete smalltalk.packages[packageName]>
        <delete smalltalk.packages[packageName]>
-! !!
+! !
 
 
 Smalltalk class instanceVariableNames: 'current'!
 Smalltalk class instanceVariableNames: 'current'!
 
 
-!!Smalltalk class methodsFor: 'accessing'!!
+!Smalltalk class methodsFor: 'accessing'!
 
 
 current
 current
 	<return smalltalk>
 	<return smalltalk>
-! !!
+! !
 
 
 Object subclass: #UndefinedObject
 Object subclass: #UndefinedObject
 	instanceVariableNames: ''
 	instanceVariableNames: ''
@@ -1652,7 +1652,7 @@ UndefinedObject describes the behavior of its sole instance, `nil`. `nil` repres
 
 
 `nil` is the Smalltalk representation of the `undefined` JavaScript object.!
 `nil` is the Smalltalk representation of the `undefined` JavaScript object.!
 
 
-!!UndefinedObject methodsFor: 'class creation'!!
+!UndefinedObject methodsFor: 'class creation'!
 
 
 subclass: aString instanceVariableNames: anotherString
 subclass: aString instanceVariableNames: anotherString
 	^self subclass: aString instanceVariableNames: anotherString package: nil
 	^self subclass: aString instanceVariableNames: anotherString package: nil
@@ -1667,15 +1667,15 @@ subclass: aString instanceVariableNames: aString2 category: aString3
 subclass: aString instanceVariableNames: aString2 package: aString3
 subclass: aString instanceVariableNames: aString2 package: aString3
 	^ClassBuilder new
 	^ClassBuilder new
 	    superclass: self subclass: aString instanceVariableNames: aString2 package: aString3
 	    superclass: self subclass: aString instanceVariableNames: aString2 package: aString3
-! !!
+! !
 
 
-!!UndefinedObject methodsFor: 'converting'!!
+!UndefinedObject methodsFor: 'converting'!
 
 
 asJSON
 asJSON
 	^null
 	^null
-! !!
+! !
 
 
-!!UndefinedObject methodsFor: 'copying'!!
+!UndefinedObject methodsFor: 'copying'!
 
 
 deepCopy
 deepCopy
 	^self
 	^self
@@ -1683,15 +1683,15 @@ deepCopy
 
 
 shallowCopy
 shallowCopy
 	^self
 	^self
-! !!
+! !
 
 
-!!UndefinedObject methodsFor: 'printing'!!
+!UndefinedObject methodsFor: 'printing'!
 
 
 printString
 printString
     ^'nil'
     ^'nil'
-! !!
+! !
 
 
-!!UndefinedObject methodsFor: 'testing'!!
+!UndefinedObject methodsFor: 'testing'!
 
 
 ifNil: aBlock
 ifNil: aBlock
 	"inlined in the Compiler"
 	"inlined in the Compiler"
@@ -1719,11 +1719,11 @@ isNil
 
 
 notNil
 notNil
 	^false
 	^false
-! !!
+! !
 
 
-!!UndefinedObject class methodsFor: 'instance creation'!!
+!UndefinedObject class methodsFor: 'instance creation'!
 
 
 new
 new
 	    self error: 'You cannot create new instances of UndefinedObject. Use nil'
 	    self error: 'You cannot create new instances of UndefinedObject. Use nil'
-! !!
+! !