Selaa lähdekoodia

Merge remote-tracking branch 'upstream/master'

Laurent Laffont 12 vuotta sitten
vanhempi
commit
9ff9e2d28b

+ 58 - 84
bin/jtalkc

@@ -15,15 +15,15 @@ popd >/dev/null
 
 function usage {
 	cat <<ENDOFHELP
-Usage: $0 [-N|D|E] [-K|C|J] [-o] [-O|-A] [-d] [-s suffix] [-m class] [-M file]
-          [-i] [-I file] [file1 [file2 ...]] [Program]
+Usage: $0 [-L level] [-l lib1,lib2...] [-i file] [-m class] [-M file]
+          [-o] [-O|-A] [-d] [-s suffix] [-S suffix] [file1 [file2 ...]] [Program]
 
    Will compile Jtalk files - either separately or into a runnable complete
-   program. If no files are listed only a linking stage is performed.
+   program. If no .st files are listed only a linking stage is performed.
    Files listed will be handled using these rules:
 
    *.js
-     Files are concatenated in listed order.
+     Files are linked (concatenated) in listed order.
      If not found we look in $JTALK/js
 
    *.st
@@ -37,29 +37,37 @@ Usage: $0 [-N|D|E] [-K|C|J] [-o] [-O|-A] [-d] [-s suffix] [-m class] [-M file]
    a .js file. Otherwise a <Program>.js file is linked together based on
    the options:
 
-  -N or -D or -E
-     Compilation target. Currently Node.js, D8 (V8 shell) or Enyo (webOS 3.0).
-     All currentl imply "-K -I" so boot.js and Kernel.js are added first and init.js
-     is added last.
+  -L level
+     Add libraries to a predefined level (default is KERNEL) of environment
+     where level is:
 
-  -K
-     Add libraries to get minimal Jtalk Kernel running.
+        KERNEL    - a reasonable level for server side programs or libraries.
+        COMPILER  - if you need to compile, import or export Jtalk code.
+        CANVAS    - if you need HTML DOM manipulation, typical for client side.
+        JQUERY    - if you want JQuery stuff on top of Canvas.
+        IDE       - if you are extending the IDE with new tools etc.
 
-  -C
-     Add libraries to get minimal Jtalk Compiler running.
+  -l library1,library2
+     Additionally add listed libraries (no spaces or .js) in listed order.
 
-  -J
-     Add libraries to get minimal Jtalk IDE running.
+  -i file
+     Add library initializer <file> instead of default $JTALK/js/init.js 
 
+  -m class
+     Add at end a call to #main in class <class>. 
+
+  -M file
+     Add at end javascript file <file> acting as main.
+        
   -o
      Optimize each js file using the Google closure compiler.
-     Using Closure at ~/compiler.jar    
+     Using Closure compiler found at ~/compiler.jar    
 
   -O
      Optimize final <Program>.js using the Google closure compiler.
-     Using Closure at ~/compiler.jar
+     Using Closure compiler found at ~/compiler.jar
 
-  -A Same as -O but use --compilation_level ADVANCED_OPTIMIZATIONS 
+  -A Same as -O but use --compilation_level ADVANCED_OPTIMIZATIONS
 
   -d
      Additionally export code for deploy - stripped from source etc.
@@ -70,26 +78,8 @@ Usage: $0 [-N|D|E] [-K|C|J] [-o] [-O|-A] [-d] [-s suffix] [-m class] [-M file]
      File.<suffix>.js.
 
   -S suffix
-     Use <suffix> for all libraries accessed using -l or -L and other options.
-
-  -l library1,library2
-     Load listed libraries (no spaces or .js) into Compiler before compiling.
-
-  -L library1,library2
-     Load listed libraries (no spaces or .js) into Compiler before compiling
-     and also into Program.js in listed order.
-
-  -i file
-     Add library initializer <file>.
-
-  -I
-     Add library standard initializer $JTALK/js/init.js  
-
-  -m class
-     Add call to #main in class <class>. 
-
-  -M file
-     Add javascript file <file> at the end acting as main.
+     Use <suffix> for all libraries accessed using -L or -l. This makes it possible
+     to have multiple flavors of Jtalk and libraries in the same place.
 
 
      Example invocations:
@@ -99,16 +89,15 @@ Usage: $0 [-N|D|E] [-K|C|J] [-o] [-O|-A] [-d] [-s suffix] [-m class] [-M file]
         jtalkc Kernel.st
 
      Compile Hello.st to Hello.js and create complete program called
-     Program.js for Node.js and adding a call to class method #main
-     in class Hello:
+     Program.js and adding a call to class method #main in class Hello:
 
-        jtalkc -N -m Hello Hello.st Program
+        jtalkc -m Hello Hello.st Program
 
      Compile two .st files into corresponding .js files,
      and link with specific myboot.js, myKernel.js, myinit.js
      and main.js and create complete program called Program.js:
 
-        jtalkc -M main.js -I myinit.js myboot.js myKernel.js Cat1.st Cat2.st Program
+        jtalkc -M main.js myinit.js myboot.js myKernel.js Cat1.st Cat2.st Program
 
 ENDOFHELP
 	exit 1;
@@ -122,9 +111,10 @@ fi
 # Define our predefined library combinations
 BOOT="boot"
 KERNEL="$BOOT Kernel"
-COMPILER="$KERNEL Parser parser Compiler"
-CANVAS="$COMPILER Canvas"
-IDE="$CANVAS JQuery IDE SUnit Examples"
+COMPILER="$KERNEL parser Compiler"
+CANVAS="$KERNEL Canvas"
+JQUERY="$CANVAS JQuery"
+IDE="$JQUERY IDE SUnit Examples"
 
 # Predefined initializer
 INITIALIZER="$JTALK/js/init.js"
@@ -136,7 +126,6 @@ MAIN=
 MAINFILE=
 BASE=$KERNEL
 LOAD=
-LOADANDADD=
 CLOSUREOPTS=
 # Ok, bad coding practice but hey, who would use such a suffix?
 SUFFIX=no-silly-suffix
@@ -145,20 +134,13 @@ DEPLOY=false
 NODECOMPILE=nodecompile
 
 # Read options and shift them away
-while getopts "NDEKCJoOAdS:s:l:L:i:IM:m:h?" o; do
+while getopts "L:l:i:m:M:oOAds:S:h?" o; do
 case "$o" in
-   N) ENV=NODE
-      BASE=$KERNEL
-      INIT=$INITIALIZER;;
-   D) ENV=D8
-      BASE=$KERNEL
-      INIT=$INITIALIZER;;
-   E) ENV=ENYO
-      BASE=$KERNEL
-      INIT=$INITIALIZER;;
-   K) BASE=$KERNEL;;
-   C) BASE=$COMPILER;;
-   J) BASE=$IDE;;
+   L) BASE=${!OPTARG};;  # If OPTARG is "KERNEL" this sets BASE to $KERNEL.
+   l) LOAD=$OPTARG;;
+   i) INIT=$OPTARG;;
+   m) MAIN=$OPTARG;;
+   M) MAINFILE=$OPTARG;;
    o) CLOSURE=true
       CLOSUREPARTS=true;;
    O) CLOSURE=true
@@ -167,16 +149,10 @@ case "$o" in
       CLOSUREOPTS="$CLOSUREOPTS --compilation_level ADVANCED_OPTIMIZATIONS"
       CLOSUREFULL=true;;
    d) DEPLOY=true;;
-   S) LOADSUFFIX=$OPTARG
-      SUFFIXUSED=$SUFFIX;;
    s) SUFFIX=$OPTARG
       SUFFIXUSED=$SUFFIX;;
-   l) LOAD=$OPTARG;;
-   L) LOADANDADD=$OPTARG;;
-   I) INIT=$INITIALIZER;;
-   i) INIT=$OPTARG;;
-   M) MAINFILE=$OPTARG;;
-   m) MAIN=$OPTARG;;
+   S) LOADSUFFIX=$OPTARG
+      SUFFIXUSED=$SUFFIX;;
    h) usage;;
    [?])  usage;;
    esac
@@ -227,33 +203,32 @@ do
    TOLOAD="$TOLOAD $RESOLVED"
 done
 
-# Resolve listed libraries in $LOADANDADD separated by ,
-LOADANDADD=${LOADANDADD//,/\ }
-for FILE in $LOADANDADD
-do
-   resolvejs $FILE
-   TOLOAD="$TOLOAD $RESOLVED"
-   TOADD="$TOADD $RESOLVED"
-done
-
 # Resolve COMPILER
 for FILE in $COMPILER
 do
    resolvejs $FILE
-   TOOURCOMPILER="$TOOURCOMPILER $RESOLVED"
+   TOCOMPILER="$TOCOMPILER $RESOLVED"
 done
-# Add supplied libraries to load (they are already resolved)
-TOOURCOMPILER="$TOOURCOMPILER$TOLOAD"
-THEREST="init $JTALK/bin/$NODECOMPILE"
+
+# Add supplied libraries we have not already loaded (they are already resolved)
+#for FILE in $EXTRA
+#do
+#   resolvejs $FILE
+#   TOEXTRA="$TOEXTRA $RESOLVED"
+#done
+
+TOCOMPILER="$TOCOMPILER$TOLOAD"
+
 # Resolve init and nodecompile
+THEREST="init $JTALK/bin/$NODECOMPILE"
 for FILE in $THEREST
 do
    resolvejs $FILE
-   TOOURCOMPILER="$TOOURCOMPILER $RESOLVED"
+   TOCOMPILER="$TOCOMPILER $RESOLVED"
 done
 
 # Add supplied libraries
-LIBS="$TOBASE $TOADD"
+LIBS="$TOBASE $TOLOAD"
 
 # Get a unique tempdir and make it get auto removed on exit
 TMPDIR=`mktemp -d jtalkc.XXXXXX`
@@ -301,12 +276,11 @@ done
 # --------------------------------------------------
 
 # Create compiler dynamically
-cat $TOOURCOMPILER > $TMPDIR/compiler.js
+cat $TOCOMPILER > $TMPDIR/compiler.js
  
 # Compile all collected .st files to .js
-echo "Loading libraries$TOOURCOMPILER and compiling ..."
+echo "Loading libraries$TOCOMPILER and compiling ..."
 node $TMPDIR/compiler.js $DEPLOY $SUFFIX $COMPILE
-echo node $TMPDIR/compiler.js $DEPLOY $SUFFIX $COMPILE
 
 # Verify all .js files corresponding to .st files were created, otherwise exit
 IFS=" "

+ 1 - 1
examples/nodejs/benchfib/Makefile

@@ -1,5 +1,5 @@
 Program.js: Benchfib.st
-	../../../bin/jtalkc -N -m Benchfib Benchfib.st Program
+	../../../bin/jtalkc -m Benchfib Benchfib.st Program
 
 run: Program.js
 	./benchfib

+ 1 - 1
examples/nodejs/hello/Makefile

@@ -1,5 +1,5 @@
 Program.js: Hello.st
-	../../../bin/jtalkc -N -m Hello Hello.st Program
+	../../../bin/jtalkc -m Hello Hello.st Program
 
 run: Program.js
 	./hello

+ 1 - 1
examples/nodejs/meta/Makefile

@@ -1,5 +1,5 @@
 Program.js: MyScript.st
-	../../../bin/jtalkc -N -C -m MyScript MyScript.st Program
+	../../../bin/jtalkc -L COMPILER -m MyScript MyScript.st Program
 
 run: Program.js
 	node Program.js

+ 6 - 6
examples/nodejs/meta/MyScript.st

@@ -4,18 +4,18 @@ Object subclass: #MyScript
 
 !MyScript class methodsFor: 'main'!
 main
-	| class compiler method |
+	| klass compiler method |
 	Object subclass: #Dummy instanceVariableNames: '' category: 'Dummy'.
-	class := smalltalk at: #Dummy.	
+	klass := smalltalk at: #Dummy.	
 	compiler := Compiler new.
 
-	method := compiler load: 'foo ^ 10' forClass: class.
+	method := compiler load: 'foo ^ 10' forClass: klass.
 	method category: 'foo'.
-	class addCompiledMethod: method.
+	klass addCompiledMethod: method.
 
-	method := compiler load: 'bar ^ self foo * 2' forClass: class.
+	method := compiler load: 'bar ^ self foo * 2' forClass: klass.
 	method category: 'foo'.
-	class addCompiledMethod: method.
+	klass addCompiledMethod: method.
 
 	console log: (Exporter new exportCategory: 'Dummy')
 ! !

+ 1 - 0
examples/nodejs/meta/meta

@@ -0,0 +1 @@
+node Program.js $@

+ 8 - 0
examples/nodejs/pystone/Makefile

@@ -0,0 +1,8 @@
+Program.js: Pystone.st
+	../../../bin/jtalkc -m Pystone Pystone.st Program
+
+run: Program.js
+	./pystone
+
+clean:
+	rm -f *.js

+ 306 - 0
examples/nodejs/pystone/Pystone.st

@@ -0,0 +1,306 @@
+Object subclass: #PyStoneRecord
+	instanceVariableNames: 'ptrComp discr enumComp intComp stringComp'
+	category: 'Pystone'!
+!PyStoneRecord commentStamp!
+Record class used in Pystone benchmark.!
+
+!PyStoneRecord methodsFor: 'accessing'!
+
+discr
+	^discr
+!
+
+discr: p
+	discr := p
+!
+
+enumComp
+	^enumComp
+!
+
+enumComp: p
+	enumComp := p
+!
+
+intComp
+	^intComp
+!
+
+intComp: p
+	intComp := p
+!
+
+ptrComp
+	^ptrComp
+!
+
+ptrComp: p
+	ptrComp := p
+!
+
+stringComp
+	^stringComp
+!
+
+stringComp: p
+	stringComp := p
+! !
+
+!PyStoneRecord methodsFor: 'copying'!
+
+copy
+	^PyStoneRecord ptrComp: ptrComp discr: discr enumComp: enumComp intComp: intComp stringComp: stringComp
+! !
+
+!PyStoneRecord methodsFor: 'initialize-release'!
+
+ptrComp: p discr: d enumComp: e intComp: i stringComp: s
+
+	ptrComp := p.
+	discr := d.
+	enumComp := e.
+	intComp := i.
+	stringComp := s
+! !
+
+!PyStoneRecord class methodsFor: 'instance-creation'!
+
+new
+
+	^self ptrComp: nil discr: 0 enumComp: 0 intComp: 0 stringComp: 0
+!
+
+ptrComp: p discr: d enumComp: e intComp: i stringComp: s
+
+	^super new ptrComp: p discr: d enumComp: e intComp: i stringComp: s
+! !
+
+Object subclass: #Pystone
+	instanceVariableNames: 'nulltime ptrGlbNext ptrGlb ident1 ident3 ident2 ident4 ident5 ident6 intGlob boolGlob char1Glob char2Glob array1Glob array2Glob func3 func2 func1'
+	category: 'Pystone'!
+!Pystone commentStamp!
+This is a straight translation of pystone 1.1 from Python to Squeak. Procedures have been mapped to instance side methods, functions have been mapped to blocks. Open a transcript and run:
+
+Pystone run!
+
+!Pystone methodsFor: 'as yet unclassified'!
+
+defineFunctions
+	"Functions have been mapped to blocks, since that
+	would be natural."
+	
+	func1 := [:charPar1 :charPar2 |
+		| charLoc1 charLoc2 |
+		charLoc1 := charPar1.
+		charLoc2 := charLoc1.
+		(charLoc2 = charPar2) ifTrue: [ident2] ifFalse: [ident1]].
+
+	func2 := [:strParI1 :strParI2 |
+		| intLoc charLoc |
+		intLoc := 1.
+		[intLoc <= 1] whileTrue: [
+			((func1 value: (strParI1 at: intLoc) value: (strParI1 at: intLoc + 1)) = ident1)
+				ifTrue: [
+					charLoc := 'A'.
+					intLoc := intLoc + 1]].
+		(charLoc >= 'W' and: [charLoc <= 'Z']) ifTrue: [
+			intLoc := 7].
+		(charLoc = 'X') ifTrue: [true] ifFalse: [
+			(strParI1 > strParI2) ifTrue: [
+				intLoc := intLoc + 7.
+				true]
+			ifFalse: [
+				false]]].
+	
+	func3 := [:enumParIn |
+		| enumLoc |
+		enumLoc := enumParIn.
+		enumLoc = ident3]
+!
+
+main: loops
+	"Adaption of pystone.py version 1.9 from Python."
+
+	ident1 := 1. ident2 := 2. ident3 := 3. ident4 := 4. ident5 := 5. ident6 := 6.
+	intGlob := 0.
+	boolGlob := false.
+	char1Glob := String value: 0.
+	char2Glob := String value: 0.
+	array1Glob := Array new.
+        51 timesRepeat: [ array1Glob add: 0].
+	array2Glob := ((1 to: 51) collect: [:i | array1Glob copy]) asArray.
+
+	self defineFunctions.
+
+	self pystones: loops block: [:benchtime :stones |
+		self log: 'Pystone(1.1) time for ', loops asString, ' passes = ', benchtime asString.
+		self log: 'This machine benchmarks at ',
+			((stones / 0.1) rounded * 0.1) asString, ' pystones/second']
+!
+
+log: aString
+	(smalltalk at: #Transcript)
+		ifNotNil: [
+			Transcript show: aString;cr]
+		ifNil: [
+			console log: aString]
+!		
+
+proc0: loops block: aBlock
+	| string1Loc starttime intLoc1 intLoc2 string2Loc enumLoc intLoc3 charIndex benchtime |
+
+	loops timesRepeat: [].
+
+	benchtime := Date millisecondsToRun: [
+	ptrGlbNext := PyStoneRecord new.
+	ptrGlb := PyStoneRecord new.
+	ptrGlb ptrComp: ptrGlbNext.
+	ptrGlb discr: ident1.
+	ptrGlb enumComp: ident3.
+	ptrGlb intComp: 40.
+	ptrGlb stringComp: 'DHRYSTONE PROGRAM, SOME STRING'.
+	string1Loc := 'DHRYSTONE PROGRAM, 1''ST STRING'.
+	
+	(array2Glob at: 8) at: 7 put: 10.
+	"1 to: loops - 1 do: [:i |       Changed this to use timesRepeat: since i is not used at all in the loop"
+	loops timesRepeat: [
+		self proc5; proc4.
+		intLoc1 := 2.
+		intLoc2 := 3.
+		string2Loc := 'DHRYSTONE PROGRAM, 2''ND STRING'.
+		enumLoc := ident2.
+		boolGlob := (func2 value: string1Loc value: string2Loc) not.
+		[intLoc1 < intLoc2] whileTrue: [
+			intLoc3 := 5 * intLoc1 - intLoc2.
+			intLoc3 := self proc7: intLoc1 with: intLoc2.
+			intLoc1 := intLoc1 + 1].
+	 	self proc8:array1Glob with: array2Glob with: intLoc1 with: intLoc3.
+		ptrGlb := self proc1: ptrGlb.
+		charIndex := 'A'.
+		[charIndex <= char2Glob] whileTrue: [
+			(enumLoc = (func1 value: charIndex value: 'C'))
+					ifTrue: [enumLoc := self proc6: ident1].
+			charIndex := String value: (charIndex asciiValue + 1)].
+		intLoc3 := intLoc2 * intLoc1.
+		intLoc2 := intLoc3 / intLoc1.
+		intLoc2 := 7 * (intLoc3 - intLoc2) - intLoc1.
+		intLoc1 := self proc2: intLoc1]].
+    ^ aBlock value: (benchtime / 1000) value: (loops / benchtime) * 1000
+!
+
+proc1: ptrParIn
+	| nextRecord tmp |
+	tmp := ptrParIn.
+	nextRecord := ptrGlb copy.
+	ptrParIn ptrComp: nextRecord.
+	ptrParIn intComp: 5.
+	nextRecord intComp: ptrParIn intComp.
+	nextRecord ptrComp: ptrParIn ptrComp.
+	nextRecord ptrComp: (self proc3: nextRecord ptrComp).
+	(nextRecord discr = ident1) ifTrue: [
+		nextRecord intComp: 6.
+		nextRecord enumComp: (self proc6: ptrParIn enumComp).
+		nextRecord ptrComp: ptrGlb ptrComp.
+		nextRecord intComp: (self proc7: nextRecord intComp with: 10) ]
+	ifFalse: [
+		tmp := nextRecord copy].
+	nextRecord ptrComp: nil.
+	^tmp
+!
+
+proc2: intParIO
+	| tmp intLoc enumLoc |
+	tmp := intParIO.
+	intLoc := intParIO + 10.
+	[true] whileTrue: [
+		(char1Glob = 'A') ifTrue: [
+			intLoc := intLoc - 1.
+			tmp := intLoc - intGlob.
+			enumLoc := ident1].
+		(enumLoc = ident1) ifTrue: [
+			^ tmp]]
+!
+
+proc3: ptrParOut
+	| tmp |
+	tmp := ptrParOut.
+	ptrGlb ifNotNil: [
+		tmp := ptrGlb ptrComp]
+	ifNil: [
+		intGlob := 100].
+	ptrGlb intComp: (self proc7: 10 with: intGlob).
+	^tmp
+!
+
+proc4
+	| boolLoc |
+	boolLoc := char1Glob = 'A'.
+	boolLoc := boolLoc | boolGlob.
+	char2Glob := 'B'
+!
+
+proc5
+	char1Glob := 'A'.
+	boolGlob := false
+!
+
+proc6: enumParIn
+	| enumParOut |
+	enumParOut := enumParIn.
+	(func3 value: enumParIn) ifFalse: [
+		enumParOut := ident4].
+	(enumParIn = ident1) ifTrue: [
+		enumParOut := ident1] ifFalse: [
+	(enumParIn = ident2) ifTrue: [
+			intGlob > 100 ifTrue: [
+				enumParOut := ident1]
+			ifFalse: [
+				enumParOut := ident4]] ifFalse: [
+	(enumParIn = ident3) ifTrue: [
+		enumParOut := ident2] ifFalse: [
+	(enumParIn = ident4) ifTrue: [] ifFalse: [
+	(enumParIn = ident5) ifTrue: [
+		enumParOut := ident3]]]]].
+	^enumParOut
+!
+
+proc7: intParI1 with: intParI2
+	| intLoc intParOut |
+	intLoc := intParI1 + 2.
+	intParOut := intParI2 + intLoc.
+	^ intParOut
+!
+
+proc8: array1Par with: array2Par with: intParI1 with: intParI2
+	| intLoc |
+	intLoc := intParI1 + 5.
+	array1Par at: intLoc put: intParI2.
+	array1Par at: intLoc + 1 put: (array1Par at: intLoc).
+	array1Par at: intLoc + 30 put: intLoc.
+	intLoc to: intLoc + 1 do: [:intIndex |
+		(array2Par at: intLoc) at: intIndex put: intLoc.
+		(array2Par at: intLoc) at: intLoc - 1 put: ((array2Par at: intLoc) at: intLoc - 1) + 1.
+		(array2Par at: intLoc + 20) at: intLoc put: (array1Par at: intLoc)].
+	intGlob := 5
+!
+
+pystones: loops block: aBlock
+	^self proc0: loops block: aBlock
+! !
+
+Pystone class instanceVariableNames: 'nulltime'!
+
+!Pystone class methodsFor: 'as yet unclassified'!
+
+main
+	"self main"
+	
+	self run: 50000
+!
+
+run: loops
+	"self run: 50000"
+	
+	self new main: loops
+! !
+

+ 1 - 0
examples/nodejs/pystone/pystone

@@ -0,0 +1 @@
+node Program.js $@

+ 1 - 1
examples/nodejs/trivialserver/Makefile

@@ -1,5 +1,5 @@
 Program.js: TrivialServer.st
-	../../../bin/jtalkc -N -m TrivialServer TrivialServer.st Program
+	../../../bin/jtalkc -m TrivialServer TrivialServer.st Program
 
 run: Program.js
 	./trivial

+ 2 - 3
examples/webos/eris/Makefile

@@ -1,14 +1,13 @@
 #
 # If you copy this file for an Enyo/Jtalk project, just
-# modify these first two lines
+# modify these first three lines
 # and then add .st files as you please. This Makefile
 # should pick them all up and compile into Program.js.
 #
 PACKAGE  := jtalk.eris
 VERSION  := 0.0.1
+FLAGS    := -L COMPILER
 
-# -E for Enyo, -O for Closure optimization of js code.
-FLAGS    := -E -C
 IPK      := $(PACKAGE)_$(VERSION)_all.ipk
 FILE     := Program
 SOURCES  := $(wildcard *.st)

+ 2 - 2
examples/webos/hellojtalk/Makefile

@@ -7,8 +7,8 @@
 PACKAGE  := jtalk.hellojtalk
 VERSION  := 1.0.0
 
-# -E for Enyo, -O for Closure optimization of js code.
-FLAGS    := -E -O
+# -O for Closure optimization of js code.
+FLAGS    := -O
 IPK      := $(PACKAGE)_$(VERSION)_all.ipk
 FILE     := Program
 SOURCES  := $(wildcard *.st)

+ 328 - 17
js/Compiler.deploy.js

@@ -1,3 +1,298 @@
+smalltalk.addClass('ChunkParser', smalltalk.Object, ['stream'], 'Compiler');
+smalltalk.addMethod(
+'_stream_',
+smalltalk.method({
+selector: 'stream:',
+fn: function (aStream){
+var self=this;
+self['@stream']=aStream;
+return self;}
+}),
+smalltalk.ChunkParser);
+
+smalltalk.addMethod(
+'_nextChunk',
+smalltalk.method({
+selector: 'nextChunk',
+fn: function (){
+var self=this;
+try{var char=nil;
+var result=nil;
+var chunk=nil;
+result=smalltalk.send("", "_writeStream", []);
+(function(){while((function(){char=smalltalk.send(self['@stream'], "_next", []);return smalltalk.send(char, "_notNil", []);})()) {(function(){(($receiver = smalltalk.send(char, "__eq", [unescape("%21")])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (($receiver = smalltalk.send(smalltalk.send(self['@stream'], "_peek", []), "__eq", [unescape("%21")])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self['@stream'], "_next", []);})() : (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(self['@stream'], "_next", []);}), (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (($receiver = smalltalk.send(smalltalk.send(self['@stream'], "_peek", []), "__eq", [unescape("%21")])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self['@stream'], "_next", []);})() : (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(self['@stream'], "_next", []);}), (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})]);})]);return smalltalk.send(result, "_nextPut_", [char]);})()}})();
+(function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return nil}})})();
+return self;
+} catch(e) {if(e.name === 'stReturn' && e.selector === '_nextChunk'){return e.fn()} throw(e)}}
+}),
+smalltalk.ChunkParser);
+
+
+smalltalk.addMethod(
+'_on_',
+smalltalk.method({
+selector: 'on:',
+fn: function (aStream){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_new", []), "_stream_", [aStream]);
+return self;}
+}),
+smalltalk.ChunkParser.klass);
+
+
+smalltalk.addClass('Importer', smalltalk.Object, [], 'Compiler');
+smalltalk.addMethod(
+'_import_',
+smalltalk.method({
+selector: 'import:',
+fn: function (aStream){
+var self=this;
+var chunk=nil;
+var result=nil;
+var parser=nil;
+var lastEmpty=nil;
+parser=smalltalk.send((smalltalk.ChunkParser || ChunkParser), "_on_", [aStream]);
+lastEmpty=false;
+(function(){while(!(function(){chunk=smalltalk.send(parser, "_nextChunk", []);return smalltalk.send(chunk, "_isNil", []);})()) {(function(){return (($receiver = smalltalk.send(chunk, "_isEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return lastEmpty=true;})() : (function(){result=smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_loadExpression_", [chunk]);return (($receiver = lastEmpty).klass === smalltalk.Boolean) ? ($receiver ? (function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return lastEmpty=true;}), (function(){result=smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_loadExpression_", [chunk]);return (($receiver = lastEmpty).klass === smalltalk.Boolean) ? ($receiver ? (function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})]);})]);})()}})();
+return self;}
+}),
+smalltalk.Importer);
+
+
+
+smalltalk.addClass('Exporter', smalltalk.Object, [], 'Compiler');
+smalltalk.addMethod(
+'_exportCategory_',
+smalltalk.method({
+selector: 'exportCategory:',
+fn: function (aString){
+var self=this;
+var stream=nil;
+stream=smalltalk.send("", "_writeStream", []);
+smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_select_", [(function(each){return smalltalk.send(smalltalk.send(each, "_category", []), "__eq", [aString]);})]), "_do_", [(function(each){return smalltalk.send(stream, "_nextPutAll_", [smalltalk.send(self, "_export_", [each])]);})]);
+smalltalk.send(self, "_exportCategoryExtensions_on_", [aString, stream]);
+return smalltalk.send(stream, "_contents", []);
+return self;}
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_export_',
+smalltalk.method({
+selector: 'export:',
+fn: function (aClass){
+var self=this;
+var stream=nil;
+stream=smalltalk.send("", "_writeStream", []);
+smalltalk.send(self, "_exportDefinitionOf_on_", [aClass, stream]);
+smalltalk.send(self, "_exportMethodsOf_on_", [aClass, stream]);
+smalltalk.send(self, "_exportMetaDefinitionOf_on_", [aClass, stream]);
+smalltalk.send(self, "_exportMethodsOf_on_", [smalltalk.send(aClass, "_class", []), stream]);
+return smalltalk.send(stream, "_contents", []);
+return self;}
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportDefinitionOf:on:',
+fn: function (aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addClass%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%27%2C%20")])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%2C%20%5B")]);})(aStream);
+smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C%20")]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D%2C%20%27")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(aClass, "_category", []), "__comma", [unescape("%27")])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);})(aStream);
+(($receiver = smalltalk.send(smalltalk.send(aClass, "_comment", []), "_notEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", ["smalltalk."]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [aClass])]);smalltalk.send($rec, "_nextPutAll_", [unescape(".comment%3D")]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aClass, "_comment", []), "_escaped", [])]), "__comma", [unescape("%27%29")])]);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", ["smalltalk."]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [aClass])]);smalltalk.send($rec, "_nextPutAll_", [unescape(".comment%3D")]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aClass, "_comment", []), "_escaped", [])]), "__comma", [unescape("%27%29")])]);})(aStream);})]);
+smalltalk.send(aStream, "_lf", []);
+return self;}
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportMetaDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportMetaDefinitionOf:on:',
+fn: function (aClass, aStream){
+var self=this;
+(($receiver = smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape(".iVarNames%20%3D%20%5B")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(unescape("%5D%3B"), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])])]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape(".iVarNames%20%3D%20%5B")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(unescape("%5D%3B"), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])])]);})]);
+return self;}
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportMethodsOf_on_',
+smalltalk.method({
+selector: 'exportMethodsOf:on:',
+fn: function (aClass, aStream){
+var self=this;
+smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_methodDictionary", []), "_values", []), "_do_", [(function(each){return (($receiver = smalltalk.send(smalltalk.send(each, "_category", []), "_match_", [unescape("%5E%5C*")])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);})]);
+smalltalk.send(aStream, "_lf", []);
+return self;}
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_classNameFor_',
+smalltalk.method({
+selector: 'classNameFor:',
+fn: function (aClass){
+var self=this;
+return (($receiver = smalltalk.send(aClass, "_isMetaclass", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [".klass"]);})() : (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [".klass"]);}), (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})]);
+return self;}
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportMethod_of_on_',
+smalltalk.method({
+selector: 'exportMethod:of:on:',
+fn: function (aMethod, aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addMethod%28")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_selector", []), "_asSelector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.method%28%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("selector%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_selector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("category%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_category", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send("fn: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_fn", []), "_compiledSource", [])]), "__comma", [unescape("%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("source%3A%20unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_source", []), "_escaped", [])]), "__comma", [unescape("%27%29%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send("messageSends: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_messageSends", []), "_asJavascript", [])]), "__comma", [unescape("%2C")])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("referencedClasses%3A%20%5B")]);})(aStream);
+smalltalk.send(smalltalk.send(aMethod, "_referencedClasses", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [each])])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("%7D%29%2C")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+return self;}
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportCategoryExtensions_on_',
+smalltalk.method({
+selector: 'exportCategoryExtensions:on:',
+fn: function (aString, aStream){
+var self=this;
+smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_collect_", [(function(each){return smalltalk.send(each, "_class", []);})])]), "_do_", [(function(each){return smalltalk.send(smalltalk.send(smalltalk.send(each, "_methodDictionary", []), "_values", []), "_do_", [(function(method){return (($receiver = smalltalk.send(smalltalk.send(method, "_category", []), "__eq", [smalltalk.send(unescape("*"), "__comma", [aString])])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self, "_exportMethod_of_on_", [method, each, aStream]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(self, "_exportMethod_of_on_", [method, each, aStream]);})]);})]);})]);
+return self;}
+}),
+smalltalk.Exporter);
+
+
+
+smalltalk.addClass('ChunkExporter', smalltalk.Exporter, [], 'Compiler');
+smalltalk.addMethod(
+'_exportDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportDefinitionOf:on:',
+fn: function (aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(unescape("%20subclass%3A%20%23"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("%09instanceVariableNames%3A%20%27")]);})(aStream);
+smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%09category%3A%20%27"), "__comma", [smalltalk.send(aClass, "_category", [])]), "__comma", [unescape("%27%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);
+(($receiver = smalltalk.send(smalltalk.send(aClass, "_comment", []), "_notEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%20commentStamp%21")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aClass, "_comment", [])]), "__comma", [unescape("%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%20commentStamp%21")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aClass, "_comment", [])]), "__comma", [unescape("%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);})]);
+smalltalk.send(aStream, "_lf", []);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMethod_of_on_',
+smalltalk.method({
+selector: 'exportMethod:of:on:',
+fn: function (aMethod, aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aMethod, "_source", [])])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("%21")]);})(aStream);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMethodsOf_on_',
+smalltalk.method({
+selector: 'exportMethodsOf:on:',
+fn: function (aClass, aStream){
+var self=this;
+smalltalk.send(aClass, "_protocolsDo_", [(function(category, methods){return (($receiver = smalltalk.send(category, "_match_", [unescape("%5E%5C*")])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, aClass, aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, aClass, aStream]);})]);})]);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMetaDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportMetaDefinitionOf:on:',
+fn: function (aClass, aStream){
+var self=this;
+(($receiver = smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%20instanceVariableNames%3A%20%27")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);return (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%20instanceVariableNames%3A%20%27")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);return (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);})]);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_classNameFor_',
+smalltalk.method({
+selector: 'classNameFor:',
+fn: function (aClass){
+var self=this;
+return (($receiver = smalltalk.send(aClass, "_isMetaclass", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [" class"]);})() : (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [" class"]);}), (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})]);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_chunkEscape_',
+smalltalk.method({
+selector: 'chunkEscape:',
+fn: function (aString){
+var self=this;
+return smalltalk.send(smalltalk.send(aString, "_replace_with_", [unescape("%21"), unescape("%21%21")]), "_trimBoth", []);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportCategoryExtensions_on_',
+smalltalk.method({
+selector: 'exportCategoryExtensions:on:',
+fn: function (aString, aStream){
+var self=this;
+smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_collect_", [(function(each){return smalltalk.send(each, "_class", []);})])]), "_do_", [(function(each){return smalltalk.send(each, "_protocolsDo_", [(function(category, methods){return (($receiver = smalltalk.send(category, "__eq", [smalltalk.send(unescape("*"), "__comma", [aString])])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, each, aStream]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, each, aStream]);})]);})]);})]);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMethods_category_of_on_',
+smalltalk.method({
+selector: 'exportMethods:category:of:on:',
+fn: function (methods, category, aClass, aStream){
+var self=this;
+(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(methods, "_do_", [(function(each){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%20%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+return self;}
+}),
+smalltalk.ChunkExporter);
+
+
+
+smalltalk.addClass('StrippedExporter', smalltalk.Exporter, [], 'Compiler');
+smalltalk.addMethod(
+'_exportDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportDefinitionOf:on:',
+fn: function (aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addClass%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%27%2C%20")])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%2C%20%5B")]);})(aStream);
+smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C%20")]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D%2C%20%27")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(aClass, "_category", []), "__comma", [unescape("%27")])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);})(aStream);
+smalltalk.send(aStream, "_lf", []);
+return self;}
+}),
+smalltalk.StrippedExporter);
+
+smalltalk.addMethod(
+'_exportMethod_of_on_',
+smalltalk.method({
+selector: 'exportMethod:of:on:',
+fn: function (aMethod, aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addMethod%28")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_selector", []), "_asSelector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.method%28%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("selector%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_selector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("fn: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_fn", []), "_compiledSource", [])])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("%7D%29%2C")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+return self;}
+}),
+smalltalk.StrippedExporter);
+
+
+
 smalltalk.addClass('Node', smalltalk.Object, ['nodes'], 'Compiler');
 smalltalk.addMethod(
 '_nodes',
@@ -802,7 +1097,7 @@ smalltalk.NodeVisitor);
 
 
 
-smalltalk.addClass('Compiler', smalltalk.NodeVisitor, ['stream', 'nestedBlocks', 'earlyReturn', 'currentClass', 'currentSelector', 'unknownVariables', 'tempVariables', 'messageSends', 'referencedClasses', 'classReferenced'], 'Compiler');
+smalltalk.addClass('Compiler', smalltalk.NodeVisitor, ['stream', 'nestedBlocks', 'earlyReturn', 'currentClass', 'currentSelector', 'unknownVariables', 'tempVariables', 'messageSends', 'referencedClasses', 'classReferenced', 'source'], 'Compiler');
 smalltalk.addMethod(
 '_initialize',
 smalltalk.method({
@@ -858,8 +1153,11 @@ smalltalk.method({
 selector: 'loadExpression:',
 fn: function (aString){
 var self=this;
+var result=nil;
 smalltalk.send((smalltalk.DoIt || DoIt), "_addCompiledMethod_", [smalltalk.send(self, "_eval_", [smalltalk.send(self, "_compileExpression_", [aString])])]);
-return smalltalk.send(smalltalk.send((smalltalk.DoIt || DoIt), "_new", []), "_doIt", []);
+result=smalltalk.send(smalltalk.send((smalltalk.DoIt || DoIt), "_new", []), "_doIt", []);
+smalltalk.send((smalltalk.DoIt || DoIt), "_removeCompiledMethod_", [smalltalk.send(smalltalk.send((smalltalk.DoIt || DoIt), "_methodDictionary", []), "_at_", ["doIt"])]);
+return result;
 return self;}
 }),
 smalltalk.Compiler);
@@ -885,6 +1183,7 @@ selector: 'compile:forClass:',
 fn: function (aString, aClass){
 var self=this;
 smalltalk.send(self, "_currentClass_", [aClass]);
+smalltalk.send(self, "_source_", [aString]);
 return smalltalk.send(self, "_compile_", [aString]);
 return self;}
 }),
@@ -897,7 +1196,8 @@ selector: 'compileExpression:',
 fn: function (aString){
 var self=this;
 smalltalk.send(self, "_currentClass_", [(smalltalk.DoIt || DoIt)]);
-return smalltalk.send(self, "_compileNode_", [smalltalk.send(self, "_parseExpression_", [aString])]);
+smalltalk.send(self, "_source_", [smalltalk.send(smalltalk.send(unescape("doIt%20%5E%5B"), "__comma", [aString]), "__comma", [unescape("%5D%20value")])]);
+return smalltalk.send(self, "_compileNode_", [smalltalk.send(self, "_parse_", [smalltalk.send(self, "_source", [])])]);
 return self;}
 }),
 smalltalk.Compiler);
@@ -964,7 +1264,7 @@ self['@referencedClasses']=[];
 self['@unknownVariables']=[];
 self['@tempVariables']=[];
 (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.method%28%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("selector%3A%20%22"), "__comma", [smalltalk.send(aNode, "_selector", [])]), "__comma", [unescape("%22%2C")])]);return smalltalk.send($rec, "_lf", []);})(self['@stream']);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("source%3A%20unescape%28%22"), "__comma", [smalltalk.send(smalltalk.send(aNode, "_source", []), "_escaped", [])]), "__comma", [unescape("%22%29%2C")])]);return smalltalk.send($rec, "_lf", []);})(self['@stream']);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("source%3A%20unescape%28%22"), "__comma", [smalltalk.send(smalltalk.send(self, "_source", []), "_escaped", [])]), "__comma", [unescape("%22%29%2C")])]);return smalltalk.send($rec, "_lf", []);})(self['@stream']);
 smalltalk.send(self['@stream'], "_nextPutAll_", [unescape("fn%3A%20function%28")]);
 smalltalk.send(smalltalk.send(aNode, "_arguments", []), "_do_separatedBy_", [(function(each){smalltalk.send(self['@tempVariables'], "_add_", [each]);return smalltalk.send(self['@stream'], "_nextPutAll_", [each]);}), (function(){return smalltalk.send(self['@stream'], "_nextPutAll_", [unescape("%2C%20")]);})]);
 (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%29%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("var%20self%3Dthis%3B")]);return smalltalk.send($rec, "_lf", []);})(self['@stream']);
@@ -1146,7 +1446,7 @@ smalltalk.method({
 selector: 'parse:',
 fn: function (aString){
 var self=this;
-return smalltalk.send(smalltalk.send(self, "_parser", []), "_parse_", [smalltalk.send(aString, "_readStream", [])]);
+return smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_parse_", [aString]);
 return self;}
 }),
 smalltalk.Compiler);
@@ -1225,7 +1525,7 @@ smalltalk.method({
 selector: 'recompileAll',
 fn: function (){
 var self=this;
-smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_do_", [(function(each){(function($rec){smalltalk.send($rec, "_show_", [each]);return smalltalk.send($rec, "_cr", []);})((smalltalk.Transcript || Transcript));return smalltalk.send((function(){return smalltalk.send(self, "_recompile_", [each]);}), "_valueWithTimeout_", [(100)]);})]);
+smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_do_", [(function(each){(function($rec){smalltalk.send($rec, "_show_", [each]);return smalltalk.send($rec, "_cr", []);})((smalltalk.Transcript || Transcript));return smalltalk.send((function(){return smalltalk.send(self, "_recompile_", [each]);}), "_valueWithTimeout_", [(1)]);})]);
 return self;}
 }),
 smalltalk.Compiler);
@@ -1363,6 +1663,28 @@ return self;}
 }),
 smalltalk.Compiler);
 
+smalltalk.addMethod(
+'_source',
+smalltalk.method({
+selector: 'source',
+fn: function (){
+var self=this;
+return (($receiver = self['@source']) == nil || $receiver == undefined) ? (function(){return "";})() : $receiver;
+return self;}
+}),
+smalltalk.Compiler);
+
+smalltalk.addMethod(
+'_source_',
+smalltalk.method({
+selector: 'source:',
+fn: function (aString){
+var self=this;
+self['@source']=aString;
+return self;}
+}),
+smalltalk.Compiler);
+
 
 smalltalk.Compiler.klass.iVarNames = ['performOptimizations'];
 smalltalk.addMethod(
@@ -1413,16 +1735,5 @@ smalltalk.Compiler.klass);
 
 
 smalltalk.addClass('DoIt', smalltalk.Object, [], 'Compiler');
-smalltalk.addMethod(
-'_doIt',
-smalltalk.method({
-selector: 'doIt',
-fn: function (){
-var self=this;
-return smalltalk.send((function(){return (($receiver = (typeof a == 'undefined' ? nil : a)).klass === smalltalk.Number) ? $receiver <(3) : smalltalk.send($receiver, "__lt", [(3)]);}), "_value", []);
-return self;}
-}),
-smalltalk.DoIt);
-
 
 

+ 388 - 20
js/Compiler.js

@@ -1,3 +1,386 @@
+smalltalk.addClass('ChunkParser', smalltalk.Object, ['stream'], 'Compiler');
+smalltalk.addMethod(
+'_stream_',
+smalltalk.method({
+selector: 'stream:',
+category: 'accessing',
+fn: function (aStream){
+var self=this;
+self['@stream']=aStream;
+return self;},
+source: unescape('stream%3A%20aStream%0A%09stream%20%3A%3D%20aStream'),
+messageSends: [],
+referencedClasses: []
+}),
+smalltalk.ChunkParser);
+
+smalltalk.addMethod(
+'_nextChunk',
+smalltalk.method({
+selector: 'nextChunk',
+category: 'reading',
+fn: function (){
+var self=this;
+try{var char=nil;
+var result=nil;
+var chunk=nil;
+result=smalltalk.send("", "_writeStream", []);
+(function(){while((function(){char=smalltalk.send(self['@stream'], "_next", []);return smalltalk.send(char, "_notNil", []);})()) {(function(){(($receiver = smalltalk.send(char, "__eq", [unescape("%21")])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (($receiver = smalltalk.send(smalltalk.send(self['@stream'], "_peek", []), "__eq", [unescape("%21")])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self['@stream'], "_next", []);})() : (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(self['@stream'], "_next", []);}), (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (($receiver = smalltalk.send(smalltalk.send(self['@stream'], "_peek", []), "__eq", [unescape("%21")])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self['@stream'], "_next", []);})() : (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(self['@stream'], "_next", []);}), (function(){return (function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return smalltalk.send(smalltalk.send(result, "_contents", []), "_trimBoth", [])}})})();})]);})]);return smalltalk.send(result, "_nextPut_", [char]);})()}})();
+(function(){throw({name: 'stReturn', selector: '_nextChunk', fn: function(){return nil}})})();
+return self;
+} catch(e) {if(e.name === 'stReturn' && e.selector === '_nextChunk'){return e.fn()} throw(e)}},
+source: unescape('nextChunk%0A%09%22The%20chunk%20format%20%28Smalltalk%20Interchange%20Format%20or%20Fileout%20format%29%0A%09is%20a%20trivial%20format%20but%20can%20be%20a%20bit%20tricky%20to%20understand%3A%0A%09%09-%20Uses%20the%20exclamation%20mark%20as%20delimiter%20of%20chunks.%0A%09%09-%20Inside%20a%20chunk%20a%20normal%20exclamation%20mark%20must%20be%20doubled.%0A%09%09-%20A%20non%20empty%20chunk%20must%20be%20a%20valid%20Smalltalk%20expression.%0A%09%09-%20A%20chunk%20on%20top%20level%20with%20a%20preceding%20empty%20chunk%20is%20an%20instruction%20chunk%3A%0A%09%09%09-%20The%20object%20created%20by%20the%20expression%20then%20takes%20over%20reading%20chunks.%0A%0A%09This%20metod%20returns%20next%20chunk%20as%20a%20String%20%28trimmed%29%2C%20empty%20String%20%28all%20whitespace%29%20or%20nil.%22%0A%0A%09%7C%20char%20result%20chunk%20%7C%0A%09result%20%3A%3D%20%27%27%20writeStream.%0A%20%20%20%20%20%20%20%20%5Bchar%20%3A%3D%20stream%20next.%0A%20%20%20%20%20%20%20%20char%20notNil%5D%20whileTrue%3A%20%5B%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20char%20%3D%20%27%21%27%20ifTrue%3A%20%5B%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20stream%20peek%20%3D%20%27%21%27%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20ifTrue%3A%20%5Bstream%20next%20%22skipping%20the%20escape%20double%22%5D%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20ifFalse%3A%20%5B%5Eresult%20contents%20trimBoth%20%20%22chunk%20end%20marker%20found%22%5D%5D.%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20result%20nextPut%3A%20char%5D.%0A%09%5Enil%20%22a%20chunk%20needs%20to%20end%20with%20%21%22'),
+messageSends: ["writeStream", "whileTrue:", "next", "notNil", "ifTrue:", unescape("%3D"), "ifTrue:ifFalse:", "peek", "trimBoth", "contents", "nextPut:"],
+referencedClasses: []
+}),
+smalltalk.ChunkParser);
+
+
+smalltalk.addMethod(
+'_on_',
+smalltalk.method({
+selector: 'on:',
+category: 'not yet classified',
+fn: function (aStream){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_new", []), "_stream_", [aStream]);
+return self;},
+source: unescape('on%3A%20aStream%0A%09%5Eself%20new%20stream%3A%20aStream'),
+messageSends: ["stream:", "new"],
+referencedClasses: []
+}),
+smalltalk.ChunkParser.klass);
+
+
+smalltalk.addClass('Importer', smalltalk.Object, [], 'Compiler');
+smalltalk.addMethod(
+'_import_',
+smalltalk.method({
+selector: 'import:',
+category: 'fileIn',
+fn: function (aStream){
+var self=this;
+var chunk=nil;
+var result=nil;
+var parser=nil;
+var lastEmpty=nil;
+parser=smalltalk.send((smalltalk.ChunkParser || ChunkParser), "_on_", [aStream]);
+lastEmpty=false;
+(function(){while(!(function(){chunk=smalltalk.send(parser, "_nextChunk", []);return smalltalk.send(chunk, "_isNil", []);})()) {(function(){return (($receiver = smalltalk.send(chunk, "_isEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return lastEmpty=true;})() : (function(){result=smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_loadExpression_", [chunk]);return (($receiver = lastEmpty).klass === smalltalk.Boolean) ? ($receiver ? (function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return lastEmpty=true;}), (function(){result=smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_loadExpression_", [chunk]);return (($receiver = lastEmpty).klass === smalltalk.Boolean) ? ($receiver ? (function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){lastEmpty=false;return smalltalk.send(result, "_scanFrom_", [parser]);})]);})]);})()}})();
+return self;},
+source: unescape('import%3A%20aStream%0A%20%20%20%20%7C%20chunk%20result%20parser%20lastEmpty%20%7C%0A%20%20%20%20parser%20%3A%3D%20ChunkParser%20on%3A%20aStream.%0A%20%20%20%20lastEmpty%20%3A%3D%20false.%0A%20%20%20%20%5Bchunk%20%3A%3D%20parser%20nextChunk.%0A%20%20%20%20%20chunk%20isNil%5D%20whileFalse%3A%20%5B%0A%20%20%20%20%20%20%20%20chunk%20isEmpty%0A%20%20%20%20%20%20%20%09%09ifTrue%3A%20%5BlastEmpty%20%3A%3D%20true%5D%0A%20%20%20%20%20%20%20%09%09ifFalse%3A%20%5B%0A%20%20%20%20%20%20%20%20%09%09result%20%3A%3D%20Compiler%20new%20loadExpression%3A%20chunk.%0A%20%20%20%20%20%20%20%20%09%09lastEmpty%20%0A%20%20%20%20%20%20%20%20%20%20%20%20%09%09%09ifTrue%3A%20%5B%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%09lastEmpty%20%3A%3D%20false.%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%09result%20scanFrom%3A%20parser%5D%5D%5D'),
+messageSends: ["on:", "whileFalse:", "nextChunk", "isNil", "ifTrue:ifFalse:", "isEmpty", "loadExpression:", "new", "ifTrue:", "scanFrom:"],
+referencedClasses: [smalltalk.ChunkParser,smalltalk.nil]
+}),
+smalltalk.Importer);
+
+
+
+smalltalk.addClass('Exporter', smalltalk.Object, [], 'Compiler');
+smalltalk.addMethod(
+'_exportCategory_',
+smalltalk.method({
+selector: 'exportCategory:',
+category: 'fileOut',
+fn: function (aString){
+var self=this;
+var stream=nil;
+stream=smalltalk.send("", "_writeStream", []);
+smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_select_", [(function(each){return smalltalk.send(smalltalk.send(each, "_category", []), "__eq", [aString]);})]), "_do_", [(function(each){return smalltalk.send(stream, "_nextPutAll_", [smalltalk.send(self, "_export_", [each])]);})]);
+smalltalk.send(self, "_exportCategoryExtensions_on_", [aString, stream]);
+return smalltalk.send(stream, "_contents", []);
+return self;},
+source: unescape('exportCategory%3A%20aString%0A%09%7C%20stream%20%7C%0A%09stream%20%3A%3D%20%27%27%20writeStream.%0A%09%28Smalltalk%20current%20classes%20%0A%09%20%20%20%20select%3A%20%5B%3Aeach%20%7C%20each%20category%20%3D%20aString%5D%29%0A%09%20%20%20%20do%3A%20%5B%3Aeach%20%7C%20stream%20nextPutAll%3A%20%28self%20export%3A%20each%29%5D.%0A%09self%20exportCategoryExtensions%3A%20aString%20on%3A%20stream.%0A%09%5Estream%20contents'),
+messageSends: ["writeStream", "do:", "select:", "classes", "current", unescape("%3D"), "category", "nextPutAll:", "export:", "exportCategoryExtensions:on:", "contents"],
+referencedClasses: [smalltalk.Smalltalk]
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_export_',
+smalltalk.method({
+selector: 'export:',
+category: 'fileOut',
+fn: function (aClass){
+var self=this;
+var stream=nil;
+stream=smalltalk.send("", "_writeStream", []);
+smalltalk.send(self, "_exportDefinitionOf_on_", [aClass, stream]);
+smalltalk.send(self, "_exportMethodsOf_on_", [aClass, stream]);
+smalltalk.send(self, "_exportMetaDefinitionOf_on_", [aClass, stream]);
+smalltalk.send(self, "_exportMethodsOf_on_", [smalltalk.send(aClass, "_class", []), stream]);
+return smalltalk.send(stream, "_contents", []);
+return self;},
+source: unescape('export%3A%20aClass%0A%09%7C%20stream%20%7C%0A%09stream%20%3A%3D%20%27%27%20writeStream.%0A%09self%20exportDefinitionOf%3A%20aClass%20on%3A%20stream.%0A%09self%20exportMethodsOf%3A%20aClass%20on%3A%20stream.%0A%09self%20exportMetaDefinitionOf%3A%20aClass%20on%3A%20stream.%0A%09self%20exportMethodsOf%3A%20aClass%20class%20on%3A%20stream.%0A%09%5Estream%20contents'),
+messageSends: ["writeStream", "exportDefinitionOf:on:", "exportMethodsOf:on:", "exportMetaDefinitionOf:on:", "class", "contents"],
+referencedClasses: []
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportDefinitionOf:on:',
+category: 'private',
+fn: function (aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addClass%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%27%2C%20")])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%2C%20%5B")]);})(aStream);
+smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C%20")]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D%2C%20%27")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(aClass, "_category", []), "__comma", [unescape("%27")])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);})(aStream);
+(($receiver = smalltalk.send(smalltalk.send(aClass, "_comment", []), "_notEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", ["smalltalk."]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [aClass])]);smalltalk.send($rec, "_nextPutAll_", [unescape(".comment%3D")]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aClass, "_comment", []), "_escaped", [])]), "__comma", [unescape("%27%29")])]);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", ["smalltalk."]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [aClass])]);smalltalk.send($rec, "_nextPutAll_", [unescape(".comment%3D")]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aClass, "_comment", []), "_escaped", [])]), "__comma", [unescape("%27%29")])]);})(aStream);})]);
+smalltalk.send(aStream, "_lf", []);
+return self;},
+source: unescape('exportDefinitionOf%3A%20aClass%20on%3A%20aStream%0A%09aStream%20%0A%09%20%20%20%20nextPutAll%3A%20%27smalltalk.addClass%28%27%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%27%27%27%2C%20%28self%20classNameFor%3A%20aClass%29%2C%20%27%27%27%2C%20%27%3B%0A%09%20%20%20%20nextPutAll%3A%20%27smalltalk.%27%2C%20%28self%20classNameFor%3A%20aClass%20superclass%29%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%2C%20%5B%27.%0A%09aClass%20instanceVariableNames%20%0A%09%20%20%20%20do%3A%20%5B%3Aeach%20%7C%20aStream%20nextPutAll%3A%20%27%27%27%27%2C%20each%2C%20%27%27%27%27%5D%0A%09%20%20%20%20separatedBy%3A%20%5BaStream%20nextPutAll%3A%20%27%2C%20%27%5D.%0A%09aStream%09%0A%09%20%20%20%20nextPutAll%3A%20%27%5D%2C%20%27%27%27%3B%0A%09%20%20%20%20nextPutAll%3A%20aClass%20category%2C%20%27%27%27%27%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%29%3B%27.%0A%09aClass%20comment%20notEmpty%20ifTrue%3A%20%5B%0A%09%20%20%20%20aStream%20%0A%09%20%20%20%20%09lf%3B%0A%09%09nextPutAll%3A%20%27smalltalk.%27%3B%0A%09%09nextPutAll%3A%20%28self%20classNameFor%3A%20aClass%29%3B%0A%09%09nextPutAll%3A%20%27.comment%3D%27%3B%0A%09%09nextPutAll%3A%20%27unescape%28%27%27%27%2C%20aClass%20comment%20escaped%2C%20%27%27%27%29%27%5D.%0A%09aStream%20lf'),
+messageSends: ["nextPutAll:", unescape("%2C"), "classNameFor:", "superclass", "do:separatedBy:", "instanceVariableNames", "category", "ifTrue:", "notEmpty", "comment", "lf", "escaped"],
+referencedClasses: []
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportMetaDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportMetaDefinitionOf:on:',
+category: 'private',
+fn: function (aClass, aStream){
+var self=this;
+(($receiver = smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape(".iVarNames%20%3D%20%5B")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(unescape("%5D%3B"), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])])]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape(".iVarNames%20%3D%20%5B")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(unescape("%5D%3B"), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])])]);})]);
+return self;},
+source: unescape('exportMetaDefinitionOf%3A%20aClass%20on%3A%20aStream%0A%09aClass%20class%20instanceVariableNames%20isEmpty%20ifFalse%3A%20%5B%0A%09%20%20%20%20aStream%20%0A%09%09nextPutAll%3A%20%27smalltalk.%27%2C%20%28self%20classNameFor%3A%20aClass%20class%29%3B%0A%09%09nextPutAll%3A%20%27.iVarNames%20%3D%20%5B%27.%0A%09%20%20%20%20aClass%20class%20instanceVariableNames%0A%09%09do%3A%20%5B%3Aeach%20%7C%20aStream%20nextPutAll%3A%20%27%27%27%27%2C%20each%2C%20%27%27%27%27%5D%0A%09%09separatedBy%3A%20%5BaStream%20nextPutAll%3A%20%27%2C%27%5D.%0A%09%20%20%20%20aStream%20nextPutAll%3A%20%27%5D%3B%27%2C%20String%20lf%5D'),
+messageSends: ["ifFalse:", "isEmpty", "instanceVariableNames", "class", "nextPutAll:", unescape("%2C"), "classNameFor:", "do:separatedBy:", "lf"],
+referencedClasses: [smalltalk.String]
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportMethodsOf_on_',
+smalltalk.method({
+selector: 'exportMethodsOf:on:',
+category: 'private',
+fn: function (aClass, aStream){
+var self=this;
+smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_methodDictionary", []), "_values", []), "_do_", [(function(each){return (($receiver = smalltalk.send(smalltalk.send(each, "_category", []), "_match_", [unescape("%5E%5C*")])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);})]);
+smalltalk.send(aStream, "_lf", []);
+return self;},
+source: unescape('exportMethodsOf%3A%20aClass%20on%3A%20aStream%0A%09aClass%20methodDictionary%20values%20do%3A%20%5B%3Aeach%20%7C%0A%09%09%28each%20category%20match%3A%20%27%5E%5C*%27%29%20ifFalse%3A%20%5B%0A%09%09%09self%20exportMethod%3A%20each%20of%3A%20aClass%20on%3A%20aStream%5D%5D.%0A%09aStream%20lf'),
+messageSends: ["do:", "values", "methodDictionary", "ifFalse:", "match:", "category", "exportMethod:of:on:", "lf"],
+referencedClasses: []
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_classNameFor_',
+smalltalk.method({
+selector: 'classNameFor:',
+category: 'private',
+fn: function (aClass){
+var self=this;
+return (($receiver = smalltalk.send(aClass, "_isMetaclass", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [".klass"]);})() : (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [".klass"]);}), (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})]);
+return self;},
+source: unescape('classNameFor%3A%20aClass%0A%09%5EaClass%20isMetaclass%0A%09%20%20%20%20ifTrue%3A%20%5BaClass%20instanceClass%20name%2C%20%27.klass%27%5D%0A%09%20%20%20%20ifFalse%3A%20%5B%0A%09%09aClass%20isNil%0A%09%09%20%20%20%20ifTrue%3A%20%5B%27nil%27%5D%0A%09%09%20%20%20%20ifFalse%3A%20%5BaClass%20name%5D%5D'),
+messageSends: ["ifTrue:ifFalse:", "isMetaclass", unescape("%2C"), "name", "instanceClass", "isNil"],
+referencedClasses: []
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportMethod_of_on_',
+smalltalk.method({
+selector: 'exportMethod:of:on:',
+category: 'private',
+fn: function (aMethod, aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addMethod%28")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_selector", []), "_asSelector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.method%28%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("selector%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_selector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("category%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_category", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send("fn: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_fn", []), "_compiledSource", [])]), "__comma", [unescape("%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("source%3A%20unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_source", []), "_escaped", [])]), "__comma", [unescape("%27%29%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send("messageSends: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_messageSends", []), "_asJavascript", [])]), "__comma", [unescape("%2C")])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("referencedClasses%3A%20%5B")]);})(aStream);
+smalltalk.send(smalltalk.send(aMethod, "_referencedClasses", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [each])])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("%7D%29%2C")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+return self;},
+source: unescape('exportMethod%3A%20aMethod%20of%3A%20aClass%20on%3A%20aStream%0A%09aStream%20%0A%09%09nextPutAll%3A%20%27smalltalk.addMethod%28%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27%27%27%27%2C%20aMethod%20selector%20asSelector%2C%20%27%27%27%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27smalltalk.method%28%7B%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27selector%3A%20%27%27%27%2C%20aMethod%20selector%2C%20%27%27%27%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27category%3A%20%27%27%27%2C%20aMethod%20category%2C%20%27%27%27%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27fn%3A%20%27%2C%20aMethod%20fn%20compiledSource%2C%20%27%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27source%3A%20unescape%28%27%27%27%2C%20aMethod%20source%20escaped%2C%20%27%27%27%29%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27messageSends%3A%20%27%2C%20aMethod%20messageSends%20asJavascript%2C%20%27%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27referencedClasses%3A%20%5B%27.%0A%09%20%20%20%20%09%09aMethod%20referencedClasses%20%0A%09%09%09%09do%3A%20%5B%3Aeach%20%7C%20aStream%20nextPutAll%3A%20%27smalltalk.%27%2C%20%28self%20classNameFor%3A%20each%29%5D%0A%09%09%09%09separatedBy%3A%20%5BaStream%20nextPutAll%3A%20%27%2C%27%5D.%0A%09aStream%0A%09%09nextPutAll%3A%20%27%5D%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27%7D%29%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27smalltalk.%27%2C%20%28self%20classNameFor%3A%20aClass%29%3B%0A%09%09nextPutAll%3A%20%27%29%3B%27%3Blf%3Blf'),
+messageSends: ["nextPutAll:", "lf", unescape("%2C"), "asSelector", "selector", "category", "compiledSource", "fn", "escaped", "source", "asJavascript", "messageSends", "do:separatedBy:", "referencedClasses", "classNameFor:"],
+referencedClasses: []
+}),
+smalltalk.Exporter);
+
+smalltalk.addMethod(
+'_exportCategoryExtensions_on_',
+smalltalk.method({
+selector: 'exportCategoryExtensions:on:',
+category: 'private',
+fn: function (aString, aStream){
+var self=this;
+smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_collect_", [(function(each){return smalltalk.send(each, "_class", []);})])]), "_do_", [(function(each){return smalltalk.send(smalltalk.send(smalltalk.send(each, "_methodDictionary", []), "_values", []), "_do_", [(function(method){return (($receiver = smalltalk.send(smalltalk.send(method, "_category", []), "__eq", [smalltalk.send(unescape("*"), "__comma", [aString])])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self, "_exportMethod_of_on_", [method, each, aStream]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(self, "_exportMethod_of_on_", [method, each, aStream]);})]);})]);})]);
+return self;},
+source: unescape('exportCategoryExtensions%3A%20aString%20on%3A%20aStream%0A%09Smalltalk%20current%20classes%2C%20%28Smalltalk%20current%20classes%20collect%3A%20%5B%3Aeach%20%7C%20each%20class%5D%29%20do%3A%20%5B%3Aeach%20%7C%0A%09%09each%20methodDictionary%20values%20do%3A%20%5B%3Amethod%20%7C%0A%09%09%09method%20category%20%3D%20%28%27*%27%2C%20aString%29%20ifTrue%3A%20%5B%0A%09%09%09%09self%20exportMethod%3A%20method%20of%3A%20each%20on%3A%20aStream%5D%5D%5D'),
+messageSends: ["do:", unescape("%2C"), "classes", "current", "collect:", "class", "values", "methodDictionary", "ifTrue:", unescape("%3D"), "category", "exportMethod:of:on:"],
+referencedClasses: [smalltalk.Smalltalk]
+}),
+smalltalk.Exporter);
+
+
+
+smalltalk.addClass('ChunkExporter', smalltalk.Exporter, [], 'Compiler');
+smalltalk.addMethod(
+'_exportDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportDefinitionOf:on:',
+category: 'not yet classified',
+fn: function (aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(unescape("%20subclass%3A%20%23"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("%09instanceVariableNames%3A%20%27")]);})(aStream);
+smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%09category%3A%20%27"), "__comma", [smalltalk.send(aClass, "_category", [])]), "__comma", [unescape("%27%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);
+(($receiver = smalltalk.send(smalltalk.send(aClass, "_comment", []), "_notEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%20commentStamp%21")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aClass, "_comment", [])]), "__comma", [unescape("%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%20commentStamp%21")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aClass, "_comment", [])]), "__comma", [unescape("%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);})]);
+smalltalk.send(aStream, "_lf", []);
+return self;},
+source: unescape('exportDefinitionOf%3A%20aClass%20on%3A%20aStream%0A%09%22Chunk%20format.%22%0A%0A%09aStream%20%0A%09%20%20%20%20nextPutAll%3A%20%28self%20classNameFor%3A%20aClass%20superclass%29%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%20subclass%3A%20%23%27%2C%20%28self%20classNameFor%3A%20aClass%29%3B%20lf%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%09instanceVariableNames%3A%20%27%27%27.%0A%09aClass%20instanceVariableNames%20%0A%09%20%20%20%20do%3A%20%5B%3Aeach%20%7C%20aStream%20nextPutAll%3A%20each%5D%0A%09%20%20%20%20separatedBy%3A%20%5BaStream%20nextPutAll%3A%20%27%20%27%5D.%0A%09aStream%09%0A%09%20%20%20%20nextPutAll%3A%20%27%27%27%27%3B%20lf%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%09category%3A%20%27%27%27%2C%20aClass%20category%2C%20%27%27%27%21%27%3B%20lf.%0A%20%09aClass%20comment%20notEmpty%20ifTrue%3A%20%5B%0A%09%20%20%20%20aStream%20%0A%09%09nextPutAll%3A%20%27%21%27%2C%20%28self%20classNameFor%3A%20aClass%29%2C%20%27%20commentStamp%21%27%3Blf%3B%0A%09%09nextPutAll%3A%20%28self%20chunkEscape%3A%20aClass%20comment%29%2C%20%27%21%27%3Blf%5D.%0A%09aStream%20lf'),
+messageSends: ["nextPutAll:", "classNameFor:", "superclass", unescape("%2C"), "lf", "do:separatedBy:", "instanceVariableNames", "category", "ifTrue:", "notEmpty", "comment", "chunkEscape:"],
+referencedClasses: []
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMethod_of_on_',
+smalltalk.method({
+selector: 'exportMethod:of:on:',
+category: 'not yet classified',
+fn: function (aMethod, aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aMethod, "_source", [])])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("%21")]);})(aStream);
+return self;},
+source: unescape('exportMethod%3A%20aMethod%20of%3A%20aClass%20on%3A%20aStream%0A%09aStream%20%0A%09%09lf%3B%20lf%3B%20nextPutAll%3A%20%28self%20chunkEscape%3A%20aMethod%20source%29%3B%20lf%3B%0A%09%09nextPutAll%3A%20%27%21%27'),
+messageSends: ["lf", "nextPutAll:", "chunkEscape:", "source"],
+referencedClasses: []
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMethodsOf_on_',
+smalltalk.method({
+selector: 'exportMethodsOf:on:',
+category: 'not yet classified',
+fn: function (aClass, aStream){
+var self=this;
+smalltalk.send(aClass, "_protocolsDo_", [(function(category, methods){return (($receiver = smalltalk.send(category, "_match_", [unescape("%5E%5C*")])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, aClass, aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, aClass, aStream]);})]);})]);
+return self;},
+source: unescape('exportMethodsOf%3A%20aClass%20on%3A%20aStream%0A%0A%20%20%20aClass%20protocolsDo%3A%20%5B%3Acategory%20%3Amethods%20%7C%0A%09%28category%20match%3A%20%27%5E%5C*%27%29%20ifFalse%3A%20%5B%20%0A%09%09self%0A%09%09%09exportMethods%3A%20methods%0A%09%09%09category%3A%20category%0A%09%09%09of%3A%20aClass%0A%09%09%09on%3A%20aStream%5D%5D'),
+messageSends: ["protocolsDo:", "ifFalse:", "match:", "exportMethods:category:of:on:"],
+referencedClasses: []
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMetaDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportMetaDefinitionOf:on:',
+category: 'not yet classified',
+fn: function (aClass, aStream){
+var self=this;
+(($receiver = smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%20instanceVariableNames%3A%20%27")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);return (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%20instanceVariableNames%3A%20%27")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);return (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);})]);
+return self;},
+source: unescape('exportMetaDefinitionOf%3A%20aClass%20on%3A%20aStream%0A%0A%09aClass%20class%20instanceVariableNames%20isEmpty%20ifFalse%3A%20%5B%0A%09%09aStream%20%0A%09%09%20%20%20%20nextPutAll%3A%20%28self%20classNameFor%3A%20aClass%20class%29%3B%0A%09%09%20%20%20%20nextPutAll%3A%20%27%20instanceVariableNames%3A%20%27%27%27.%0A%09%09aClass%20class%20instanceVariableNames%20%0A%09%09%20%20%20%20do%3A%20%5B%3Aeach%20%7C%20aStream%20nextPutAll%3A%20each%5D%0A%09%09%20%20%20%20separatedBy%3A%20%5BaStream%20nextPutAll%3A%20%27%20%27%5D.%0A%09%09aStream%09%0A%09%09%20%20%20%20nextPutAll%3A%20%27%27%27%21%27%3B%20lf%3B%20lf%5D'),
+messageSends: ["ifFalse:", "isEmpty", "instanceVariableNames", "class", "nextPutAll:", "classNameFor:", "do:separatedBy:", "lf"],
+referencedClasses: []
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_classNameFor_',
+smalltalk.method({
+selector: 'classNameFor:',
+category: 'not yet classified',
+fn: function (aClass){
+var self=this;
+return (($receiver = smalltalk.send(aClass, "_isMetaclass", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [" class"]);})() : (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [" class"]);}), (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})]);
+return self;},
+source: unescape('classNameFor%3A%20aClass%0A%09%5EaClass%20isMetaclass%0A%09%20%20%20%20ifTrue%3A%20%5BaClass%20instanceClass%20name%2C%20%27%20class%27%5D%0A%09%20%20%20%20ifFalse%3A%20%5B%0A%09%09aClass%20isNil%0A%09%09%20%20%20%20ifTrue%3A%20%5B%27nil%27%5D%0A%09%09%20%20%20%20ifFalse%3A%20%5BaClass%20name%5D%5D'),
+messageSends: ["ifTrue:ifFalse:", "isMetaclass", unescape("%2C"), "name", "instanceClass", "isNil"],
+referencedClasses: []
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_chunkEscape_',
+smalltalk.method({
+selector: 'chunkEscape:',
+category: 'not yet classified',
+fn: function (aString){
+var self=this;
+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%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'),
+messageSends: ["trimBoth", "replace:with:"],
+referencedClasses: []
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportCategoryExtensions_on_',
+smalltalk.method({
+selector: 'exportCategoryExtensions:on:',
+category: 'not yet classified',
+fn: function (aString, aStream){
+var self=this;
+smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_collect_", [(function(each){return smalltalk.send(each, "_class", []);})])]), "_do_", [(function(each){return smalltalk.send(each, "_protocolsDo_", [(function(category, methods){return (($receiver = smalltalk.send(category, "__eq", [smalltalk.send(unescape("*"), "__comma", [aString])])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, each, aStream]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, each, aStream]);})]);})]);})]);
+return self;},
+source: unescape('exportCategoryExtensions%3A%20aString%20on%3A%20aStream%0A%09%22We%20need%20to%20override%20this%20one%20too%20since%20we%20need%20to%20group%0A%09all%20methods%20in%20a%20given%20protocol%20under%20a%20leading%20methodsFor%3A%20chunk%0A%09for%20that%20class.%22%0A%0A%09Smalltalk%20current%20classes%2C%20%28Smalltalk%20current%20classes%20collect%3A%20%5B%3Aeach%20%7C%20each%20class%5D%29%20do%3A%20%5B%3Aeach%20%7C%0A%09%09each%20protocolsDo%3A%20%5B%3Acategory%20%3Amethods%20%7C%0A%09%09%09category%20%3D%20%28%27*%27%2C%20aString%29%20ifTrue%3A%20%5B%0A%09%09%09%09self%20exportMethods%3A%20methods%20category%3A%20category%20of%3A%20each%20on%3A%20aStream%5D%5D%5D'),
+messageSends: ["do:", unescape("%2C"), "classes", "current", "collect:", "class", "protocolsDo:", "ifTrue:", unescape("%3D"), "exportMethods:category:of:on:"],
+referencedClasses: [smalltalk.Smalltalk]
+}),
+smalltalk.ChunkExporter);
+
+smalltalk.addMethod(
+'_exportMethods_category_of_on_',
+smalltalk.method({
+selector: 'exportMethods:category:of:on:',
+category: 'not yet classified',
+fn: function (methods, category, aClass, aStream){
+var self=this;
+(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(methods, "_do_", [(function(each){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%20%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+return self;},
+source: unescape('exportMethods%3A%20methods%20category%3A%20category%20of%3A%20aClass%20on%3A%20aStream%0A%0A%09aStream%0A%09%09nextPutAll%3A%20%27%21%27%2C%20%28self%20classNameFor%3A%20aClass%29%3B%0A%09%09nextPutAll%3A%20%27%20methodsFor%3A%20%27%27%27%2C%20category%2C%20%27%27%27%21%27.%0A%20%20%20%20%09methods%20do%3A%20%5B%3Aeach%20%7C%0A%09%09self%20exportMethod%3A%20each%20of%3A%20aClass%20on%3A%20aStream%5D.%0A%09aStream%20nextPutAll%3A%20%27%20%21%27%3B%20lf%3B%20lf'),
+messageSends: ["nextPutAll:", unescape("%2C"), "classNameFor:", "do:", "exportMethod:of:on:", "lf"],
+referencedClasses: []
+}),
+smalltalk.ChunkExporter);
+
+
+
+smalltalk.addClass('StrippedExporter', smalltalk.Exporter, [], 'Compiler');
+smalltalk.addMethod(
+'_exportDefinitionOf_on_',
+smalltalk.method({
+selector: 'exportDefinitionOf:on:',
+category: 'private',
+fn: function (aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addClass%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%27%2C%20")])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%2C%20%5B")]);})(aStream);
+smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C%20")]);})]);
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D%2C%20%27")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(aClass, "_category", []), "__comma", [unescape("%27")])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);})(aStream);
+smalltalk.send(aStream, "_lf", []);
+return self;},
+source: unescape('exportDefinitionOf%3A%20aClass%20on%3A%20aStream%0A%09aStream%20%0A%09%20%20%20%20nextPutAll%3A%20%27smalltalk.addClass%28%27%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%27%27%27%2C%20%28self%20classNameFor%3A%20aClass%29%2C%20%27%27%27%2C%20%27%3B%0A%09%20%20%20%20nextPutAll%3A%20%27smalltalk.%27%2C%20%28self%20classNameFor%3A%20aClass%20superclass%29%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%2C%20%5B%27.%0A%09aClass%20instanceVariableNames%20%0A%09%20%20%20%20do%3A%20%5B%3Aeach%20%7C%20aStream%20nextPutAll%3A%20%27%27%27%27%2C%20each%2C%20%27%27%27%27%5D%0A%09%20%20%20%20separatedBy%3A%20%5BaStream%20nextPutAll%3A%20%27%2C%20%27%5D.%0A%09aStream%09%0A%09%20%20%20%20nextPutAll%3A%20%27%5D%2C%20%27%27%27%3B%0A%09%20%20%20%20nextPutAll%3A%20aClass%20category%2C%20%27%27%27%27%3B%0A%09%20%20%20%20nextPutAll%3A%20%27%29%3B%27.%0A%09aStream%20lf'),
+messageSends: ["nextPutAll:", unescape("%2C"), "classNameFor:", "superclass", "do:separatedBy:", "instanceVariableNames", "category", "lf"],
+referencedClasses: []
+}),
+smalltalk.StrippedExporter);
+
+smalltalk.addMethod(
+'_exportMethod_of_on_',
+smalltalk.method({
+selector: 'exportMethod:of:on:',
+category: 'private',
+fn: function (aMethod, aClass, aStream){
+var self=this;
+(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addMethod%28")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_selector", []), "_asSelector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.method%28%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("selector%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_selector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("fn: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_fn", []), "_compiledSource", [])])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("%7D%29%2C")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
+return self;},
+source: unescape('exportMethod%3A%20aMethod%20of%3A%20aClass%20on%3A%20aStream%0A%09aStream%20%0A%09%09nextPutAll%3A%20%27smalltalk.addMethod%28%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27%27%27%27%2C%20aMethod%20selector%20asSelector%2C%20%27%27%27%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27smalltalk.method%28%7B%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27selector%3A%20%27%27%27%2C%20aMethod%20selector%2C%20%27%27%27%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27fn%3A%20%27%2C%20aMethod%20fn%20compiledSource%3Blf%3B%0A%09%09nextPutAll%3A%20%27%7D%29%2C%27%3Blf%3B%0A%09%09nextPutAll%3A%20%27smalltalk.%27%2C%20%28self%20classNameFor%3A%20aClass%29%3B%0A%09%09nextPutAll%3A%20%27%29%3B%27%3Blf%3Blf'),
+messageSends: ["nextPutAll:", "lf", unescape("%2C"), "asSelector", "selector", "compiledSource", "fn", "classNameFor:"],
+referencedClasses: []
+}),
+smalltalk.StrippedExporter);
+
+
+
 smalltalk.addClass('Node', smalltalk.Object, ['nodes'], 'Compiler');
 smalltalk.addMethod(
 '_nodes',
@@ -333,7 +716,7 @@ return (function($rec){smalltalk.send($rec, "_receiver_", [smalltalk.send(self,
 return self;},
 source: unescape('cascadeNodeWithMessages%3A%20aCollection%0A%09%7C%20first%20%7C%0A%09first%20%3A%3D%20SendNode%20new%0A%09%20%20%20%20selector%3A%20self%20selector%3B%0A%09%20%20%20%20arguments%3A%20self%20arguments%3B%0A%09%20%20%20%20yourself.%0A%09%5ECascadeNode%20new%0A%09%20%20%20%20receiver%3A%20self%20receiver%3B%0A%09%20%20%20%20nodes%3A%20%28Array%20with%3A%20first%29%2C%20aCollection%3B%0A%09%20%20%20%20yourself'),
 messageSends: ["selector:", "selector", "arguments:", "arguments", "yourself", "new", "receiver:", "receiver", "nodes:", unescape("%2C"), "with:"],
-referencedClasses: [smalltalk.SendNode,smalltalk.Array,smalltalk.CascadeNode]
+referencedClasses: [smalltalk.SendNode,smalltalk.Array,smalltalk.nil]
 }),
 smalltalk.SendNode);
 
@@ -616,7 +999,7 @@ return (function($rec){smalltalk.send($rec, "_nodes_", [smalltalk.send(self, "_n
 return self;},
 source: unescape('asBlockSequenceNode%0A%09%5EBlockSequenceNode%20new%0A%09%20%20%20%20nodes%3A%20self%20nodes%3B%0A%09%20%20%20%20temps%3A%20self%20temps%3B%0A%09%20%20%20%20yourself'),
 messageSends: ["nodes:", "nodes", "temps:", "temps", "yourself", "new"],
-referencedClasses: [smalltalk.BlockSequenceNode]
+referencedClasses: [smalltalk.nil]
 }),
 smalltalk.SequenceNode);
 
@@ -1159,7 +1542,7 @@ return result;
 return self;},
 source: unescape('loadExpression%3A%20aString%0A%09%7C%20result%20%7C%0A%09DoIt%20addCompiledMethod%3A%20%28self%20eval%3A%20%28self%20compileExpression%3A%20aString%29%29.%0A%09result%20%3A%3D%20DoIt%20new%20doIt.%0A%09DoIt%20removeCompiledMethod%3A%20%28DoIt%20methodDictionary%20at%3A%20%23doIt%29.%0A%09%5Eresult'),
 messageSends: ["addCompiledMethod:", "eval:", "compileExpression:", "doIt", "new", "removeCompiledMethod:", "at:", "methodDictionary"],
-referencedClasses: [smalltalk.DoIt]
+referencedClasses: [smalltalk.nil]
 }),
 smalltalk.Compiler);
 
@@ -1211,7 +1594,7 @@ return smalltalk.send(self, "_compileNode_", [smalltalk.send(self, "_parse_", [s
 return self;},
 source: unescape('compileExpression%3A%20aString%0A%09self%20currentClass%3A%20DoIt.%0A%09self%20source%3A%20%27doIt%20%5E%5B%27%2C%20aString%2C%20%27%5D%20value%27.%0A%09%5Eself%20compileNode%3A%20%28self%20parse%3A%20self%20source%29'),
 messageSends: ["currentClass:", "source:", unescape("%2C"), "compileNode:", "parse:", "source"],
-referencedClasses: [smalltalk.DoIt]
+referencedClasses: [smalltalk.nil]
 }),
 smalltalk.Compiler);
 
@@ -1635,7 +2018,7 @@ smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk),
 return self;},
 source: unescape('recompileAll%0A%09Smalltalk%20current%20classes%20do%3A%20%5B%3Aeach%20%7C%0A%09%09Transcript%20show%3A%20each%3B%20cr.%0A%09%09%5Bself%20recompile%3A%20each%5D%20valueWithTimeout%3A%20100%5D'),
 messageSends: ["do:", "classes", "current", "show:", "cr", "valueWithTimeout:", "recompile:"],
-referencedClasses: [smalltalk.Smalltalk,smalltalk.Transcript]
+referencedClasses: [smalltalk.Smalltalk,smalltalk.nil]
 }),
 smalltalk.Compiler);
 
@@ -1904,20 +2287,5 @@ smalltalk.Compiler.klass);
 
 
 smalltalk.addClass('DoIt', smalltalk.Object, [], 'Compiler');
-smalltalk.addMethod(
-'_doIt',
-smalltalk.method({
-selector: 'doIt',
-category: '',
-fn: function (){
-var self=this;
-return smalltalk.send((function(){return smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_do_", [(function(each){(function($rec){smalltalk.send($rec, "_show_", [each]);return smalltalk.send($rec, "_cr", []);})((smalltalk.Transcript || Transcript));return smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_recompile_", [each]);})]);}), "_value", []);
-return self;},
-source: unescape(''),
-messageSends: ["value", "do:", "classes", "current", "show:", "cr", "recompile:", "new"],
-referencedClasses: [smalltalk.Smalltalk,smalltalk.Transcript,smalltalk.Compiler]
-}),
-smalltalk.DoIt);
-
 
 

+ 121 - 23
js/Kernel.deploy.js

@@ -520,7 +520,7 @@ selector: 'log:block:',
 fn: function (aString, aBlock){
 var self=this;
 var result=nil;
-smalltalk.send(smalltalk.send(aString, "__comma", [" time: "]), "__comma", [smalltalk.send(smalltalk.send((smalltalk.Date || Date), "_millisecondsToRun_", [(function(){return result=smalltalk.send(aBlock, "_value", []);})]), "_printString", [])]);
+smalltalk.send((typeof console == 'undefined' ? nil : console), "_log_", [smalltalk.send(smalltalk.send(aString, "__comma", [" time: "]), "__comma", [smalltalk.send(smalltalk.send((smalltalk.Date || Date), "_millisecondsToRun_", [(function(){return result=smalltalk.send(aBlock, "_value", []);})]), "_printString", [])])]);
 return result;
 return self;}
 }),
@@ -587,6 +587,42 @@ return self;}
 }),
 smalltalk.Smalltalk);
 
+smalltalk.addMethod(
+'_basicParse_',
+smalltalk.method({
+selector: 'basicParse:',
+fn: function (aString){
+var self=this;
+return smalltalk.parser.parse(aString);
+return self;}
+}),
+smalltalk.Smalltalk);
+
+smalltalk.addMethod(
+'_parse_',
+smalltalk.method({
+selector: 'parse:',
+fn: function (aString){
+var self=this;
+var result=nil;
+smalltalk.send(self, "_try_catch_", [(function(){return result=smalltalk.send(self, "_basicParse_", [aString]);}), (function(ex){return smalltalk.send(smalltalk.send(self, "_parseError_", [ex]), "_signal", []);})]);
+return result;
+return self;}
+}),
+smalltalk.Smalltalk);
+
+smalltalk.addMethod(
+'_parseError_',
+smalltalk.method({
+selector: 'parseError:',
+fn: function (anException){
+var self=this;
+return smalltalk.Error._new()
+		._messageText_('Parse error on line ' + anException.line + ' column ' + anException.column + ' : ' + anException.message);
+return self;}
+}),
+smalltalk.Smalltalk);
+
 
 smalltalk.Smalltalk.klass.iVarNames = ['current'];
 smalltalk.addMethod(
@@ -1624,17 +1660,6 @@ return self;}
 }),
 smalltalk.BlockClosure);
 
-smalltalk.addMethod(
-'_printString',
-smalltalk.method({
-selector: 'printString',
-fn: function (){
-var self=this;
-return smalltalk.send((smalltalk.String || String), "_streamContents_", [(function(aStream){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_printString", [], smalltalk.Object)]);smalltalk.send($rec, "_nextPutAll_", [unescape("%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_compiledSource", [])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29")]);return smalltalk.send($rec, "_cr", []);})(aStream);})]);
-return self;}
-}),
-smalltalk.BlockClosure);
-
 smalltalk.addMethod(
 '_whileFalse',
 smalltalk.method({
@@ -1668,6 +1693,17 @@ return self;}
 }),
 smalltalk.BlockClosure);
 
+smalltalk.addMethod(
+'_applyTo_arguments_',
+smalltalk.method({
+selector: 'applyTo:arguments:',
+fn: function (anObject, aCollection){
+var self=this;
+return self.apply(anObject, aCollection);
+return self;}
+}),
+smalltalk.BlockClosure);
+
 
 
 smalltalk.addClass('Boolean', smalltalk.Object, [], 'Kernel');
@@ -4489,13 +4525,10 @@ smalltalk.addMethod(
 '_scanFrom_',
 smalltalk.method({
 selector: 'scanFrom:',
-fn: function (aStream){
+fn: function (aChunkParser){
 var self=this;
-var nextChunk=nil;
-var par=nil;
-smalltalk.send(self, "_log_block_", ["nextChunk build", (function(){return par=(($receiver = smalltalk.send(self['@chunkParser'], "_emptyChunk", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(self['@chunkParser'], "_chunk", []) : smalltalk.send($receiver, "__slash", [smalltalk.send(self['@chunkParser'], "_chunk", [])]);})]);
-smalltalk.send(self, "_log_block_", ["nextChunk", (function(){return nextChunk=smalltalk.send(par, "_parse_", [aStream]);})]);
-(($receiver = smalltalk.send(nextChunk, "_isEmptyChunk", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){smalltalk.send(self, "_compileMethod_", [smalltalk.send(nextChunk, "_contents", [])]);return smalltalk.send(self, "_scanFrom_", [aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){smalltalk.send(self, "_compileMethod_", [smalltalk.send(nextChunk, "_contents", [])]);return smalltalk.send(self, "_scanFrom_", [aStream]);})]);
+var chunk=nil;
+(function(){while(!(function(){chunk=smalltalk.send(aChunkParser, "_nextChunk", []);return smalltalk.send(chunk, "_isEmpty", []);})()) {(function(){return smalltalk.send(self, "_compileMethod_", [chunk]);})()}})();
 return self;}
 }),
 smalltalk.ClassCategoryReader);
@@ -4509,7 +4542,7 @@ var self=this;
 var method=nil;
 method=smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_load_forClass_", [aString, self['@class']]);
 smalltalk.send(method, "_category_", [self['@category']]);
-smalltalk.send(self, "_log_block_", ["addCompiledMethod", (function(){return smalltalk.send(self['@class'], "_addCompiledMethod_", [method]);})]);
+smalltalk.send(self['@class'], "_addCompiledMethod_", [method]);
 return self;}
 }),
 smalltalk.ClassCategoryReader);
@@ -4891,11 +4924,11 @@ smalltalk.addMethod(
 '_scanFrom_',
 smalltalk.method({
 selector: 'scanFrom:',
-fn: function (aStream){
+fn: function (aChunkParser){
 var self=this;
-var nextChunk=nil;
-nextChunk=smalltalk.send((($receiver = smalltalk.send(self['@chunkParser'], "_emptyChunk", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(self['@chunkParser'], "_chunk", []) : smalltalk.send($receiver, "__slash", [smalltalk.send(self['@chunkParser'], "_chunk", [])]), "_parse_", [aStream]);
-(($receiver = smalltalk.send(nextChunk, "_isEmptyChunk", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_setComment_", [smalltalk.send(nextChunk, "_contents", [])]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_setComment_", [smalltalk.send(nextChunk, "_contents", [])]);})]);
+var chunk=nil;
+chunk=smalltalk.send(aChunkParser, "_nextChunk", []);
+(($receiver = smalltalk.send(chunk, "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_setComment_", [chunk]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_setComment_", [chunk]);})]);
 return self;}
 }),
 smalltalk.ClassCommentReader);
@@ -5284,3 +5317,68 @@ return self;}
 smalltalk.ErrorHandler.klass);
 
 
+smalltalk.addClass('JSObjectProxy', smalltalk.Object, ['jsObject'], 'Kernel');
+smalltalk.addMethod(
+'_jsObject_',
+smalltalk.method({
+selector: 'jsObject:',
+fn: function (aJSObject){
+var self=this;
+self['@jsObject']=aJSObject;
+return self;}
+}),
+smalltalk.JSObjectProxy);
+
+smalltalk.addMethod(
+'_jsObject',
+smalltalk.method({
+selector: 'jsObject',
+fn: function (){
+var self=this;
+return self['@jsObject'];
+return self;}
+}),
+smalltalk.JSObjectProxy);
+
+smalltalk.addMethod(
+'_printString',
+smalltalk.method({
+selector: 'printString',
+fn: function (){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_jsObject", []), "_toString", []);
+return self;}
+}),
+smalltalk.JSObjectProxy);
+
+smalltalk.addMethod(
+'_inspectOn_',
+smalltalk.method({
+selector: 'inspectOn:',
+fn: function (anInspector){
+var self=this;
+var variables=nil;
+variables=smalltalk.send((smalltalk.Dictionary || Dictionary), "_new", []);
+smalltalk.send(variables, "_at_put_", [unescape("%23self"), smalltalk.send(self, "_jsObject", [])]);
+smalltalk.send(anInspector, "_setLabel_", [smalltalk.send(self, "_printString", [])]);
+for(var i in self['@jsObject']) {
+		variables._at_put_(i, self['@jsObject'][i]);
+	};
+smalltalk.send(anInspector, "_setVariables_", [variables]);
+return self;}
+}),
+smalltalk.JSObjectProxy);
+
+
+smalltalk.addMethod(
+'_on_',
+smalltalk.method({
+selector: 'on:',
+fn: function (aJSObject){
+var self=this;
+return (function($rec){smalltalk.send($rec, "_jsObject_", [aJSObject]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(self, "_new", []));
+return self;}
+}),
+smalltalk.JSObjectProxy.klass);
+
+

+ 118 - 36
js/Kernel.js

@@ -701,11 +701,11 @@ category: 'printing',
 fn: function (aString, aBlock){
 var self=this;
 var result=nil;
-smalltalk.send(smalltalk.send(aString, "__comma", [" time: "]), "__comma", [smalltalk.send(smalltalk.send((smalltalk.Date || Date), "_millisecondsToRun_", [(function(){return result=smalltalk.send(aBlock, "_value", []);})]), "_printString", [])]);
+smalltalk.send((typeof console == 'undefined' ? nil : console), "_log_", [smalltalk.send(smalltalk.send(aString, "__comma", [" time: "]), "__comma", [smalltalk.send(smalltalk.send((smalltalk.Date || Date), "_millisecondsToRun_", [(function(){return result=smalltalk.send(aBlock, "_value", []);})]), "_printString", [])])]);
 return result;
 return self;},
-source: unescape('log%3A%20aString%20block%3A%20aBlock%0A%0A%09%7C%20result%20%7C%0A%09%22console%20log%3A%22%20%20aString%2C%20%20%27%20time%3A%20%27%2C%20%28Date%20millisecondsToRun%3A%20%5Bresult%20%3A%3D%20aBlock%20value%5D%29%20printString.%0A%09%5Eresult%0A%0A'),
-messageSends: [unescape("%2C"), "printString", "millisecondsToRun:", "value"],
+source: unescape('log%3A%20aString%20block%3A%20aBlock%0A%0A%09%7C%20result%20%7C%0A%09console%20log%3A%20%20aString%2C%20%20%27%20time%3A%20%27%2C%20%28Date%20millisecondsToRun%3A%20%5Bresult%20%3A%3D%20aBlock%20value%5D%29%20printString.%0A%09%5Eresult%0A%0A'),
+messageSends: ["log:", unescape("%2C"), "printString", "millisecondsToRun:", "value"],
 referencedClasses: [smalltalk.Date]
 }),
 smalltalk.Object);
@@ -2232,21 +2232,6 @@ referencedClasses: []
 }),
 smalltalk.BlockClosure);
 
-smalltalk.addMethod(
-'_printString',
-smalltalk.method({
-selector: 'printString',
-category: 'printing',
-fn: function (){
-var self=this;
-return smalltalk.send((smalltalk.String || String), "_streamContents_", [(function(aStream){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_printString", [], smalltalk.Object)]);smalltalk.send($rec, "_nextPutAll_", [unescape("%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_compiledSource", [])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29")]);return smalltalk.send($rec, "_cr", []);})(aStream);})]);
-return self;},
-source: unescape('printString%0A%09%5E%20String%20streamContents%3A%20%5B%3AaStream%7C%20%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20aStream%20%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%09nextPutAll%3A%20super%20printString%3B%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%09nextPutAll%3A%20%27%28%27%3B%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%09nextPutAll%3A%20self%20compiledSource%3B%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%09nextPutAll%3A%20%27%29%27%3B%0A%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%20%09cr.%0A%20%20%20%20%20%20%20%20%20%20%20%5D'),
-messageSends: ["streamContents:", "nextPutAll:", "printString", "compiledSource", "cr"],
-referencedClasses: [smalltalk.String]
-}),
-smalltalk.BlockClosure);
-
 smalltalk.addMethod(
 '_whileFalse',
 smalltalk.method({
@@ -2292,6 +2277,21 @@ referencedClasses: []
 }),
 smalltalk.BlockClosure);
 
+smalltalk.addMethod(
+'_applyTo_arguments_',
+smalltalk.method({
+selector: 'applyTo:arguments:',
+category: 'evaluating',
+fn: function (anObject, aCollection){
+var self=this;
+return self.apply(anObject, aCollection);
+return self;},
+source: unescape('applyTo%3A%20anObject%20arguments%3A%20aCollection%0A%09%3Creturn%20self.apply%28anObject%2C%20aCollection%29%3E'),
+messageSends: [],
+referencedClasses: []
+}),
+smalltalk.BlockClosure);
+
 
 
 smalltalk.addClass('Boolean', smalltalk.Object, [], 'Kernel');
@@ -6075,16 +6075,13 @@ smalltalk.addMethod(
 smalltalk.method({
 selector: 'scanFrom:',
 category: 'fileIn',
-fn: function (aStream){
+fn: function (aChunkParser){
 var self=this;
-var nextChunk=nil;
-var par=nil;
-smalltalk.send(self, "_log_block_", ["nextChunk build", (function(){return par=(($receiver = smalltalk.send(self['@chunkParser'], "_emptyChunk", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(self['@chunkParser'], "_chunk", []) : smalltalk.send($receiver, "__slash", [smalltalk.send(self['@chunkParser'], "_chunk", [])]);})]);
-smalltalk.send(self, "_log_block_", ["nextChunk", (function(){return nextChunk=smalltalk.send(par, "_parse_", [aStream]);})]);
-(($receiver = smalltalk.send(nextChunk, "_isEmptyChunk", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){smalltalk.send(self, "_compileMethod_", [smalltalk.send(nextChunk, "_contents", [])]);return smalltalk.send(self, "_scanFrom_", [aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){smalltalk.send(self, "_compileMethod_", [smalltalk.send(nextChunk, "_contents", [])]);return smalltalk.send(self, "_scanFrom_", [aStream]);})]);
+var chunk=nil;
+(function(){while(!(function(){chunk=smalltalk.send(aChunkParser, "_nextChunk", []);return smalltalk.send(chunk, "_isEmpty", []);})()) {(function(){return smalltalk.send(self, "_compileMethod_", [chunk]);})()}})();
 return self;},
-source: unescape('scanFrom%3A%20aStream%0A%09%7C%20nextChunk%20par%20%7C%0A%09self%20log%3A%20%27nextChunk%20build%27%20block%3A%20%5Bpar%20%3A%3D%20%28chunkParser%20emptyChunk%20/%20chunkParser%20chunk%29%5D.%0A%09self%20log%3A%20%27nextChunk%27%20block%3A%20%5BnextChunk%20%3A%3D%20par%20parse%3A%20aStream%5D.%0A%09nextChunk%20isEmptyChunk%20ifFalse%3A%20%5B%0A%09%20%20%20%20self%20compileMethod%3A%20nextChunk%20contents.%0A%09%20%20%20%20self%20scanFrom%3A%20aStream%5D.'),
-messageSends: ["log:block:", unescape("/"), "emptyChunk", "chunk", "parse:", "ifFalse:", "isEmptyChunk", "compileMethod:", "contents", "scanFrom:"],
+source: unescape('scanFrom%3A%20aChunkParser%0A%09%7C%20chunk%20%7C%0A%09%5Bchunk%20%3A%3D%20aChunkParser%20nextChunk.%0A%09chunk%20isEmpty%5D%20whileFalse%3A%20%5B%0A%09%20%20%20%20self%20compileMethod%3A%20chunk%5D'),
+messageSends: ["whileFalse:", "nextChunk", "isEmpty", "compileMethod:"],
 referencedClasses: []
 }),
 smalltalk.ClassCategoryReader);
@@ -6099,11 +6096,11 @@ var self=this;
 var method=nil;
 method=smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_load_forClass_", [aString, self['@class']]);
 smalltalk.send(method, "_category_", [self['@category']]);
-smalltalk.send(self, "_log_block_", ["addCompiledMethod", (function(){return smalltalk.send(self['@class'], "_addCompiledMethod_", [method]);})]);
+smalltalk.send(self['@class'], "_addCompiledMethod_", [method]);
 return self;},
-source: unescape('compileMethod%3A%20aString%0A%09%7C%20method%20%7C%0A%09method%20%3A%3D%20Compiler%20new%20load%3A%20aString%20forClass%3A%20class.%0A%09method%20category%3A%20category.%0A%09self%20log%3A%20%27addCompiledMethod%27%20block%3A%20%5Bclass%20addCompiledMethod%3A%20method%5D'),
-messageSends: ["load:forClass:", "new", "category:", "log:block:", "addCompiledMethod:"],
-referencedClasses: [smalltalk.Compiler]
+source: unescape('compileMethod%3A%20aString%0A%09%7C%20method%20%7C%0A%09method%20%3A%3D%20Compiler%20new%20load%3A%20aString%20forClass%3A%20class.%0A%09method%20category%3A%20category.%0A%09class%20addCompiledMethod%3A%20method'),
+messageSends: ["load:forClass:", "new", "category:", "addCompiledMethod:"],
+referencedClasses: [smalltalk.nil]
 }),
 smalltalk.ClassCategoryReader);
 
@@ -6613,14 +6610,14 @@ smalltalk.addMethod(
 smalltalk.method({
 selector: 'scanFrom:',
 category: 'fileIn',
-fn: function (aStream){
+fn: function (aChunkParser){
 var self=this;
-var nextChunk=nil;
-nextChunk=smalltalk.send((($receiver = smalltalk.send(self['@chunkParser'], "_emptyChunk", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(self['@chunkParser'], "_chunk", []) : smalltalk.send($receiver, "__slash", [smalltalk.send(self['@chunkParser'], "_chunk", [])]), "_parse_", [aStream]);
-(($receiver = smalltalk.send(nextChunk, "_isEmptyChunk", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_setComment_", [smalltalk.send(nextChunk, "_contents", [])]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_setComment_", [smalltalk.send(nextChunk, "_contents", [])]);})]);
+var chunk=nil;
+chunk=smalltalk.send(aChunkParser, "_nextChunk", []);
+(($receiver = smalltalk.send(chunk, "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_setComment_", [chunk]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_setComment_", [chunk]);})]);
 return self;},
-source: unescape('scanFrom%3A%20aStream%0A%09%7C%20nextChunk%20%7C%0A%09nextChunk%20%3A%3D%20%28chunkParser%20emptyChunk%20/%20chunkParser%20chunk%29%20parse%3A%20aStream.%0A%09nextChunk%20isEmptyChunk%20ifFalse%3A%20%5B%0A%09%20%20%20%20self%20setComment%3A%20nextChunk%20contents%5D.'),
-messageSends: ["parse:", unescape("/"), "emptyChunk", "chunk", "ifFalse:", "isEmptyChunk", "setComment:", "contents"],
+source: unescape('scanFrom%3A%20aChunkParser%0A%09%7C%20chunk%20%7C%0A%09chunk%20%3A%3D%20aChunkParser%20nextChunk.%0A%09chunk%20isEmpty%20ifFalse%3A%20%5B%0A%09%20%20%20%20self%20setComment%3A%20chunk%5D.'),
+messageSends: ["nextChunk", "ifFalse:", "isEmpty", "setComment:"],
 referencedClasses: []
 }),
 smalltalk.ClassCommentReader);
@@ -7141,3 +7138,88 @@ referencedClasses: []
 smalltalk.ErrorHandler.klass);
 
 
+smalltalk.addClass('JSObjectProxy', smalltalk.Object, ['jsObject'], 'Kernel');
+smalltalk.addMethod(
+'_jsObject_',
+smalltalk.method({
+selector: 'jsObject:',
+category: 'accessing',
+fn: function (aJSObject){
+var self=this;
+self['@jsObject']=aJSObject;
+return self;},
+source: unescape('jsObject%3A%20aJSObject%0A%09jsObject%20%3A%3D%20aJSObject'),
+messageSends: [],
+referencedClasses: []
+}),
+smalltalk.JSObjectProxy);
+
+smalltalk.addMethod(
+'_jsObject',
+smalltalk.method({
+selector: 'jsObject',
+category: 'accessing',
+fn: function (){
+var self=this;
+return self['@jsObject'];
+return self;},
+source: unescape('jsObject%0A%09%5EjsObject'),
+messageSends: [],
+referencedClasses: []
+}),
+smalltalk.JSObjectProxy);
+
+smalltalk.addMethod(
+'_printString',
+smalltalk.method({
+selector: 'printString',
+category: 'proxy',
+fn: function (){
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_jsObject", []), "_toString", []);
+return self;},
+source: unescape('printString%0A%09%5Eself%20jsObject%20toString'),
+messageSends: ["toString", "jsObject"],
+referencedClasses: []
+}),
+smalltalk.JSObjectProxy);
+
+smalltalk.addMethod(
+'_inspectOn_',
+smalltalk.method({
+selector: 'inspectOn:',
+category: 'proxy',
+fn: function (anInspector){
+var self=this;
+var variables=nil;
+variables=smalltalk.send((smalltalk.Dictionary || Dictionary), "_new", []);
+smalltalk.send(variables, "_at_put_", [unescape("%23self"), smalltalk.send(self, "_jsObject", [])]);
+smalltalk.send(anInspector, "_setLabel_", [smalltalk.send(self, "_printString", [])]);
+for(var i in self['@jsObject']) {
+		variables._at_put_(i, self['@jsObject'][i]);
+	};
+smalltalk.send(anInspector, "_setVariables_", [variables]);
+return self;},
+source: unescape('inspectOn%3A%20anInspector%0A%09%7C%20variables%20%7C%0A%09variables%20%3A%3D%20Dictionary%20new.%0A%09variables%20at%3A%20%27%23self%27%20put%3A%20self%20jsObject.%0A%09anInspector%20setLabel%3A%20self%20printString.%0A%09%3Cfor%28var%20i%20in%20self%5B%27@jsObject%27%5D%29%20%7B%0A%09%09variables._at_put_%28i%2C%20self%5B%27@jsObject%27%5D%5Bi%5D%29%3B%0A%09%7D%3E.%0A%09anInspector%20setVariables%3A%20variables'),
+messageSends: ["new", "at:put:", "jsObject", "setLabel:", "printString", "setVariables:"],
+referencedClasses: [smalltalk.Dictionary]
+}),
+smalltalk.JSObjectProxy);
+
+
+smalltalk.addMethod(
+'_on_',
+smalltalk.method({
+selector: 'on:',
+category: 'instance creation',
+fn: function (aJSObject){
+var self=this;
+return (function($rec){smalltalk.send($rec, "_jsObject_", [aJSObject]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(self, "_new", []));
+return self;},
+source: unescape('on%3A%20aJSObject%0A%09%5Eself%20new%0A%09%09jsObject%3A%20aJSObject%3B%0A%09%09yourself'),
+messageSends: ["jsObject:", "yourself", "new"],
+referencedClasses: []
+}),
+smalltalk.JSObjectProxy.klass);
+
+

+ 0 - 1283
js/Parser.deploy.js

@@ -1,1283 +0,0 @@
-smalltalk.addClass('PPParser', smalltalk.Object, ['memo'], 'Parser');
-smalltalk.addMethod(
-'_initialize',
-smalltalk.method({
-selector: 'initialize',
-fn: function (){
-var self=this;
-self['@memo']=smalltalk.send((smalltalk.Dictionary || Dictionary), "_new", []);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_memo',
-smalltalk.method({
-selector: 'memo',
-fn: function (){
-var self=this;
-return self['@memo'];
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_flatten',
-smalltalk.method({
-selector: 'flatten',
-fn: function (){
-var self=this;
-return smalltalk.send((smalltalk.PPFlattenParser || PPFlattenParser), "_on_", [self]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_withSource',
-smalltalk.method({
-selector: 'withSource',
-fn: function (){
-var self=this;
-return smalltalk.send((smalltalk.PPSourceParser || PPSourceParser), "_on_", [self]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'__eq_eq_gt',
-smalltalk.method({
-selector: '==>',
-fn: function (aBlock){
-var self=this;
-return smalltalk.send((smalltalk.PPActionParser || PPActionParser), "_on_block_", [self, aBlock]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'__comma',
-smalltalk.method({
-selector: ',',
-fn: function (aParser){
-var self=this;
-return smalltalk.send((smalltalk.PPSequenceParser || PPSequenceParser), "_with_with_", [self, aParser]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'__slash',
-smalltalk.method({
-selector: '/',
-fn: function (aParser){
-var self=this;
-return smalltalk.send((smalltalk.PPChoiceParser || PPChoiceParser), "_with_with_", [self, aParser]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_plus',
-smalltalk.method({
-selector: 'plus',
-fn: function (){
-var self=this;
-return smalltalk.send((smalltalk.PPRepeatingParser || PPRepeatingParser), "_on_min_", [self, (1)]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_star',
-smalltalk.method({
-selector: 'star',
-fn: function (){
-var self=this;
-return smalltalk.send((smalltalk.PPRepeatingParser || PPRepeatingParser), "_on_min_", [self, (0)]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_not',
-smalltalk.method({
-selector: 'not',
-fn: function (){
-var self=this;
-return smalltalk.send((smalltalk.PPNotParser || PPNotParser), "_on_", [self]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_optional',
-smalltalk.method({
-selector: 'optional',
-fn: function (){
-var self=this;
-return (($receiver = self).klass === smalltalk.Number) ? $receiver /smalltalk.send((smalltalk.PPEpsilonParser || PPEpsilonParser), "_new", []) : smalltalk.send($receiver, "__slash", [smalltalk.send((smalltalk.PPEpsilonParser || PPEpsilonParser), "_new", [])]);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_memoizedParse_',
-smalltalk.method({
-selector: 'memoizedParse:',
-fn: function (aStream){
-var self=this;
-var r=nil;
-var start=nil;
-var end=nil;
-var node=nil;
-start=smalltalk.send(aStream, "_position", []);
-smalltalk.send(self, "_log_block_", ["memoizedParse", (function(){return r=smalltalk.send(smalltalk.send(self, "_memo", []), "_at_ifPresent_ifAbsent_", [start, (function(value){smalltalk.send(aStream, "_position_", [smalltalk.send(smalltalk.send(smalltalk.send(self, "_memo", []), "_at_", [start]), "_second", [])]);return smalltalk.send(value, "_first", []);}), (function(){node=smalltalk.send(self, "_parse_", [aStream]);end=smalltalk.send(aStream, "_position", []);smalltalk.send(smalltalk.send(self, "_memo", []), "_at_put_", [start, smalltalk.send((smalltalk.Array || Array), "_with_with_", [node, end])]);return node;})]);})]);
-return r;
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-smalltalk.send(self, "_subclassResponsibility", []);
-return self;}
-}),
-smalltalk.PPParser);
-
-smalltalk.addMethod(
-'_parseAll_',
-smalltalk.method({
-selector: 'parseAll:',
-fn: function (aStream){
-var self=this;
-var result=nil;
-result=smalltalk.send(smalltalk.send((smalltalk.PPSequenceParser || PPSequenceParser), "_with_with_", [self, smalltalk.send((smalltalk.PPEOFParser || PPEOFParser), "_new", [])]), "_memoizedParse_", [aStream]);
-return (($receiver = smalltalk.send(result, "_isParseFailure", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self, "_error_", [smalltalk.send(result, "_messageFor_", [smalltalk.send(aStream, "_contents", [])])]);})() : (function(){return smalltalk.send(result, "_first", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(self, "_error_", [smalltalk.send(result, "_messageFor_", [smalltalk.send(aStream, "_contents", [])])]);}), (function(){return smalltalk.send(result, "_first", []);})]);
-return self;}
-}),
-smalltalk.PPParser);
-
-
-
-smalltalk.addClass('PPEOFParser', smalltalk.PPParser, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return (($receiver = smalltalk.send(aStream, "_atEnd", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []), "_reason_at_", [smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(aStream, "_contents", []), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])]), "__comma", [unescape("---------------")]), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])]), "__comma", ["EOF expected"]), smalltalk.send(aStream, "_position", [])]);})() : (function(){return nil;})()) : smalltalk.send($receiver, "_ifFalse_ifTrue_", [(function(){return smalltalk.send(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []), "_reason_at_", [smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(aStream, "_contents", []), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])]), "__comma", [unescape("---------------")]), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])]), "__comma", ["EOF expected"]), smalltalk.send(aStream, "_position", [])]);}), (function(){return nil;})]);
-return self;}
-}),
-smalltalk.PPEOFParser);
-
-
-
-smalltalk.addClass('PPAnyParser', smalltalk.PPParser, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return (($receiver = smalltalk.send(aStream, "_atEnd", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []), "_reason_at_", ["did not expect EOF", smalltalk.send(aStream, "_position", [])]);})() : (function(){return smalltalk.send(aStream, "_next", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []), "_reason_at_", ["did not expect EOF", smalltalk.send(aStream, "_position", [])]);}), (function(){return smalltalk.send(aStream, "_next", []);})]);
-return self;}
-}),
-smalltalk.PPAnyParser);
-
-
-
-smalltalk.addClass('PPEpsilonParser', smalltalk.PPParser, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return nil;
-return self;}
-}),
-smalltalk.PPEpsilonParser);
-
-
-
-smalltalk.addClass('PPStringParser', smalltalk.PPParser, ['string'], 'Parser');
-smalltalk.addMethod(
-'_string',
-smalltalk.method({
-selector: 'string',
-fn: function (){
-var self=this;
-return self['@string'];
-return self;}
-}),
-smalltalk.PPStringParser);
-
-smalltalk.addMethod(
-'_string_',
-smalltalk.method({
-selector: 'string:',
-fn: function (aString){
-var self=this;
-self['@string']=aString;
-return self;}
-}),
-smalltalk.PPStringParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var position=nil;
-var result=nil;
-position=smalltalk.send(aStream, "_position", []);
-result=smalltalk.send(aStream, "_next_", [smalltalk.send(smalltalk.send(self, "_string", []), "_size", [])]);
-return (($receiver = smalltalk.send(result, "__eq", [smalltalk.send(self, "_string", [])])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return result;})() : (function(){smalltalk.send(aStream, "_position_", [position]);return (function($rec){smalltalk.send($rec, "_reason_", [smalltalk.send(smalltalk.send(smalltalk.send("Expected ", "__comma", [smalltalk.send(self, "_string", [])]), "__comma", [" but got "]), "__comma", [smalltalk.send(smalltalk.send(result, "_at_", [position]), "_printString", [])])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []));})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return result;}), (function(){smalltalk.send(aStream, "_position_", [position]);return (function($rec){smalltalk.send($rec, "_reason_", [smalltalk.send(smalltalk.send(smalltalk.send("Expected ", "__comma", [smalltalk.send(self, "_string", [])]), "__comma", [" but got "]), "__comma", [smalltalk.send(smalltalk.send(result, "_at_", [position]), "_printString", [])])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []));})]);
-return self;}
-}),
-smalltalk.PPStringParser);
-
-
-
-smalltalk.addClass('PPCharacterParser', smalltalk.PPParser, ['regexp'], 'Parser');
-smalltalk.addMethod(
-'_string_',
-smalltalk.method({
-selector: 'string:',
-fn: function (aString){
-var self=this;
-self['@regexp']=smalltalk.send((smalltalk.RegularExpression || RegularExpression), "_fromString_", [smalltalk.send(smalltalk.send(unescape("%5B"), "__comma", [aString]), "__comma", [unescape("%5D")])]);
-return self;}
-}),
-smalltalk.PPCharacterParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return (($receiver = smalltalk.send(smalltalk.send(smalltalk.send(aStream, "_peek", []), "_notNil", []), "_and_", [(function(){return smalltalk.send(self, "_match_", [smalltalk.send(aStream, "_peek", [])]);})])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(aStream, "_next", []);})() : (function(){return smalltalk.send(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []), "_reason_at_", ["Could not match", smalltalk.send(aStream, "_position", [])]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(aStream, "_next", []);}), (function(){return smalltalk.send(smalltalk.send((smalltalk.PPFailure || PPFailure), "_new", []), "_reason_at_", ["Could not match", smalltalk.send(aStream, "_position", [])]);})]);
-return self;}
-}),
-smalltalk.PPCharacterParser);
-
-smalltalk.addMethod(
-'_match_',
-smalltalk.method({
-selector: 'match:',
-fn: function (aString){
-var self=this;
-return smalltalk.send(aString, "_match_", [self['@regexp']]);
-return self;}
-}),
-smalltalk.PPCharacterParser);
-
-
-
-smalltalk.addClass('PPListParser', smalltalk.PPParser, ['parsers'], 'Parser');
-smalltalk.addMethod(
-'_parsers',
-smalltalk.method({
-selector: 'parsers',
-fn: function (){
-var self=this;
-return (($receiver = self['@parsers']) == nil || $receiver == undefined) ? (function(){return [];})() : $receiver;
-return self;}
-}),
-smalltalk.PPListParser);
-
-smalltalk.addMethod(
-'_parsers_',
-smalltalk.method({
-selector: 'parsers:',
-fn: function (aCollection){
-var self=this;
-self['@parsers']=aCollection;
-return self;}
-}),
-smalltalk.PPListParser);
-
-smalltalk.addMethod(
-'_copyWith_',
-smalltalk.method({
-selector: 'copyWith:',
-fn: function (aParser){
-var self=this;
-return smalltalk.send(smalltalk.send(self, "_class", []), "_withAll_", [smalltalk.send(smalltalk.send(self, "_parsers", []), "_copyWith_", [aParser])]);
-return self;}
-}),
-smalltalk.PPListParser);
-
-
-smalltalk.addMethod(
-'_withAll_',
-smalltalk.method({
-selector: 'withAll:',
-fn: function (aCollection){
-var self=this;
-return (function($rec){smalltalk.send($rec, "_parsers_", [aCollection]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(self, "_new", []));
-return self;}
-}),
-smalltalk.PPListParser.klass);
-
-smalltalk.addMethod(
-'_with_with_',
-smalltalk.method({
-selector: 'with:with:',
-fn: function (aParser, anotherParser){
-var self=this;
-return smalltalk.send(self, "_withAll_", [smalltalk.send((smalltalk.Array || Array), "_with_with_", [aParser, anotherParser])]);
-return self;}
-}),
-smalltalk.PPListParser.klass);
-
-
-smalltalk.addClass('PPSequenceParser', smalltalk.PPListParser, [], 'Parser');
-smalltalk.addMethod(
-'__comma',
-smalltalk.method({
-selector: ',',
-fn: function (aRule){
-var self=this;
-return smalltalk.send(self, "_copyWith_", [aRule]);
-return self;}
-}),
-smalltalk.PPSequenceParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var start=nil;
-var elements=nil;
-var element=nil;
-start=smalltalk.send(aStream, "_position", []);
-elements=[];
-smalltalk.send(smalltalk.send(self, "_parsers", []), "_detect_ifNone_", [(function(each){element=smalltalk.send(each, "_memoizedParse_", [aStream]);smalltalk.send(elements, "_add_", [element]);return smalltalk.send(element, "_isParseFailure", []);}), (function(){return nil;})]);
-return (($receiver = smalltalk.send(element, "_isParseFailure", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return elements;})() : (function(){smalltalk.send(aStream, "_position_", [start]);return element;})()) : smalltalk.send($receiver, "_ifFalse_ifTrue_", [(function(){return elements;}), (function(){smalltalk.send(aStream, "_position_", [start]);return element;})]);
-return self;}
-}),
-smalltalk.PPSequenceParser);
-
-
-
-smalltalk.addClass('PPChoiceParser', smalltalk.PPListParser, [], 'Parser');
-smalltalk.addMethod(
-'__slash',
-smalltalk.method({
-selector: '/',
-fn: function (aRule){
-var self=this;
-return smalltalk.send(self, "_copyWith_", [aRule]);
-return self;}
-}),
-smalltalk.PPChoiceParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var result=nil;
-smalltalk.send(smalltalk.send(self, "_parsers", []), "_detect_ifNone_", [(function(each){result=smalltalk.send(each, "_memoizedParse_", [aStream]);return smalltalk.send(smalltalk.send(result, "_isParseFailure", []), "_not", []);}), (function(){return nil;})]);
-return result;
-return self;}
-}),
-smalltalk.PPChoiceParser);
-
-
-
-smalltalk.addClass('PPDelegateParser', smalltalk.PPParser, ['parser'], 'Parser');
-smalltalk.addMethod(
-'_parser',
-smalltalk.method({
-selector: 'parser',
-fn: function (){
-var self=this;
-return self['@parser'];
-return self;}
-}),
-smalltalk.PPDelegateParser);
-
-smalltalk.addMethod(
-'_parser_',
-smalltalk.method({
-selector: 'parser:',
-fn: function (aParser){
-var self=this;
-self['@parser']=aParser;
-return self;}
-}),
-smalltalk.PPDelegateParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return smalltalk.send(smalltalk.send(self, "_parser", []), "_memoizedParse_", [aStream]);
-return self;}
-}),
-smalltalk.PPDelegateParser);
-
-
-smalltalk.addMethod(
-'_on_',
-smalltalk.method({
-selector: 'on:',
-fn: function (aParser){
-var self=this;
-return (function($rec){smalltalk.send($rec, "_parser_", [aParser]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(self, "_new", []));
-return self;}
-}),
-smalltalk.PPDelegateParser.klass);
-
-
-smalltalk.addClass('PPAndParser', smalltalk.PPDelegateParser, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return smalltalk.send(self, "_basicParse_", [aStream]);
-return self;}
-}),
-smalltalk.PPAndParser);
-
-smalltalk.addMethod(
-'_basicParse_',
-smalltalk.method({
-selector: 'basicParse:',
-fn: function (aStream){
-var self=this;
-var element=nil;
-var position=nil;
-position=smalltalk.send(aStream, "_position", []);
-element=smalltalk.send(smalltalk.send(self, "_parser", []), "_memoizedParse_", [aStream]);
-smalltalk.send(aStream, "_position_", [position]);
-return element;
-return self;}
-}),
-smalltalk.PPAndParser);
-
-
-
-smalltalk.addClass('PPNotParser', smalltalk.PPAndParser, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var element=nil;
-element=smalltalk.send(self, "_basicParse_", [aStream]);
-return (($receiver = smalltalk.send(element, "_isParseFailure", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return nil;})() : (function(){return smalltalk.send((smalltalk.PPFailure || PPFailure), "_reason_at_", [element, smalltalk.send(aStream, "_position", [])]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return nil;}), (function(){return smalltalk.send((smalltalk.PPFailure || PPFailure), "_reason_at_", [element, smalltalk.send(aStream, "_position", [])]);})]);
-return self;}
-}),
-smalltalk.PPNotParser);
-
-
-
-smalltalk.addClass('PPActionParser', smalltalk.PPDelegateParser, ['block'], 'Parser');
-smalltalk.addMethod(
-'_block',
-smalltalk.method({
-selector: 'block',
-fn: function (){
-var self=this;
-return self['@block'];
-return self;}
-}),
-smalltalk.PPActionParser);
-
-smalltalk.addMethod(
-'_block_',
-smalltalk.method({
-selector: 'block:',
-fn: function (aBlock){
-var self=this;
-self['@block']=aBlock;
-return self;}
-}),
-smalltalk.PPActionParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var element=nil;
-element=smalltalk.send(smalltalk.send(self, "_parser", []), "_memoizedParse_", [aStream]);
-return (($receiver = smalltalk.send(element, "_isParseFailure", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(smalltalk.send(self, "_block", []), "_value_", [element]);})() : (function(){return element;})()) : smalltalk.send($receiver, "_ifFalse_ifTrue_", [(function(){return smalltalk.send(smalltalk.send(self, "_block", []), "_value_", [element]);}), (function(){return element;})]);
-return self;}
-}),
-smalltalk.PPActionParser);
-
-
-smalltalk.addMethod(
-'_on_block_',
-smalltalk.method({
-selector: 'on:block:',
-fn: function (aParser, aBlock){
-var self=this;
-return (function($rec){smalltalk.send($rec, "_parser_", [aParser]);smalltalk.send($rec, "_block_", [aBlock]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(self, "_new", []));
-return self;}
-}),
-smalltalk.PPActionParser.klass);
-
-
-smalltalk.addClass('PPFlattenParser', smalltalk.PPDelegateParser, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var start=nil;
-var element=nil;
-var stop=nil;
-start=smalltalk.send(aStream, "_position", []);
-element=smalltalk.send(smalltalk.send(self, "_parser", []), "_memoizedParse_", [aStream]);
-return (($receiver = smalltalk.send(element, "_isParseFailure", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return element;})() : (function(){return smalltalk.send(smalltalk.send(aStream, "_collection", []), "_copyFrom_to_", [(($receiver = start).klass === smalltalk.Number) ? $receiver +(1) : smalltalk.send($receiver, "__plus", [(1)]), smalltalk.send(aStream, "_position", [])]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return element;}), (function(){return smalltalk.send(smalltalk.send(aStream, "_collection", []), "_copyFrom_to_", [(($receiver = start).klass === smalltalk.Number) ? $receiver +(1) : smalltalk.send($receiver, "__plus", [(1)]), smalltalk.send(aStream, "_position", [])]);})]);
-return self;}
-}),
-smalltalk.PPFlattenParser);
-
-
-
-smalltalk.addClass('PPSourceParser', smalltalk.PPDelegateParser, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var start=nil;
-var element=nil;
-var stop=nil;
-var result=nil;
-start=smalltalk.send(aStream, "_position", []);
-element=smalltalk.send(smalltalk.send(self, "_parser", []), "_memoizedParse_", [aStream]);
-return (($receiver = smalltalk.send(element, "_isParseFailure", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return element;})() : (function(){result=smalltalk.send(smalltalk.send(aStream, "_collection", []), "_copyFrom_to_", [(($receiver = start).klass === smalltalk.Number) ? $receiver +(1) : smalltalk.send($receiver, "__plus", [(1)]), smalltalk.send(aStream, "_position", [])]);return smalltalk.send((smalltalk.Array || Array), "_with_with_", [element, result]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return element;}), (function(){result=smalltalk.send(smalltalk.send(aStream, "_collection", []), "_copyFrom_to_", [(($receiver = start).klass === smalltalk.Number) ? $receiver +(1) : smalltalk.send($receiver, "__plus", [(1)]), smalltalk.send(aStream, "_position", [])]);return smalltalk.send((smalltalk.Array || Array), "_with_with_", [element, result]);})]);
-return self;}
-}),
-smalltalk.PPSourceParser);
-
-
-
-smalltalk.addClass('PPRepeatingParser', smalltalk.PPDelegateParser, ['min'], 'Parser');
-smalltalk.addMethod(
-'_min',
-smalltalk.method({
-selector: 'min',
-fn: function (){
-var self=this;
-return self['@min'];
-return self;}
-}),
-smalltalk.PPRepeatingParser);
-
-smalltalk.addMethod(
-'_min_',
-smalltalk.method({
-selector: 'min:',
-fn: function (aNumber){
-var self=this;
-self['@min']=aNumber;
-return self;}
-}),
-smalltalk.PPRepeatingParser);
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-var start=nil;
-var element=nil;
-var elements=nil;
-var failure=nil;
-start=smalltalk.send(aStream, "_position", []);
-elements=smalltalk.send((smalltalk.Array || Array), "_new", []);
-(function(){while((function(){return smalltalk.send((($receiver = smalltalk.send(elements, "_size", [])).klass === smalltalk.Number) ? $receiver <smalltalk.send(self, "_min", []) : smalltalk.send($receiver, "__lt", [smalltalk.send(self, "_min", [])]), "_and_", [(function(){return smalltalk.send(failure, "_isNil", []);})]);})()) {(function(){element=smalltalk.send(smalltalk.send(self, "_parser", []), "_memoizedParse_", [aStream]);return (($receiver = smalltalk.send(element, "_isParseFailure", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(elements, "_addLast_", [element]);})() : (function(){smalltalk.send(aStream, "_position_", [start]);return failure=element;})()) : smalltalk.send($receiver, "_ifFalse_ifTrue_", [(function(){return smalltalk.send(elements, "_addLast_", [element]);}), (function(){smalltalk.send(aStream, "_position_", [start]);return failure=element;})]);})()}})();
-return (($receiver = failure) == nil || $receiver == undefined) ? (function(){(function(){while((function(){return smalltalk.send(failure, "_isNil", []);})()) {(function(){element=smalltalk.send(smalltalk.send(self, "_parser", []), "_memoizedParse_", [aStream]);return (($receiver = smalltalk.send(element, "_isParseFailure", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return failure=element;})() : (function(){return smalltalk.send(elements, "_addLast_", [element]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return failure=element;}), (function(){return smalltalk.send(elements, "_addLast_", [element]);})]);})()}})();return elements;})() : (function(){return failure;})();
-return self;}
-}),
-smalltalk.PPRepeatingParser);
-
-
-smalltalk.addMethod(
-'_on_min_',
-smalltalk.method({
-selector: 'on:min:',
-fn: function (aParser, aNumber){
-var self=this;
-return (function($rec){smalltalk.send($rec, "_parser_", [aParser]);smalltalk.send($rec, "_min_", [aNumber]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(self, "_new", []));
-return self;}
-}),
-smalltalk.PPRepeatingParser.klass);
-
-
-smalltalk.addClass('PPFailure', smalltalk.Object, ['position', 'reason'], 'Parser');
-smalltalk.addMethod(
-'_position',
-smalltalk.method({
-selector: 'position',
-fn: function (){
-var self=this;
-return (($receiver = self['@position']) == nil || $receiver == undefined) ? (function(){return (0);})() : $receiver;
-return self;}
-}),
-smalltalk.PPFailure);
-
-smalltalk.addMethod(
-'_position_',
-smalltalk.method({
-selector: 'position:',
-fn: function (aNumber){
-var self=this;
-self['@position']=aNumber;
-return self;}
-}),
-smalltalk.PPFailure);
-
-smalltalk.addMethod(
-'_reason',
-smalltalk.method({
-selector: 'reason',
-fn: function (){
-var self=this;
-return (($receiver = self['@reason']) == nil || $receiver == undefined) ? (function(){return "";})() : $receiver;
-return self;}
-}),
-smalltalk.PPFailure);
-
-smalltalk.addMethod(
-'_reason_',
-smalltalk.method({
-selector: 'reason:',
-fn: function (aString){
-var self=this;
-self['@reason']=aString;
-return self;}
-}),
-smalltalk.PPFailure);
-
-smalltalk.addMethod(
-'_reason_at_',
-smalltalk.method({
-selector: 'reason:at:',
-fn: function (aString, anInteger){
-var self=this;
-(function($rec){smalltalk.send($rec, "_reason_", [aString]);return smalltalk.send($rec, "_position_", [anInteger]);})(self);
-return self;}
-}),
-smalltalk.PPFailure);
-
-smalltalk.addMethod(
-'_isParseFailure',
-smalltalk.method({
-selector: 'isParseFailure',
-fn: function (){
-var self=this;
-return true;
-return self;}
-}),
-smalltalk.PPFailure);
-
-smalltalk.addMethod(
-'_accept_',
-smalltalk.method({
-selector: 'accept:',
-fn: function (aVisitor){
-var self=this;
-smalltalk.send(aVisitor, "_visitFailure_", [self]);
-return self;}
-}),
-smalltalk.PPFailure);
-
-smalltalk.addMethod(
-'_asString',
-smalltalk.method({
-selector: 'asString',
-fn: function (){
-var self=this;
-return smalltalk.send(smalltalk.send(self['@reason'], "__comma", [" at "]), "__comma", [smalltalk.send(self['@position'], "_asString", [])]);
-return self;}
-}),
-smalltalk.PPFailure);
-
-
-smalltalk.addMethod(
-'_reason_at_',
-smalltalk.method({
-selector: 'reason:at:',
-fn: function (aString, anInteger){
-var self=this;
-return (function($rec){smalltalk.send($rec, "_reason_at_", [aString, anInteger]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(self, "_new", []));
-return self;}
-}),
-smalltalk.PPFailure.klass);
-
-
-smalltalk.addClass('SmalltalkParser', smalltalk.Object, [], 'Parser');
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return smalltalk.send(smalltalk.send(self, "_parser", []), "_parse_", [aStream]);
-return self;}
-}),
-smalltalk.SmalltalkParser);
-
-smalltalk.addMethod(
-'_parser',
-smalltalk.method({
-selector: 'parser',
-fn: function (){
-var self=this;
-var method=nil;
-var expression=nil;
-var separator=nil;
-var comment=nil;
-var ws=nil;
-var identifier=nil;
-var keyword=nil;
-var className=nil;
-var string=nil;
-var symbol=nil;
-var number=nil;
-var literalArray=nil;
-var variable=nil;
-var reference=nil;
-var classReference=nil;
-var literal=nil;
-var ret=nil;
-var methodParser=nil;
-var expressionParser=nil;
-var keyword=nil;
-var unarySelector=nil;
-var binarySelector=nil;
-var keywordPattern=nil;
-var unaryPattern=nil;
-var binaryPattern=nil;
-var assignment=nil;
-var temps=nil;
-var blockParamList=nil;
-var block=nil;
-var expression=nil;
-var expressions=nil;
-var subexpression=nil;
-var statements=nil;
-var sequence=nil;
-var operand=nil;
-var unaryMessage=nil;
-var unarySend=nil;
-var unaryTail=nil;
-var binaryMessage=nil;
-var binarySend=nil;
-var binaryTail=nil;
-var keywordMessage=nil;
-var keywordSend=nil;
-var keywordPair=nil;
-var cascade=nil;
-var message=nil;
-var jsStatement=nil;
-separator=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.String || String), "_cr", []), "__comma", [smalltalk.send((smalltalk.String || String), "_space", [])]), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])]), "__comma", [smalltalk.send((smalltalk.String || String), "_tab", [])]), "_asChoiceParser", []);
-comment=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%22"), "_asCharacterParser", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%22"), "_asParser", []), "_not", []), "__comma", [smalltalk.send((smalltalk.PPAnyParser || PPAnyParser), "_new", [])]), "_star", [])]), "__comma", [smalltalk.send(unescape("%22"), "_asCharacterParser", [])]), "_flatten", []);
-ws=smalltalk.send((($receiver = separator).klass === smalltalk.Number) ? $receiver /comment : smalltalk.send($receiver, "__slash", [comment]), "_star", []);
-identifier=smalltalk.send(smalltalk.send(smalltalk.send(unescape("a-z"), "_asCharacterParser", []), "__comma", [smalltalk.send(smalltalk.send(unescape("a-zA-Z0-9"), "_asCharacterParser", []), "_star", [])]), "_flatten", []);
-keyword=smalltalk.send(smalltalk.send(identifier, "__comma", [smalltalk.send(":", "_asParser", [])]), "_flatten", []);
-className=smalltalk.send(smalltalk.send(smalltalk.send(unescape("A-Z"), "_asCharacterParser", []), "__comma", [smalltalk.send(smalltalk.send(unescape("a-zA-Z0-9"), "_asCharacterParser", []), "_star", [])]), "_flatten", []);
-string=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%27"), "_asParser", []), "__comma", [smalltalk.send(smalltalk.send((($receiver = smalltalk.send(unescape("%27%27"), "_asParser", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(smalltalk.send(smalltalk.send(unescape("%27"), "_asParser", []), "_not", []), "__comma", [smalltalk.send((smalltalk.PPAnyParser || PPAnyParser), "_new", [])]) : smalltalk.send($receiver, "__slash", [smalltalk.send(smalltalk.send(smalltalk.send(unescape("%27"), "_asParser", []), "_not", []), "__comma", [smalltalk.send((smalltalk.PPAnyParser || PPAnyParser), "_new", [])])]), "_star", []), "_flatten", [])]), "__comma", [smalltalk.send(unescape("%27"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send((smalltalk.ValueNode || ValueNode), "_new", []), "_value_", [smalltalk.send(smalltalk.send(node, "_at_", [(2)]), "_replace_with_", [unescape("%27%27"), unescape("%27")])]);})]);
-symbol=smalltalk.send(smalltalk.send(smalltalk.send(unescape("%23"), "_asParser", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send(unescape("a-zA-Z0-9"), "_asCharacterParser", []), "_plus", []), "_flatten", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send((smalltalk.ValueNode || ValueNode), "_new", []), "_value_", [smalltalk.send(node, "_second", [])]);})]);
-number=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("0-9"), "_asCharacterParser", []), "_plus", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send(".", "_asParser", []), "__comma", [smalltalk.send(smalltalk.send(unescape("0-9"), "_asCharacterParser", []), "_plus", [])]), "_optional", [])]), "_flatten", []), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send((smalltalk.ValueNode || ValueNode), "_new", []), "_value_", [smalltalk.send(node, "_asNumber", [])]);})]);
-literal=smalltalk.send((smalltalk.PPDelegateParser || PPDelegateParser), "_new", []);
-literalArray=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%23%28"), "_asParser", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [literal]), "__comma", [ws]), "_star", [])]), "__comma", [smalltalk.send(unescape("%29"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send((smalltalk.ValueNode || ValueNode), "_new", []), "_value_", [smalltalk.send((smalltalk.Array || Array), "_withAll_", [smalltalk.send(smalltalk.send(node, "_second", []), "_collect_", [(function(each){return smalltalk.send(smalltalk.send(each, "_second", []), "_value", []);})])])]);})]);
-variable=smalltalk.send(identifier, "__eq_eq_gt", [(function(token){return smalltalk.send(smalltalk.send((smalltalk.VariableNode || VariableNode), "_new", []), "_value_", [token]);})]);
-classReference=smalltalk.send(className, "__eq_eq_gt", [(function(token){return smalltalk.send(smalltalk.send((smalltalk.ClassReferenceNode || ClassReferenceNode), "_new", []), "_value_", [token]);})]);
-reference=(($receiver = variable).klass === smalltalk.Number) ? $receiver /classReference : smalltalk.send($receiver, "__slash", [classReference]);
-binarySelector=smalltalk.send(smalltalk.send(smalltalk.send(unescape("+*/%3D%3E%3C%2C@%25%7E%7C%26-"), "_asCharacterParser", []), "_plus", []), "_flatten", []);
-unarySelector=identifier;
-keywordPattern=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [keyword]), "__comma", [ws]), "__comma", [identifier]), "_plus", []), "__eq_eq_gt", [(function(nodes){return smalltalk.send((smalltalk.Array || Array), "_with_with_", [smalltalk.send(smalltalk.send(nodes, "_collect_", [(function(each){return smalltalk.send(each, "_at_", [(2)]);})]), "_join_", [""]), smalltalk.send(nodes, "_collect_", [(function(each){return smalltalk.send(each, "_at_", [(4)]);})])]);})]);
-binaryPattern=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [binarySelector]), "__comma", [ws]), "__comma", [identifier]), "__eq_eq_gt", [(function(node){return smalltalk.send((smalltalk.Array || Array), "_with_with_", [smalltalk.send(node, "_second", []), smalltalk.send((smalltalk.Array || Array), "_with_", [smalltalk.send(node, "_fourth", [])])]);})]);
-unaryPattern=smalltalk.send(smalltalk.send(ws, "__comma", [unarySelector]), "__eq_eq_gt", [(function(node){return smalltalk.send((smalltalk.Array || Array), "_with_with_", [smalltalk.send(node, "_second", []), smalltalk.send((smalltalk.Array || Array), "_new", [])]);})]);
-expression=smalltalk.send((smalltalk.PPDelegateParser || PPDelegateParser), "_new", []);
-expressions=smalltalk.send(smalltalk.send(expression, "__comma", [smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [smalltalk.send(".", "_asParser", [])]), "__comma", [ws]), "__comma", [expression]), "__eq_eq_gt", [(function(node){return smalltalk.send(node, "_fourth", []);})]), "_star", [])]), "__eq_eq_gt", [(function(node){var result=nil;
-result=smalltalk.send((smalltalk.Array || Array), "_with_", [smalltalk.send(node, "_first", [])]);smalltalk.send(smalltalk.send(node, "_second", []), "_do_", [(function(each){return smalltalk.send(result, "_add_", [each]);})]);return result;})]);
-assignment=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(variable, "__comma", [ws]), "__comma", [smalltalk.send(unescape("%3A%3D"), "_asParser", [])]), "__comma", [ws]), "__comma", [expression]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_left_", [smalltalk.send(node, "_first", [])]);return smalltalk.send($rec, "_right_", [smalltalk.send(node, "_at_", [(5)])]);})(smalltalk.send((smalltalk.AssignmentNode || AssignmentNode), "_new", []));})]);
-ret=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%5E"), "_asParser", []), "__comma", [ws]), "__comma", [expression]), "__comma", [ws]), "__comma", [smalltalk.send(smalltalk.send(".", "_asParser", []), "_optional", [])]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_addNode_", [smalltalk.send(node, "_third", [])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send((smalltalk.ReturnNode || ReturnNode), "_new", []));})]);
-temps=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%7C"), "_asParser", []), "__comma", [smalltalk.send(smalltalk.send(ws, "__comma", [identifier]), "_star", [])]), "__comma", [ws]), "__comma", [smalltalk.send(unescape("%7C"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send(node, "_second", []), "_collect_", [(function(each){return smalltalk.send(each, "_second", []);})]);})]);
-blockParamList=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(":", "_asParser", []), "__comma", [identifier]), "__comma", [ws]), "_plus", []), "__comma", [smalltalk.send(unescape("%7C"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send(node, "_first", []), "_collect_", [(function(each){return smalltalk.send(each, "_second", []);})]);})]);
-subexpression=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%28"), "_asParser", []), "__comma", [ws]), "__comma", [expression]), "__comma", [ws]), "__comma", [smalltalk.send(unescape("%29"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(node, "_third", []);})]);
-statements=(($receiver = (($receiver = smalltalk.send(ret, "__eq_eq_gt", [(function(node){return smalltalk.send((smalltalk.Array || Array), "_with_", [node]);})])).klass === smalltalk.Number) ? $receiver /smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(expressions, "__comma", [ws]), "__comma", [smalltalk.send(".", "_asParser", [])]), "__comma", [ws]), "__comma", [ret]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_add_", [smalltalk.send(node, "_at_", [(5)])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(node, "_first", []));})]) : smalltalk.send($receiver, "__slash", [smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(expressions, "__comma", [ws]), "__comma", [smalltalk.send(".", "_asParser", [])]), "__comma", [ws]), "__comma", [ret]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_add_", [smalltalk.send(node, "_at_", [(5)])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send(node, "_first", []));})])])).klass === smalltalk.Number) ? $receiver /smalltalk.send(smalltalk.send(expressions, "__comma", [smalltalk.send(smalltalk.send(".", "_asParser", []), "_optional", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(node, "_first", []);})]) : smalltalk.send($receiver, "__slash", [smalltalk.send(smalltalk.send(expressions, "__comma", [smalltalk.send(smalltalk.send(".", "_asParser", []), "_optional", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(node, "_first", []);})])]);
-sequence=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(temps, "_optional", []), "__comma", [ws]), "__comma", [smalltalk.send(statements, "_optional", [])]), "__comma", [ws]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_temps_", [smalltalk.send(node, "_first", [])]);smalltalk.send($rec, "_nodes_", [smalltalk.send(node, "_third", [])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send((smalltalk.SequenceNode || SequenceNode), "_new", []));})]);
-block=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%5B"), "_asParser", []), "__comma", [ws]), "__comma", [smalltalk.send(blockParamList, "_optional", [])]), "__comma", [ws]), "__comma", [smalltalk.send(sequence, "_optional", [])]), "__comma", [ws]), "__comma", [smalltalk.send(unescape("%5D"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_parameters_", [smalltalk.send(node, "_third", [])]);return smalltalk.send($rec, "_addNode_", [smalltalk.send(smalltalk.send(node, "_at_", [(5)]), "_asBlockSequenceNode", [])]);})(smalltalk.send((smalltalk.BlockNode || BlockNode), "_new", []));})]);
-operand=(($receiver = (($receiver = literal).klass === smalltalk.Number) ? $receiver /reference : smalltalk.send($receiver, "__slash", [reference])).klass === smalltalk.Number) ? $receiver /subexpression : smalltalk.send($receiver, "__slash", [subexpression]);
-smalltalk.send(literal, "_parser_", [(($receiver = (($receiver = (($receiver = (($receiver = number).klass === smalltalk.Number) ? $receiver /string : smalltalk.send($receiver, "__slash", [string])).klass === smalltalk.Number) ? $receiver /literalArray : smalltalk.send($receiver, "__slash", [literalArray])).klass === smalltalk.Number) ? $receiver /symbol : smalltalk.send($receiver, "__slash", [symbol])).klass === smalltalk.Number) ? $receiver /block : smalltalk.send($receiver, "__slash", [block])]);
-unaryMessage=smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [unarySelector]), "__comma", [smalltalk.send(smalltalk.send(":", "_asParser", []), "_not", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send((smalltalk.SendNode || SendNode), "_new", []), "_selector_", [smalltalk.send(node, "_second", [])]);})]);
-unaryTail=smalltalk.send((smalltalk.PPDelegateParser || PPDelegateParser), "_new", []);
-smalltalk.send(unaryTail, "_parser_", [smalltalk.send(smalltalk.send(unaryMessage, "__comma", [smalltalk.send(unaryTail, "_optional", [])]), "__eq_eq_gt", [(function(node){return (($receiver = smalltalk.send(node, "_second", [])) == nil || $receiver == undefined) ? (function(){return smalltalk.send(node, "_first", []);})() : (function(){return smalltalk.send(smalltalk.send(node, "_second", []), "_valueForReceiver_", [smalltalk.send(node, "_first", [])]);})();})])]);
-unarySend=smalltalk.send(smalltalk.send(operand, "__comma", [smalltalk.send(unaryTail, "_optional", [])]), "__eq_eq_gt", [(function(node){return (($receiver = smalltalk.send(node, "_second", [])) == nil || $receiver == undefined) ? (function(){return smalltalk.send(node, "_first", []);})() : (function(){return smalltalk.send(smalltalk.send(node, "_second", []), "_valueForReceiver_", [smalltalk.send(node, "_first", [])]);})();})]);
-binaryMessage=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [binarySelector]), "__comma", [ws]), "__comma", [(($receiver = unarySend).klass === smalltalk.Number) ? $receiver /operand : smalltalk.send($receiver, "__slash", [operand])]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_selector_", [smalltalk.send(node, "_second", [])]);return smalltalk.send($rec, "_arguments_", [smalltalk.send((smalltalk.Array || Array), "_with_", [smalltalk.send(node, "_fourth", [])])]);})(smalltalk.send((smalltalk.SendNode || SendNode), "_new", []));})]);
-binaryTail=smalltalk.send((smalltalk.PPDelegateParser || PPDelegateParser), "_new", []);
-smalltalk.send(binaryTail, "_parser_", [smalltalk.send(smalltalk.send(binaryMessage, "__comma", [smalltalk.send(binaryTail, "_optional", [])]), "__eq_eq_gt", [(function(node){return (($receiver = smalltalk.send(node, "_second", [])) == nil || $receiver == undefined) ? (function(){return smalltalk.send(node, "_first", []);})() : (function(){return smalltalk.send(smalltalk.send(node, "_second", []), "_valueForReceiver_", [smalltalk.send(node, "_first", [])]);})();})])]);
-binarySend=smalltalk.send(smalltalk.send(unarySend, "__comma", [smalltalk.send(binaryTail, "_optional", [])]), "__eq_eq_gt", [(function(node){return (($receiver = smalltalk.send(node, "_second", [])) == nil || $receiver == undefined) ? (function(){return smalltalk.send(node, "_first", []);})() : (function(){return smalltalk.send(smalltalk.send(node, "_second", []), "_valueForReceiver_", [smalltalk.send(node, "_first", [])]);})();})]);
-keywordPair=smalltalk.send(smalltalk.send(keyword, "__comma", [ws]), "__comma", [binarySend]);
-keywordMessage=smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [keywordPair]), "_plus", []), "__eq_eq_gt", [(function(nodes){return (function($rec){smalltalk.send($rec, "_selector_", [smalltalk.send(smalltalk.send(nodes, "_collect_", [(function(each){return smalltalk.send(smalltalk.send(each, "_second", []), "_first", []);})]), "_join_", [""])]);return smalltalk.send($rec, "_arguments_", [smalltalk.send(nodes, "_collect_", [(function(each){return smalltalk.send(smalltalk.send(each, "_second", []), "_third", []);})])]);})(smalltalk.send((smalltalk.SendNode || SendNode), "_new", []));})]);
-keywordSend=smalltalk.send(smalltalk.send(binarySend, "__comma", [keywordMessage]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send(node, "_second", []), "_valueForReceiver_", [smalltalk.send(node, "_first", [])]);})]);
-message=(($receiver = (($receiver = binaryMessage).klass === smalltalk.Number) ? $receiver /unaryMessage : smalltalk.send($receiver, "__slash", [unaryMessage])).klass === smalltalk.Number) ? $receiver /keywordMessage : smalltalk.send($receiver, "__slash", [keywordMessage]);
-cascade=smalltalk.send(smalltalk.send((($receiver = keywordSend).klass === smalltalk.Number) ? $receiver /binarySend : smalltalk.send($receiver, "__slash", [binarySend]), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [smalltalk.send(unescape("%3B"), "_asParser", [])]), "__comma", [message]), "_plus", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send(node, "_first", []), "_cascadeNodeWithMessages_", [smalltalk.send(smalltalk.send(node, "_second", []), "_collect_", [(function(each){return smalltalk.send(each, "_third", []);})])]);})]);
-jsStatement=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(unescape("%3C"), "_asParser", []), "__comma", [smalltalk.send(smalltalk.send((($receiver = smalltalk.send(unescape("%3E%3E"), "_asParser", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(smalltalk.send(smalltalk.send(unescape("%3E"), "_asParser", []), "_not", []), "__comma", [smalltalk.send((smalltalk.PPAnyParser || PPAnyParser), "_new", [])]) : smalltalk.send($receiver, "__slash", [smalltalk.send(smalltalk.send(smalltalk.send(unescape("%3E"), "_asParser", []), "_not", []), "__comma", [smalltalk.send((smalltalk.PPAnyParser || PPAnyParser), "_new", [])])]), "_star", []), "_flatten", [])]), "__comma", [smalltalk.send(unescape("%3E"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_source_", [smalltalk.send(node, "_second", [])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send((smalltalk.JSStatementNode || JSStatementNode), "_new", []));})]);
-smalltalk.send(expression, "_parser_", [(($receiver = (($receiver = (($receiver = (($receiver = assignment).klass === smalltalk.Number) ? $receiver /cascade : smalltalk.send($receiver, "__slash", [cascade])).klass === smalltalk.Number) ? $receiver /keywordSend : smalltalk.send($receiver, "__slash", [keywordSend])).klass === smalltalk.Number) ? $receiver /binarySend : smalltalk.send($receiver, "__slash", [binarySend])).klass === smalltalk.Number) ? $receiver /jsStatement : smalltalk.send($receiver, "__slash", [jsStatement])]);
-method=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(ws, "__comma", [(($receiver = (($receiver = keywordPattern).klass === smalltalk.Number) ? $receiver /binaryPattern : smalltalk.send($receiver, "__slash", [binaryPattern])).klass === smalltalk.Number) ? $receiver /unaryPattern : smalltalk.send($receiver, "__slash", [unaryPattern])]), "__comma", [ws]), "__comma", [smalltalk.send(sequence, "_optional", [])]), "__comma", [ws]), "_withSource", []), "__eq_eq_gt", [(function(node){return (function($rec){smalltalk.send($rec, "_selector_", [smalltalk.send(smalltalk.send(smalltalk.send(node, "_first", []), "_second", []), "_first", [])]);smalltalk.send($rec, "_arguments_", [smalltalk.send(smalltalk.send(smalltalk.send(node, "_first", []), "_second", []), "_second", [])]);smalltalk.send($rec, "_addNode_", [smalltalk.send(smalltalk.send(node, "_first", []), "_fourth", [])]);smalltalk.send($rec, "_source_", [smalltalk.send(node, "_second", [])]);return smalltalk.send($rec, "_yourself", []);})(smalltalk.send((smalltalk.MethodNode || MethodNode), "_new", []));})]);
-return smalltalk.send(smalltalk.send(method, "__comma", [smalltalk.send((smalltalk.PPEOFParser || PPEOFParser), "_new", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(node, "_first", []);})]);
-return self;}
-}),
-smalltalk.SmalltalkParser);
-
-
-smalltalk.addMethod(
-'_parse_',
-smalltalk.method({
-selector: 'parse:',
-fn: function (aStream){
-var self=this;
-return smalltalk.send(smalltalk.send(self, "_new", []), "_parse_", [aStream]);
-return self;}
-}),
-smalltalk.SmalltalkParser.klass);
-
-
-smalltalk.addClass('Chunk', smalltalk.Object, ['contents'], 'Parser');
-smalltalk.addMethod(
-'_contents',
-smalltalk.method({
-selector: 'contents',
-fn: function (){
-var self=this;
-return (($receiver = self['@contents']) == nil || $receiver == undefined) ? (function(){return "";})() : $receiver;
-return self;}
-}),
-smalltalk.Chunk);
-
-smalltalk.addMethod(
-'_contents_',
-smalltalk.method({
-selector: 'contents:',
-fn: function (aString){
-var self=this;
-self['@contents']=aString;
-return self;}
-}),
-smalltalk.Chunk);
-
-smalltalk.addMethod(
-'_isEmptyChunk',
-smalltalk.method({
-selector: 'isEmptyChunk',
-fn: function (){
-var self=this;
-return false;
-return self;}
-}),
-smalltalk.Chunk);
-
-smalltalk.addMethod(
-'_isInstructionChunk',
-smalltalk.method({
-selector: 'isInstructionChunk',
-fn: function (){
-var self=this;
-return false;
-return self;}
-}),
-smalltalk.Chunk);
-
-
-
-smalltalk.addClass('InstructionChunk', smalltalk.Chunk, [], 'Parser');
-smalltalk.addMethod(
-'_isInstructionChunk',
-smalltalk.method({
-selector: 'isInstructionChunk',
-fn: function (){
-var self=this;
-return true;
-return self;}
-}),
-smalltalk.InstructionChunk);
-
-
-
-smalltalk.addClass('EmptyChunk', smalltalk.Chunk, [], 'Parser');
-smalltalk.addMethod(
-'_isEmptyChunk',
-smalltalk.method({
-selector: 'isEmptyChunk',
-fn: function (){
-var self=this;
-return true;
-return self;}
-}),
-smalltalk.EmptyChunk);
-
-
-
-smalltalk.addClass('ChunkParser', smalltalk.Object, ['parser', 'separator', 'eof', 'ws', 'chunk', 'emptyChunk', 'instructionChunk'], 'Parser');
-smalltalk.addMethod(
-'_parser',
-smalltalk.method({
-selector: 'parser',
-fn: function (){
-var self=this;
-return (($receiver = self['@parser']) == nil || $receiver == undefined) ? (function(){return self['@parser']=(($receiver = (($receiver = (($receiver = smalltalk.send(self, "_instructionChunk", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(self, "_emptyChunk", []) : smalltalk.send($receiver, "__slash", [smalltalk.send(self, "_emptyChunk", [])])).klass === smalltalk.Number) ? $receiver /smalltalk.send(self, "_chunk", []) : smalltalk.send($receiver, "__slash", [smalltalk.send(self, "_chunk", [])])).klass === smalltalk.Number) ? $receiver /smalltalk.send(self, "_eof", []) : smalltalk.send($receiver, "__slash", [smalltalk.send(self, "_eof", [])]);})() : $receiver;
-return self;}
-}),
-smalltalk.ChunkParser);
-
-smalltalk.addMethod(
-'_eof',
-smalltalk.method({
-selector: 'eof',
-fn: function (){
-var self=this;
-return (($receiver = self['@eof']) == nil || $receiver == undefined) ? (function(){return self['@eof']=smalltalk.send(smalltalk.send(smalltalk.send(self, "_ws", []), "__comma", [smalltalk.send((smalltalk.PPEOFParser || PPEOFParser), "_new", [])]), "__eq_eq_gt", [(function(node){return nil;})]);})() : $receiver;
-return self;}
-}),
-smalltalk.ChunkParser);
-
-smalltalk.addMethod(
-'_separator',
-smalltalk.method({
-selector: 'separator',
-fn: function (){
-var self=this;
-return (($receiver = self['@separator']) == nil || $receiver == undefined) ? (function(){return self['@separator']=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.String || String), "_cr", []), "__comma", [smalltalk.send((smalltalk.String || String), "_space", [])]), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])]), "__comma", [smalltalk.send((smalltalk.String || String), "_tab", [])]), "_asChoiceParser", []);})() : $receiver;
-return self;}
-}),
-smalltalk.ChunkParser);
-
-smalltalk.addMethod(
-'_ws',
-smalltalk.method({
-selector: 'ws',
-fn: function (){
-var self=this;
-return (($receiver = self['@ws']) == nil || $receiver == undefined) ? (function(){return self['@ws']=smalltalk.send(smalltalk.send(self, "_separator", []), "_star", []);})() : $receiver;
-return self;}
-}),
-smalltalk.ChunkParser);
-
-smalltalk.addMethod(
-'_chunk',
-smalltalk.method({
-selector: 'chunk',
-fn: function (){
-var self=this;
-return (($receiver = self['@chunk']) == nil || $receiver == undefined) ? (function(){return self['@chunk']=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(self, "_ws", []), "__comma", [smalltalk.send(smalltalk.send((($receiver = smalltalk.send(unescape("%21%21"), "_asParser", [])).klass === smalltalk.Number) ? $receiver /smalltalk.send(smalltalk.send(smalltalk.send(unescape("%21"), "_asParser", []), "_not", []), "__comma", [smalltalk.send((smalltalk.PPAnyParser || PPAnyParser), "_new", [])]) : smalltalk.send($receiver, "__slash", [smalltalk.send(smalltalk.send(smalltalk.send(unescape("%21"), "_asParser", []), "_not", []), "__comma", [smalltalk.send((smalltalk.PPAnyParser || PPAnyParser), "_new", [])])]), "_plus", []), "_flatten", [])]), "__comma", [smalltalk.send(unescape("%21"), "_asParser", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send((smalltalk.Chunk || Chunk), "_new", []), "_contents_", [smalltalk.send(smalltalk.send(smalltalk.send(node, "_second", []), "_replace_with_", [unescape("%21%21"), unescape("%21")]), "_trimBoth", [])]);})]);})() : $receiver;
-return self;}
-}),
-smalltalk.ChunkParser);
-
-smalltalk.addMethod(
-'_emptyChunk',
-smalltalk.method({
-selector: 'emptyChunk',
-fn: function (){
-var self=this;
-return (($receiver = self['@emptyChunk']) == nil || $receiver == undefined) ? (function(){return self['@emptyChunk']=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(self, "_separator", []), "_plus", []), "__comma", [smalltalk.send(unescape("%21"), "_asParser", [])]), "__comma", [smalltalk.send(self, "_ws", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send((smalltalk.EmptyChunk || EmptyChunk), "_new", []);})]);})() : $receiver;
-return self;}
-}),
-smalltalk.ChunkParser);
-
-smalltalk.addMethod(
-'_instructionChunk',
-smalltalk.method({
-selector: 'instructionChunk',
-fn: function (){
-var self=this;
-return (($receiver = self['@instructionChunk']) == nil || $receiver == undefined) ? (function(){return self['@instructionChunk']=smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send(self, "_ws", []), "__comma", [smalltalk.send(unescape("%21"), "_asParser", [])]), "__comma", [smalltalk.send(self, "_chunk", [])]), "__eq_eq_gt", [(function(node){return smalltalk.send(smalltalk.send((smalltalk.InstructionChunk || InstructionChunk), "_new", []), "_contents_", [smalltalk.send(smalltalk.send(node, "_last", []), "_contents", [])]);})]);})() : $receiver;
-return self;}
-}),
-smalltalk.ChunkParser);
-
-
-
-smalltalk.addClass('Importer', smalltalk.Object, ['chunkParser'], 'Parser');
-smalltalk.addMethod(
-'_chunkParser',
-smalltalk.method({
-selector: 'chunkParser',
-fn: function (){
-var self=this;
-return (($receiver = self['@chunkParser']) == nil || $receiver == undefined) ? (function(){return self['@chunkParser']=smalltalk.send(smalltalk.send((smalltalk.ChunkParser || ChunkParser), "_new", []), "_parser", []);})() : $receiver;
-return self;}
-}),
-smalltalk.Importer);
-
-smalltalk.addMethod(
-'_import_',
-smalltalk.method({
-selector: 'import:',
-fn: function (aStream){
-var self=this;
-try{var nextChunk=nil;
-var result=nil;
-(function(){while(!(function(){return smalltalk.send(aStream, "_atEnd", []);})()) {(function(){nextChunk=smalltalk.send(smalltalk.send(self, "_chunkParser", []), "_parse_", [aStream]);(($receiver = nextChunk) == nil || $receiver == undefined) ? (function(){return (function(){throw({name: 'stReturn', selector: '_import_', fn: function(){return self}})})();})() : $receiver;result=smalltalk.send(smalltalk.send((smalltalk.Compiler || Compiler), "_new", []), "_loadExpression_", [smalltalk.send(nextChunk, "_contents", [])]);return (($receiver = smalltalk.send(nextChunk, "_isInstructionChunk", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(result, "_scanFrom_", [aStream]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(result, "_scanFrom_", [aStream]);})]);})()}})();
-return self;
-} catch(e) {if(e.name === 'stReturn' && e.selector === '_import_'){return e.fn()} throw(e)}}
-}),
-smalltalk.Importer);
-
-
-
-smalltalk.addClass('Exporter', smalltalk.Object, [], 'Parser');
-smalltalk.addMethod(
-'_exportCategory_',
-smalltalk.method({
-selector: 'exportCategory:',
-fn: function (aString){
-var self=this;
-var stream=nil;
-stream=smalltalk.send("", "_writeStream", []);
-smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_select_", [(function(each){return smalltalk.send(smalltalk.send(each, "_category", []), "__eq", [aString]);})]), "_do_", [(function(each){return smalltalk.send(stream, "_nextPutAll_", [smalltalk.send(self, "_export_", [each])]);})]);
-smalltalk.send(self, "_exportCategoryExtensions_on_", [aString, stream]);
-return smalltalk.send(stream, "_contents", []);
-return self;}
-}),
-smalltalk.Exporter);
-
-smalltalk.addMethod(
-'_export_',
-smalltalk.method({
-selector: 'export:',
-fn: function (aClass){
-var self=this;
-var stream=nil;
-stream=smalltalk.send("", "_writeStream", []);
-smalltalk.send(self, "_exportDefinitionOf_on_", [aClass, stream]);
-smalltalk.send(self, "_exportMethodsOf_on_", [aClass, stream]);
-smalltalk.send(self, "_exportMetaDefinitionOf_on_", [aClass, stream]);
-smalltalk.send(self, "_exportMethodsOf_on_", [smalltalk.send(aClass, "_class", []), stream]);
-return smalltalk.send(stream, "_contents", []);
-return self;}
-}),
-smalltalk.Exporter);
-
-smalltalk.addMethod(
-'_exportDefinitionOf_on_',
-smalltalk.method({
-selector: 'exportDefinitionOf:on:',
-fn: function (aClass, aStream){
-var self=this;
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addClass%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%27%2C%20")])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%2C%20%5B")]);})(aStream);
-smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C%20")]);})]);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D%2C%20%27")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(aClass, "_category", []), "__comma", [unescape("%27")])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);})(aStream);
-(($receiver = smalltalk.send(smalltalk.send(aClass, "_comment", []), "_notEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", ["smalltalk."]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [aClass])]);smalltalk.send($rec, "_nextPutAll_", [unescape(".comment%3D")]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aClass, "_comment", []), "_escaped", [])]), "__comma", [unescape("%27%29")])]);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", ["smalltalk."]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [aClass])]);smalltalk.send($rec, "_nextPutAll_", [unescape(".comment%3D")]);return smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aClass, "_comment", []), "_escaped", [])]), "__comma", [unescape("%27%29")])]);})(aStream);})]);
-smalltalk.send(aStream, "_lf", []);
-return self;}
-}),
-smalltalk.Exporter);
-
-smalltalk.addMethod(
-'_exportMetaDefinitionOf_on_',
-smalltalk.method({
-selector: 'exportMetaDefinitionOf:on:',
-fn: function (aClass, aStream){
-var self=this;
-(($receiver = smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape(".iVarNames%20%3D%20%5B")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(unescape("%5D%3B"), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])])]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape(".iVarNames%20%3D%20%5B")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(unescape("%5D%3B"), "__comma", [smalltalk.send((smalltalk.String || String), "_lf", [])])]);})]);
-return self;}
-}),
-smalltalk.Exporter);
-
-smalltalk.addMethod(
-'_exportMethodsOf_on_',
-smalltalk.method({
-selector: 'exportMethodsOf:on:',
-fn: function (aClass, aStream){
-var self=this;
-smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_methodDictionary", []), "_values", []), "_do_", [(function(each){return (($receiver = smalltalk.send(smalltalk.send(each, "_category", []), "_match_", [unescape("%5E%5C*")])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);})]);
-smalltalk.send(aStream, "_lf", []);
-return self;}
-}),
-smalltalk.Exporter);
-
-smalltalk.addMethod(
-'_classNameFor_',
-smalltalk.method({
-selector: 'classNameFor:',
-fn: function (aClass){
-var self=this;
-return (($receiver = smalltalk.send(aClass, "_isMetaclass", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [".klass"]);})() : (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [".klass"]);}), (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})]);
-return self;}
-}),
-smalltalk.Exporter);
-
-smalltalk.addMethod(
-'_exportMethod_of_on_',
-smalltalk.method({
-selector: 'exportMethod:of:on:',
-fn: function (aMethod, aClass, aStream){
-var self=this;
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addMethod%28")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_selector", []), "_asSelector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.method%28%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("selector%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_selector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("category%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_category", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send("fn: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_fn", []), "_compiledSource", [])]), "__comma", [unescape("%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("source%3A%20unescape%28%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_source", []), "_escaped", [])]), "__comma", [unescape("%27%29%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send("messageSends: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_messageSends", []), "_asJavascript", [])]), "__comma", [unescape("%2C")])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("referencedClasses%3A%20%5B")]);})(aStream);
-smalltalk.send(smalltalk.send(aMethod, "_referencedClasses", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [each])])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C")]);})]);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("%7D%29%2C")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
-return self;}
-}),
-smalltalk.Exporter);
-
-smalltalk.addMethod(
-'_exportCategoryExtensions_on_',
-smalltalk.method({
-selector: 'exportCategoryExtensions:on:',
-fn: function (aString, aStream){
-var self=this;
-smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_collect_", [(function(each){return smalltalk.send(each, "_class", []);})])]), "_do_", [(function(each){return smalltalk.send(smalltalk.send(smalltalk.send(each, "_methodDictionary", []), "_values", []), "_do_", [(function(method){return (($receiver = smalltalk.send(smalltalk.send(method, "_category", []), "__eq", [smalltalk.send(unescape("*"), "__comma", [aString])])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self, "_exportMethod_of_on_", [method, each, aStream]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(self, "_exportMethod_of_on_", [method, each, aStream]);})]);})]);})]);
-return self;}
-}),
-smalltalk.Exporter);
-
-
-
-smalltalk.addClass('ChunkExporter', smalltalk.Exporter, [], 'Parser');
-smalltalk.addMethod(
-'_exportDefinitionOf_on_',
-smalltalk.method({
-selector: 'exportDefinitionOf:on:',
-fn: function (aClass, aStream){
-var self=this;
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(unescape("%20subclass%3A%20%23"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("%09instanceVariableNames%3A%20%27")]);})(aStream);
-smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%09category%3A%20%27"), "__comma", [smalltalk.send(aClass, "_category", [])]), "__comma", [unescape("%27%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);
-(($receiver = smalltalk.send(smalltalk.send(aClass, "_comment", []), "_notEmpty", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%20commentStamp%21")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aClass, "_comment", [])]), "__comma", [unescape("%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return (function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%21"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%20commentStamp%21")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aClass, "_comment", [])]), "__comma", [unescape("%21")])]);return smalltalk.send($rec, "_lf", []);})(aStream);})]);
-smalltalk.send(aStream, "_lf", []);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-smalltalk.addMethod(
-'_exportMethod_of_on_',
-smalltalk.method({
-selector: 'exportMethod:of:on:',
-fn: function (aMethod, aClass, aStream){
-var self=this;
-(function($rec){smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_chunkEscape_", [smalltalk.send(aMethod, "_source", [])])]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_nextPutAll_", [unescape("%21")]);})(aStream);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-smalltalk.addMethod(
-'_exportMethodsOf_on_',
-smalltalk.method({
-selector: 'exportMethodsOf:on:',
-fn: function (aClass, aStream){
-var self=this;
-smalltalk.send(aClass, "_protocolsDo_", [(function(category, methods){return (($receiver = smalltalk.send(category, "_match_", [unescape("%5E%5C*")])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, aClass, aStream]);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, aClass, aStream]);})]);})]);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-smalltalk.addMethod(
-'_exportMetaDefinitionOf_on_',
-smalltalk.method({
-selector: 'exportMetaDefinitionOf:on:',
-fn: function (aClass, aStream){
-var self=this;
-(($receiver = smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_isEmpty", [])).klass === smalltalk.Boolean) ? (! $receiver ? (function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%20instanceVariableNames%3A%20%27")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);return (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);})() : nil) : smalltalk.send($receiver, "_ifFalse_", [(function(){(function($rec){smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_class", [])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%20instanceVariableNames%3A%20%27")]);})(aStream);smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_class", []), "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [each]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [" "]);})]);return (function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%27%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);})]);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-smalltalk.addMethod(
-'_classNameFor_',
-smalltalk.method({
-selector: 'classNameFor:',
-fn: function (aClass){
-var self=this;
-return (($receiver = smalltalk.send(aClass, "_isMetaclass", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [" class"]);})() : (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return smalltalk.send(smalltalk.send(smalltalk.send(aClass, "_instanceClass", []), "_name", []), "__comma", [" class"]);}), (function(){return (($receiver = smalltalk.send(aClass, "_isNil", [])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return "nil";})() : (function(){return smalltalk.send(aClass, "_name", []);})()) : smalltalk.send($receiver, "_ifTrue_ifFalse_", [(function(){return "nil";}), (function(){return smalltalk.send(aClass, "_name", []);})]);})]);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-smalltalk.addMethod(
-'_chunkEscape_',
-smalltalk.method({
-selector: 'chunkEscape:',
-fn: function (aString){
-var self=this;
-return smalltalk.send(smalltalk.send(aString, "_replace_with_", [unescape("%21"), unescape("%21%21")]), "_trimBoth", []);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-smalltalk.addMethod(
-'_exportCategoryExtensions_on_',
-smalltalk.method({
-selector: 'exportCategoryExtensions:on:',
-fn: function (aString, aStream){
-var self=this;
-smalltalk.send(smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "__comma", [smalltalk.send(smalltalk.send(smalltalk.send((smalltalk.Smalltalk || Smalltalk), "_current", []), "_classes", []), "_collect_", [(function(each){return smalltalk.send(each, "_class", []);})])]), "_do_", [(function(each){return smalltalk.send(each, "_protocolsDo_", [(function(category, methods){return (($receiver = smalltalk.send(category, "__eq", [smalltalk.send(unescape("*"), "__comma", [aString])])).klass === smalltalk.Boolean) ? ($receiver ? (function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, each, aStream]);})() : nil) : smalltalk.send($receiver, "_ifTrue_", [(function(){return smalltalk.send(self, "_exportMethods_category_of_on_", [methods, category, each, aStream]);})]);})]);})]);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-smalltalk.addMethod(
-'_exportMethods_category_of_on_',
-smalltalk.method({
-selector: 'exportMethods:category:of:on:',
-fn: function (methods, category, aClass, aStream){
-var self=this;
-(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(methods, "_do_", [(function(each){return smalltalk.send(self, "_exportMethod_of_on_", [each, aClass, aStream]);})]);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%20%21")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
-return self;}
-}),
-smalltalk.ChunkExporter);
-
-
-
-smalltalk.addClass('StrippedExporter', smalltalk.Exporter, [], 'Parser');
-smalltalk.addMethod(
-'_exportDefinitionOf_on_',
-smalltalk.method({
-selector: 'exportDefinitionOf:on:',
-fn: function (aClass, aStream){
-var self=this;
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addClass%28")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])]), "__comma", [unescape("%27%2C%20")])]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [smalltalk.send(aClass, "_superclass", [])])])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%2C%20%5B")]);})(aStream);
-smalltalk.send(smalltalk.send(aClass, "_instanceVariableNames", []), "_do_separatedBy_", [(function(each){return smalltalk.send(aStream, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [each]), "__comma", [unescape("%27")])]);}), (function(){return smalltalk.send(aStream, "_nextPutAll_", [unescape("%2C%20")]);})]);
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("%5D%2C%20%27")]);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(aClass, "_category", []), "__comma", [unescape("%27")])]);return smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);})(aStream);
-smalltalk.send(aStream, "_lf", []);
-return self;}
-}),
-smalltalk.StrippedExporter);
-
-smalltalk.addMethod(
-'_exportMethod_of_on_',
-smalltalk.method({
-selector: 'exportMethod:of:on:',
-fn: function (aMethod, aClass, aStream){
-var self=this;
-(function($rec){smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.addMethod%28")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("%27"), "__comma", [smalltalk.send(smalltalk.send(aMethod, "_selector", []), "_asSelector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("smalltalk.method%28%7B")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send(smalltalk.send(unescape("selector%3A%20%27"), "__comma", [smalltalk.send(aMethod, "_selector", [])]), "__comma", [unescape("%27%2C")])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("fn: ", "__comma", [smalltalk.send(smalltalk.send(aMethod, "_fn", []), "_compiledSource", [])])]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [unescape("%7D%29%2C")]);smalltalk.send($rec, "_lf", []);smalltalk.send($rec, "_nextPutAll_", [smalltalk.send("smalltalk.", "__comma", [smalltalk.send(self, "_classNameFor_", [aClass])])]);smalltalk.send($rec, "_nextPutAll_", [unescape("%29%3B")]);smalltalk.send($rec, "_lf", []);return smalltalk.send($rec, "_lf", []);})(aStream);
-return self;}
-}),
-smalltalk.StrippedExporter);
-
-
-

Tiedoston diff-näkymää rajattu, sillä se on liian suuri
+ 0 - 1088
js/Parser.js


+ 6 - 11
js/boot.js

@@ -209,7 +209,7 @@ function Smalltalk(){
        If the receiver does not understand the selector, call its #doesNotUnderstand: method */
 
     sendWithoutContext = function(receiver, selector, args, klass) {
-	if(typeof receiver === "undefined") {
+	if(receiver === undefined || receiver === null) {
 	    receiver = nil;
 	}
 	if(!klass && receiver.klass && receiver[selector]) {
@@ -244,7 +244,7 @@ function Smalltalk(){
 
     withContextSend = function(receiver, selector, args, klass) {
 	var call, context;
-	if(typeof receiver === "undefined") {
+	if(receiver === undefined || receiver === null) {
 	    receiver = nil;
 	}
 	if(!klass && receiver.klass && receiver[selector]) {
@@ -290,7 +290,8 @@ function Smalltalk(){
     };
 
     function callJavaScriptMethod(receiver, selector, args) {
-	/* Call a method of a JS object, or answer a property.
+	/* Call a method of a JS object, or answer a property if it exists.
+	   Else try wrapping a JSObjectProxy around the receiver.
  
 	   Converts keyword-based selectors by using the first
 	   keyword only, but keeping all message arguments.
@@ -312,7 +313,8 @@ function Smalltalk(){
 		return jsProperty
 	    }
 	}
-	smalltalk.Error._signal_(receiver + ' is not a Jtalk object and "' + jsSelector + '" is undefined')
+	
+	return st.send(st.JSObjectProxy._on_(receiver), selector, args);
     };
 
 
@@ -432,13 +434,6 @@ var nil = new SmalltalkNil();
 var smalltalk = new Smalltalk();
 var thisContext = undefined;
 
-/* Utilities */
-
-Array.prototype.remove = function(s){
-    var index = this.indexOf(s);
-    if(this.indexOf(s) != -1)this.splice(index, 1);
-}
-
 if(this.jQuery) {
     this.jQuery.allowJavaScriptCalls = true;
 }

+ 0 - 2
js/jtalk.js

@@ -26,7 +26,6 @@
 
     function loadIDEDependencies() {
 	loadJS('lib/jQuery/jquery.textarea.js');
-	loadJS('lib/jQuery/jQuery.twFile.js');
 	loadJS('lib/CodeMirror/lib/codemirror.js');
 	loadCSS('lib/CodeMirror/lib/codemirror.css', 'js');
 	loadJS('lib/CodeMirror/mode/smalltalk/smalltalk.js');
@@ -42,7 +41,6 @@
 	loadJS("Kernel.js");
 	loadJS("Canvas.js");
 	loadJS("JQuery.js");
-	loadJS("Parser.js");
 	loadJS("Compiler.js");
 	loadJS("parser.js");
 	loadJS("IDE.js");

+ 1 - 1
js/parser.js

@@ -945,7 +945,7 @@ smalltalk.parser = (function(){
           pos = savedPos1;
         }
         var result2 = result1 !== null
-          ? (function(neg, digits) {return (parseInt(neg+digits, 10))})(result1[0], result1[1])
+          ? (function(neg, digits) {return (parseInt(neg+digits.join(""), 10))})(result1[0], result1[1])
           : null;
         if (result2 !== null) {
           var result0 = result2;

+ 1 - 1
js/parser.pegjs

@@ -20,7 +20,7 @@ number         = n:(float / integer) {
                	   	._value_(n)
                	 }
 float          = neg:[-]?int:integer "." dec:integer {return parseFloat((neg+int+"."+dec), 10)}
-integer        = neg:[-]?digits:[0-9]+ {return (parseInt(neg+digits, 10))}
+integer        = neg:[-]?digits:[0-9]+ {return (parseInt(neg+digits.join(""), 10))}
 literalArray   = "#(" ws lits:(lit:literal ws {return lit._value()})* ws ")" {
 		  return smalltalk.ValueNode._new()
                	   	._value_(lits)

+ 295 - 5
st/Compiler.st

@@ -1,3 +1,298 @@
+Object subclass: #ChunkParser
+	instanceVariableNames: 'stream'
+	category: 'Compiler'!
+
+!ChunkParser methodsFor: 'accessing'!
+
+stream: aStream
+	stream := aStream
+! !
+
+!ChunkParser methodsFor: 'reading'!
+
+nextChunk
+	"The chunk format (Smalltalk Interchange Format or Fileout format)
+	is a trivial format but can be a bit tricky to understand:
+		- Uses the exclamation mark as delimiter of chunks.
+		- Inside a chunk a normal exclamation mark must be doubled.
+		- A non empty chunk must be a valid Smalltalk expression.
+		- A chunk on top level with a preceding empty chunk is an instruction chunk:
+			- The object created by the expression then takes over reading chunks.
+
+	This metod returns next chunk as a String (trimmed), empty String (all whitespace) or nil."
+
+	| char result chunk |
+	result := '' writeStream.
+        [char := stream next.
+        char notNil] whileTrue: [
+                 char = '!!' ifTrue: [
+                         stream peek = '!!'
+                                ifTrue: [stream next "skipping the escape double"]
+                                ifFalse: [^result contents trimBoth  "chunk end marker found"]].
+                 result nextPut: char].
+	^nil "a chunk needs to end with !!"
+! !
+
+!ChunkParser class methodsFor: 'not yet classified'!
+
+on: aStream
+	^self new stream: aStream
+! !
+
+Object subclass: #Importer
+	instanceVariableNames: ''
+	category: 'Compiler'!
+
+!Importer methodsFor: 'fileIn'!
+
+import: aStream
+    | chunk result parser lastEmpty |
+    parser := ChunkParser on: aStream.
+    lastEmpty := false.
+    [chunk := parser nextChunk.
+     chunk isNil] whileFalse: [
+        chunk isEmpty
+       		ifTrue: [lastEmpty := true]
+       		ifFalse: [
+        		result := Compiler new loadExpression: chunk.
+        		lastEmpty 
+            			ifTrue: [
+                                  	lastEmpty := false.
+                                  	result scanFrom: parser]]]
+! !
+
+Object subclass: #Exporter
+	instanceVariableNames: ''
+	category: 'Compiler'!
+
+!Exporter methodsFor: 'fileOut'!
+
+exportCategory: aString
+	| stream |
+	stream := '' writeStream.
+	(Smalltalk current classes 
+	    select: [:each | each category = aString])
+	    do: [:each | stream nextPutAll: (self export: each)].
+	self exportCategoryExtensions: aString on: stream.
+	^stream contents
+!
+
+export: aClass
+	| stream |
+	stream := '' writeStream.
+	self exportDefinitionOf: aClass on: stream.
+	self exportMethodsOf: aClass on: stream.
+	self exportMetaDefinitionOf: aClass on: stream.
+	self exportMethodsOf: aClass class on: stream.
+	^stream contents
+! !
+
+!Exporter methodsFor: 'private'!
+
+exportDefinitionOf: aClass on: aStream
+	aStream 
+	    nextPutAll: 'smalltalk.addClass(';
+	    nextPutAll: '''', (self classNameFor: aClass), ''', ';
+	    nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
+	    nextPutAll: ', ['.
+	aClass instanceVariableNames 
+	    do: [:each | aStream nextPutAll: '''', each, '''']
+	    separatedBy: [aStream nextPutAll: ', '].
+	aStream	
+	    nextPutAll: '], ''';
+	    nextPutAll: aClass category, '''';
+	    nextPutAll: ');'.
+	aClass comment notEmpty ifTrue: [
+	    aStream 
+	    	lf;
+		nextPutAll: 'smalltalk.';
+		nextPutAll: (self classNameFor: aClass);
+		nextPutAll: '.comment=';
+		nextPutAll: 'unescape(''', aClass comment escaped, ''')'].
+	aStream lf
+!
+
+exportMetaDefinitionOf: aClass on: aStream
+	aClass class instanceVariableNames isEmpty ifFalse: [
+	    aStream 
+		nextPutAll: 'smalltalk.', (self classNameFor: aClass class);
+		nextPutAll: '.iVarNames = ['.
+	    aClass class instanceVariableNames
+		do: [:each | aStream nextPutAll: '''', each, '''']
+		separatedBy: [aStream nextPutAll: ','].
+	    aStream nextPutAll: '];', String lf]
+!
+
+exportMethodsOf: aClass on: aStream
+	aClass methodDictionary values do: [:each |
+		(each category match: '^\*') ifFalse: [
+			self exportMethod: each of: aClass on: aStream]].
+	aStream lf
+!
+
+classNameFor: aClass
+	^aClass isMetaclass
+	    ifTrue: [aClass instanceClass name, '.klass']
+	    ifFalse: [
+		aClass isNil
+		    ifTrue: ['nil']
+		    ifFalse: [aClass name]]
+!
+
+exportMethod: aMethod of: aClass on: aStream
+	aStream 
+		nextPutAll: 'smalltalk.addMethod(';lf;
+		nextPutAll: '''', aMethod selector asSelector, ''',';lf;
+		nextPutAll: 'smalltalk.method({';lf;
+		nextPutAll: 'selector: ''', aMethod selector, ''',';lf;
+		nextPutAll: 'category: ''', aMethod category, ''',';lf;
+		nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
+		nextPutAll: 'source: unescape(''', aMethod source escaped, '''),';lf;
+		nextPutAll: 'messageSends: ', aMethod messageSends asJavascript, ',';lf;
+		nextPutAll: 'referencedClasses: ['.
+	    		aMethod referencedClasses 
+				do: [:each | aStream nextPutAll: 'smalltalk.', (self classNameFor: each)]
+				separatedBy: [aStream nextPutAll: ','].
+	aStream
+		nextPutAll: ']';lf;
+		nextPutAll: '}),';lf;
+		nextPutAll: 'smalltalk.', (self classNameFor: aClass);
+		nextPutAll: ');';lf;lf
+!
+
+exportCategoryExtensions: aString on: aStream
+	Smalltalk current classes, (Smalltalk current classes collect: [:each | each class]) do: [:each |
+		each methodDictionary values do: [:method |
+			method category = ('*', aString) ifTrue: [
+				self exportMethod: method of: each on: aStream]]]
+! !
+
+Exporter subclass: #ChunkExporter
+	instanceVariableNames: ''
+	category: 'Compiler'!
+
+!ChunkExporter methodsFor: 'not yet classified'!
+
+exportDefinitionOf: aClass on: aStream
+	"Chunk format."
+
+	aStream 
+	    nextPutAll: (self classNameFor: aClass superclass);
+	    nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
+	    nextPutAll: '	instanceVariableNames: '''.
+	aClass instanceVariableNames 
+	    do: [:each | aStream nextPutAll: each]
+	    separatedBy: [aStream nextPutAll: ' '].
+	aStream	
+	    nextPutAll: ''''; lf;
+	    nextPutAll: '	category: ''', aClass category, '''!!'; lf.
+ 	aClass comment notEmpty ifTrue: [
+	    aStream 
+		nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
+		nextPutAll: (self chunkEscape: aClass comment), '!!';lf].
+	aStream lf
+!
+
+exportMethod: aMethod of: aClass on: aStream
+	aStream 
+		lf; lf; nextPutAll: (self chunkEscape: aMethod source); lf;
+		nextPutAll: '!!'
+!
+
+exportMethodsOf: aClass on: aStream
+
+   aClass protocolsDo: [:category :methods |
+	(category match: '^\*') ifFalse: [ 
+		self
+			exportMethods: methods
+			category: category
+			of: aClass
+			on: aStream]]
+!
+
+exportMetaDefinitionOf: aClass on: aStream
+
+	aClass class instanceVariableNames isEmpty ifFalse: [
+		aStream 
+		    nextPutAll: (self classNameFor: aClass class);
+		    nextPutAll: ' instanceVariableNames: '''.
+		aClass class instanceVariableNames 
+		    do: [:each | aStream nextPutAll: each]
+		    separatedBy: [aStream nextPutAll: ' '].
+		aStream	
+		    nextPutAll: '''!!'; lf; lf]
+!
+
+classNameFor: aClass
+	^aClass isMetaclass
+	    ifTrue: [aClass instanceClass name, ' class']
+	    ifFalse: [
+		aClass isNil
+		    ifTrue: ['nil']
+		    ifFalse: [aClass name]]
+!
+
+chunkEscape: aString
+	"Replace all occurrences of !! with !!!! and trim at both ends."
+
+	^(aString replace: '!!' with: '!!!!') trimBoth
+!
+
+exportCategoryExtensions: aString on: aStream
+	"We need to override this one too since we need to group
+	all methods in a given protocol under a leading methodsFor: chunk
+	for that class."
+
+	Smalltalk current classes, (Smalltalk current classes collect: [:each | each class]) do: [:each |
+		each protocolsDo: [:category :methods |
+			category = ('*', aString) ifTrue: [
+				self exportMethods: methods category: category of: each on: aStream]]]
+!
+
+exportMethods: methods category: category of: aClass on: aStream
+
+	aStream
+		nextPutAll: '!!', (self classNameFor: aClass);
+		nextPutAll: ' methodsFor: ''', category, '''!!'.
+    	methods do: [:each |
+		self exportMethod: each of: aClass on: aStream].
+	aStream nextPutAll: ' !!'; lf; lf
+! !
+
+Exporter subclass: #StrippedExporter
+	instanceVariableNames: ''
+	category: 'Compiler'!
+
+!StrippedExporter methodsFor: 'private'!
+
+exportDefinitionOf: aClass on: aStream
+	aStream 
+	    nextPutAll: 'smalltalk.addClass(';
+	    nextPutAll: '''', (self classNameFor: aClass), ''', ';
+	    nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
+	    nextPutAll: ', ['.
+	aClass instanceVariableNames 
+	    do: [:each | aStream nextPutAll: '''', each, '''']
+	    separatedBy: [aStream nextPutAll: ', '].
+	aStream	
+	    nextPutAll: '], ''';
+	    nextPutAll: aClass category, '''';
+	    nextPutAll: ');'.
+	aStream lf
+!
+
+exportMethod: aMethod of: aClass on: aStream
+	aStream 
+		nextPutAll: 'smalltalk.addMethod(';lf;
+		nextPutAll: '''', aMethod selector asSelector, ''',';lf;
+		nextPutAll: 'smalltalk.method({';lf;
+		nextPutAll: 'selector: ''', aMethod selector, ''',';lf;
+		nextPutAll: 'fn: ', aMethod fn compiledSource;lf;
+		nextPutAll: '}),';lf;
+		nextPutAll: 'smalltalk.', (self classNameFor: aClass);
+		nextPutAll: ');';lf;lf
+! !
+
 Object subclass: #Node
 	instanceVariableNames: 'nodes'
 	category: 'Compiler'!
@@ -1044,8 +1339,3 @@ Object subclass: #DoIt
 	instanceVariableNames: ''
 	category: 'Compiler'!
 
-!DoIt methodsFor: ''!
-
-
-! !
-

+ 54 - 26
st/Kernel.st

@@ -170,7 +170,7 @@ printNl
 log: aString block: aBlock
 
 	| result |
-	"console log:"  aString,  ' time: ', (Date millisecondsToRun: [result := aBlock value]) printString.
+	console log:  aString,  ' time: ', (Date millisecondsToRun: [result := aBlock value]) printString.
 	^result
 ! !
 
@@ -792,19 +792,10 @@ new
 	"Use the receiver as a JS constructor. 
 	*Do not* use this method to instanciate Smalltalk objects!!"
 	<return new self()>
-! !
-
-!BlockClosure methodsFor: 'printing'!
+!
 
-printString
-	^ String streamContents: [:aStream| 
-                                  aStream 
-                                  	nextPutAll: super printString;
-                                  	nextPutAll: '(';
-                                  	nextPutAll: self compiledSource;
-                                  	nextPutAll: ')';
-                                  	cr.
-           ]
+applyTo: anObject arguments: aCollection
+	<return self.apply(anObject, aCollection)>
 ! !
 
 !BlockClosure methodsFor: 'timeout/interval'!
@@ -2179,13 +2170,11 @@ class: aClass category: aString
 
 !ClassCategoryReader methodsFor: 'fileIn'!
 
-scanFrom: aStream
-	| nextChunk par |
-	self log: 'nextChunk build' block: [par := (chunkParser emptyChunk / chunkParser chunk)].
-	self log: 'nextChunk' block: [nextChunk := par parse: aStream].
-	nextChunk isEmptyChunk ifFalse: [
-	    self compileMethod: nextChunk contents.
-	    self scanFrom: aStream].
+scanFrom: aChunkParser
+	| chunk |
+	[chunk := aChunkParser nextChunk.
+	chunk isEmpty] whileFalse: [
+	    self compileMethod: chunk]
 ! !
 
 !ClassCategoryReader methodsFor: 'initialization'!
@@ -2201,7 +2190,7 @@ compileMethod: aString
 	| method |
 	method := Compiler new load: aString forClass: class.
 	method category: category.
-	self log: 'addCompiledMethod' block: [class addCompiledMethod: method]
+	class addCompiledMethod: method
 ! !
 
 Object subclass: #Stream
@@ -2392,11 +2381,11 @@ class: aClass
 
 !ClassCommentReader methodsFor: 'fileIn'!
 
-scanFrom: aStream
-	| nextChunk |
-	nextChunk := (chunkParser emptyChunk / chunkParser chunk) parse: aStream.
-	nextChunk isEmptyChunk ifFalse: [
-	    self setComment: nextChunk contents].
+scanFrom: aChunkParser
+	| chunk |
+	chunk := aChunkParser nextChunk.
+	chunk isEmpty ifFalse: [
+	    self setComment: chunk].
 ! !
 
 !ClassCommentReader methodsFor: 'initialization'!
@@ -2593,3 +2582,42 @@ register
 	ErrorHandler setCurrent: self new
 ! !
 
+Object subclass: #JSObjectProxy
+	instanceVariableNames: 'jsObject'
+	category: 'Kernel'!
+
+!JSObjectProxy methodsFor: 'accessing'!
+
+jsObject: aJSObject
+	jsObject := aJSObject
+!
+
+jsObject
+	^jsObject
+! !
+
+!JSObjectProxy methodsFor: 'proxy'!
+
+printString
+	^self jsObject toString
+!
+
+inspectOn: anInspector
+	| variables |
+	variables := Dictionary new.
+	variables at: '#self' put: self jsObject.
+	anInspector setLabel: self printString.
+	<for(var i in self['@jsObject']) {
+		variables._at_put_(i, self['@jsObject'][i]);
+	}>.
+	anInspector setVariables: variables
+! !
+
+!JSObjectProxy class methodsFor: 'instance creation'!
+
+on: aJSObject
+	^self new
+		jsObject: aJSObject;
+		yourself
+! !
+

+ 4 - 9
st/Makefile

@@ -12,7 +12,7 @@ JTALKC	:= ../bin/jtalkc
 FLAGS   := -d
 
 # All corresponding js filenames for every st file available
-# In other words, if we have Kernel.st and Parser.st, then OBJECTS will be "Kernel.js Parser.js"
+# In other words, if we have Kernel.st and Compiler.st, then OBJECTS will be "Kernel.js Compiler.js"
 OBJECTS := $(patsubst %.st,%.js,$(wildcard *.st))
 
 # Default make target since it is the first target in this Makefile
@@ -30,14 +30,9 @@ boot.js init.js:
 Kernel.js: Kernel.st boot.js init.js
 	$(JTALKC) $(FLAGS) $<
 
-# ...then Parser, but using the new Kernel from step above.
-# We only need to depend on Kernel.js since it in turn depends on boot.js and init.js.
-Parser.js: Parser.st Kernel.js
-	$(JTALKC) $(FLAGS) $<
-
-# ...and Compiler, but using the new Parser and Kernel from above.
-# We only need to depend on Parser.js since it in turn depends on Kernel.js, boot.js etc
-Compiler.js: Compiler.st Parser.js
+# ...and Compiler, but using the new Kernel from above.
+# We only need to depend on Kernel.js since it in turn depends on Kernel.js, boot.js etc
+Compiler.js: Compiler.st Kernel.js
 	$(JTALKC) $(FLAGS) $<
 
 # ...now that we have a new Kernel/Parser/Compiler we use them

+ 0 - 994
st/Parser.st

@@ -1,994 +0,0 @@
-Object subclass: #PPParser
-	instanceVariableNames: 'memo'
-	category: 'Parser'!
-
-!PPParser methodsFor: 'accessing'!
-
-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
-	| r start end node |
-	start := aStream position.
-        self log: 'memoizedParse' block: [r := self memo at: start 
-	    ifPresent: [:value |
-		aStream position: (self memo at: start) second.
-		value first]
-	    ifAbsent: [
-		node := self parse: aStream.
-		end := aStream position.
-		self memo at: start put: (Array with: node with: end).
-		node]].
-	^r
-! !
-
-!PPParser methodsFor: 'parsing'!
-
-parse: aStream
-	self subclassResponsibility
-!
-
-parseAll: aStream
-	| result |
-	result := (PPSequenceParser with: self with: PPEOFParser new) memoizedParse: aStream.
-	^result isParseFailure 
-	    ifTrue: [self error: (result messageFor: aStream contents)]
-	    ifFalse: [result first]
-! !
-
-PPParser subclass: #PPEOFParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPEOFParser methodsFor: 'parsing'!
-
-parse: aStream
-	^aStream atEnd 
-	    ifFalse: [
-		PPFailure new reason: aStream contents, String lf, '---------------', String lf, 'EOF expected' at: aStream position]
-	    ifTrue: [nil]
-! !
-
-PPParser subclass: #PPAnyParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPAnyParser methodsFor: 'parsing'!
-
-parse: aStream
-	^aStream atEnd
-	    ifTrue: [PPFailure new
-			 reason: 'did not expect EOF' at: aStream position]
-	    ifFalse: [aStream next]
-! !
-
-PPParser subclass: #PPEpsilonParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPEpsilonParser methodsFor: 'parsing'!
-
-parse: aStream
-	^nil
-! !
-
-PPParser subclass: #PPStringParser
-	instanceVariableNames: 'string'
-	category: 'Parser'!
-
-!PPStringParser methodsFor: 'accessing'!
-
-string
-	^string
-!
-
-string: aString
-	string := aString
-! !
-
-!PPStringParser methodsFor: 'parsing'!
-
-parse: aStream
-	| position result |
-	position := aStream position.
-	result := aStream next: self string size.
-	^result = self string
-	    ifTrue: [result]
-	    ifFalse: [
-		aStream position: position.
-		PPFailure new reason: 'Expected ', self string, ' but got ', (result at: position) printString; yourself]
-! !
-
-PPParser subclass: #PPCharacterParser
-	instanceVariableNames: 'regexp'
-	category: 'Parser'!
-
-!PPCharacterParser methodsFor: 'accessing'!
-
-string: aString
-	regexp := RegularExpression fromString: '[', aString, ']'
-! !
-
-!PPCharacterParser methodsFor: 'parsing'!
-
-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
-	instanceVariableNames: 'parsers'
-	category: 'Parser'!
-
-!PPListParser methodsFor: 'accessing'!
-
-parsers
-	^parsers ifNil: [#()]
-!
-
-parsers: aCollection
-	parsers := aCollection
-! !
-
-!PPListParser methodsFor: 'copying'!
-
-copyWith: aParser
-	^self class withAll: (self parsers copyWith: aParser)
-! !
-
-!PPListParser class methodsFor: 'instance creation'!
-
-withAll: aCollection
-	    ^self new
-		parsers: aCollection;
-		yourself
-!
-
-with: aParser with: anotherParser
-	    ^self withAll: (Array with: aParser with: anotherParser)
-! !
-
-PPListParser subclass: #PPSequenceParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPSequenceParser methodsFor: 'copying'!
-
-, aRule
-	^self copyWith: aRule
-! !
-
-!PPSequenceParser methodsFor: 'parsing'!
-
-parse: aStream
-	| start elements element |
-	start := aStream position.
-	elements := #().
-	self parsers 
-	    detect: [:each |
-		element := each memoizedParse: aStream.
-		elements add: element.
-		element isParseFailure] 
-	    ifNone: [].
-	^element isParseFailure
-	    ifFalse: [elements]
-	    ifTrue: [aStream position: start. element]
-! !
-
-PPListParser subclass: #PPChoiceParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPChoiceParser methodsFor: 'copying'!
-
-/ aRule
-	^self copyWith: aRule
-! !
-
-!PPChoiceParser methodsFor: 'parsing'!
-
-parse: aStream
-	| result |
-	self parsers
-    	    detect: [:each |
-		result := each memoizedParse: aStream.
-		result isParseFailure not]
-	    ifNone: [].
-	^result
-! !
-
-PPParser subclass: #PPDelegateParser
-	instanceVariableNames: 'parser'
-	category: 'Parser'!
-
-!PPDelegateParser methodsFor: 'accessing'!
-
-parser
-	^parser
-!
-
-parser: aParser
-	parser := aParser
-! !
-
-!PPDelegateParser methodsFor: 'parsing'!
-
-parse: aStream
-	^self parser memoizedParse: aStream
-! !
-
-!PPDelegateParser class methodsFor: 'instance creation'!
-
-on: aParser
-	    ^self new
-		parser: aParser;
-		yourself
-! !
-
-PPDelegateParser subclass: #PPAndParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPAndParser methodsFor: 'parsing'!
-
-parse: aStream
-	^self basicParse: aStream
-!
-
-basicParse: aStream
-	| element position |
-	position := aStream position.
-	element := self parser memoizedParse: aStream.
-	aStream position: position.
-	^element
-! !
-
-PPAndParser subclass: #PPNotParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPNotParser methodsFor: 'parsing'!
-
-parse: aStream
-	| element |
-	element := self basicParse: aStream.
-	^element isParseFailure 
-	    ifTrue: [nil]
-	    ifFalse: [PPFailure reason: element at: aStream position]
-! !
-
-PPDelegateParser subclass: #PPActionParser
-	instanceVariableNames: 'block'
-	category: 'Parser'!
-
-!PPActionParser methodsFor: 'accessing'!
-
-block
-	^block
-!
-
-block: aBlock
-	block := aBlock
-! !
-
-!PPActionParser methodsFor: 'parsing'!
-
-parse: aStream
-	| element |
-	element := self parser memoizedParse: aStream.
-	^element isParseFailure
-	    ifFalse: [self block value: element]
-	    ifTrue: [element]
-! !
-
-!PPActionParser class methodsFor: 'instance creation'!
-
-on: aParser block: aBlock
-	    ^self new
-		parser: aParser;
-		block: aBlock;
-		yourself
-! !
-
-PPDelegateParser subclass: #PPFlattenParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPFlattenParser methodsFor: 'parsing'!
-
-parse: aStream
-	| start element stop |
-	start := aStream position.
-	element := self parser memoizedParse: aStream.
-	^element isParseFailure
-	    ifTrue: [element]
-	    ifFalse: [aStream collection 
-		copyFrom: start + 1 
-		to: aStream position]
-! !
-
-PPDelegateParser subclass: #PPSourceParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!PPSourceParser methodsFor: 'parsing'!
-
-parse: aStream
-	| start element stop result |
-	start := aStream position.
-	element := self parser memoizedParse: aStream.
-	^element isParseFailure
-		ifTrue: [element]
-		ifFalse: [result := aStream collection copyFrom: start + 1 to: aStream position.
-			Array with: element with: result].
-! !
-
-PPDelegateParser subclass: #PPRepeatingParser
-	instanceVariableNames: 'min'
-	category: 'Parser'!
-
-!PPRepeatingParser methodsFor: 'accessing'!
-
-min
-	^min
-!
-
-min: aNumber
-	min := aNumber
-! !
-
-!PPRepeatingParser methodsFor: 'parsing'!
-
-parse: aStream
-	| start element elements failure |
-	start := aStream position.
-	elements := Array new.
-	[(elements size < self min) and: [failure isNil]] whileTrue: [
-	    element := self parser memoizedParse: aStream.
-	    element isParseFailure
-			ifFalse: [elements addLast: element]
-			ifTrue: [aStream position: start.
-				 failure := element]].
-	^failure ifNil: [
-	    [failure isNil] whileTrue: [
-			element := self parser memoizedParse: aStream.
-	 		element isParseFailure
-				ifTrue: [failure := element]
-				ifFalse: [elements addLast: element]].
-				elements]
-		ifNotNil: [failure].
-! !
-
-!PPRepeatingParser class methodsFor: 'instance creation'!
-
-on: aParser min: aNumber
-	    ^self new
-		parser: aParser;
-		min: aNumber;
-		yourself
-! !
-
-Object subclass: #PPFailure
-	instanceVariableNames: 'position reason'
-	category: 'Parser'!
-
-!PPFailure methodsFor: 'accessing'!
-
-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
-	aVisitor visitFailure: self
-! !
-
-!PPFailure methodsFor: 'testing'!
-
-isParseFailure
-	^true
-!
-
-asString
-	^reason, ' at ', position asString
-! !
-
-!PPFailure class methodsFor: 'instance creation'!
-
-reason: aString at: anInteger
-	    ^self new
-		reason: aString at: anInteger;
-		yourself
-! !
-
-Object subclass: #SmalltalkParser
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!SmalltalkParser methodsFor: 'grammar'!
-
-parser
-	| method expression separator comment ws identifier keyword className string symbol number literalArray variable reference classReference literal ret methodParser expressionParser keyword unarySelector binarySelector keywordPattern unaryPattern binaryPattern assignment temps blockParamList block expression expressions subexpression statements sequence operand unaryMessage unarySend unaryTail binaryMessage binarySend binaryTail keywordMessage keywordSend keywordPair cascade message jsStatement |
-	
-	separator := (String cr, String space, String lf, String tab) asChoiceParser.
-	comment := ('"' asCharacterParser, ('"' asParser not, PPAnyParser new) star, '"' asCharacterParser) flatten.
-
-	ws := (separator / comment) star.
-	
-	identifier := ('a-z' asCharacterParser, 'a-zA-Z0-9' asCharacterParser star) flatten.
-
-	keyword := (identifier, ':' asParser) flatten.
-
-	className := ('A-Z' asCharacterParser, 'a-zA-Z0-9' asCharacterParser star) flatten.
-
-	string := '''' asParser, ('''''' asParser / ('''' asParser not, PPAnyParser new)) star flatten, '''' asParser
-		==> [:node | ValueNode new value: ((node at: 2) replace: '''''' with: '''')].
-
-	symbol := '#' asParser, 'a-zA-Z0-9' asCharacterParser plus flatten
-		==> [:node | ValueNode new value: node second].
-
-	number := ('0-9' asCharacterParser plus, ('.' asParser, '0-9' asCharacterParser plus) optional) flatten
-		==> [:node | ValueNode new value: node asNumber].
-
-	literal := PPDelegateParser new.
-
-	literalArray := '#(' asParser, (ws, literal, ws) star, ')' asParser
-		==> [:node | ValueNode new value: (Array withAll: (node second collect: [:each | each second value]))].
-
-	variable := identifier ==> [:token | VariableNode new value: token].
-
-	classReference := className ==> [:token | ClassReferenceNode new value: token].
-
-	reference := variable / classReference.
-
-	binarySelector := '+*/=><,@%~|&-' asCharacterParser plus flatten.
-
-	unarySelector := identifier.
-
-	keywordPattern := (ws, keyword, ws, identifier) plus
-		==> [:nodes | Array
-				  with: ((nodes collect: [:each | each at: 2]) join: '')
-				  with: (nodes collect: [:each | each at: 4])].
-
-	binaryPattern := ws, binarySelector, ws, identifier
-		==> [:node | Array with: node second with: (Array with: node fourth)].
-
-	unaryPattern := ws, unarySelector
-		==> [:node | Array with: node second with: Array new].
-	
-	expression := PPDelegateParser new.
-
-	expressions := expression, ((ws, '.' asParser, ws, expression) ==> [:node | node fourth]) star
-		==> [:node || result |
-		    result := Array with: node first.
-		    node second do: [:each | result add: each].
-		    result].
-
-	assignment := reference, ws, ':=' asParser, ws, expression
-		==> [:node | AssignmentNode new left: node first; right: (node at: 5)].
-
-	ret := '^' asParser, ws, expression, ws, '.' asParser optional
-	    ==> [:node | ReturnNode new
-			     addNode: node third;
-			     yourself].
-
-	temps := '|' asParser, (ws, identifier) star, ws, '|' asParser
-		==> [:node | node second collect: [:each | each second]].
-
-	blockParamList := (':' asParser, identifier, ws) plus, '|' asParser
-		==> [:node | node first collect: [:each | each second]].
-
-	subexpression := '(' asParser, ws, expression, ws, ')' asParser
-		==> [:node | node third].
-
-	statements := (ret ==> [:node | Array with: node]) / (expressions, ws, '.' asParser, ws, ret ==> [:node | node first add: (node at: 5); yourself]) / (expressions , '.' asParser optional ==> [:node | node first]).
-
-	sequence := temps optional, ws, statements optional, ws
-		==> [:node | SequenceNode new
-				 temps: node first;
-				 nodes: node third;
-				 yourself].
-
-	block := '[' asParser, ws, blockParamList optional, ws, sequence optional, ws, ']' asParser
-		==> [:node |
-		    BlockNode new
-			parameters: node third;
-			addNode: (node at: 5) asBlockSequenceNode].
-
-	operand := literal / reference / subexpression.
-
-	literal parser: number / string / literalArray / symbol / block.
-
-	unaryMessage := ws, unarySelector, ':' asParser not
-		==> [:node | SendNode new selector: node second].
-
-	unaryTail := PPDelegateParser new.
-	unaryTail parser: (unaryMessage, unaryTail optional
-			       ==> [:node |
-				   node second
-					   ifNil: [node first]
-					   ifNotNil: [node second valueForReceiver: node first]]).
-
-	unarySend := operand, unaryTail optional
-		==> [:node |
-		    node second 
-			ifNil: [node first]
-			ifNotNil: [node second valueForReceiver: node first]].
-
-	binaryMessage := ws, binarySelector, ws, (unarySend / operand)
-		==> [:node |
-		    SendNode new
-			selector: node second;
-			arguments: (Array with: node fourth)].
-
-	binaryTail := PPDelegateParser new.
-	binaryTail parser: (binaryMessage, binaryTail optional
-				    ==> [:node |
-					node second 
-					    ifNil: [node first]
-					    ifNotNil: [ node second valueForReceiver: node first]]).
-
-	binarySend := unarySend, binaryTail optional
-		==> [:node |
-		    node second
-			ifNil: [node first]
-			ifNotNil: [node second valueForReceiver: node first]].
-
-	keywordPair := keyword, ws, binarySend.
-
-	keywordMessage := (ws, keywordPair) plus
-		==> [:nodes |
-		    SendNode new
-			selector: ((nodes collect: [:each | each second first]) join: '');
-			arguments: (nodes collect: [:each | each second third])].
-
-	keywordSend := binarySend, keywordMessage
-		==> [:node |
-		    node second valueForReceiver: node first].
-
-	message := binaryMessage / unaryMessage / keywordMessage.
-
-	cascade := (keywordSend / binarySend), (ws, ';' asParser, message) plus
-		==> [:node |
-		    node first cascadeNodeWithMessages: 
-			(node second collect: [:each | each third])].
-
-	jsStatement := '<' asParser, ('>>' asParser / ('>' asParser not, PPAnyParser new)) star flatten, '>' asParser
-		==> [:node | JSStatementNode new
-			source: node second;
-			yourself].
-
-	expression parser: assignment / cascade / keywordSend / binarySend / jsStatement.
-
-	method := (ws, (keywordPattern / binaryPattern / unaryPattern), ws, sequence optional, ws) withSource
-	    ==> [:node |
-		MethodNode new
-		    selector: node first second first;
-		    arguments: node first second second;
-		    addNode: node first fourth;
-		    source: node second;
-		    yourself].
-	
-	^method, PPEOFParser new ==> [:node | node first]
-! !
-
-!SmalltalkParser methodsFor: 'parsing'!
-
-parse: aStream
-	^self parser parse: aStream
-! !
-
-!SmalltalkParser class methodsFor: 'instance creation'!
-
-parse: aStream
-	    ^self new
-		parse: aStream
-! !
-
-Object subclass: #Chunk
-	instanceVariableNames: 'contents'
-	category: 'Parser'!
-
-!Chunk methodsFor: 'accessing'!
-
-contents
-	^contents ifNil: ['']
-!
-
-contents: aString
-	contents := aString
-! !
-
-!Chunk methodsFor: 'testing'!
-
-isEmptyChunk
-	^false
-!
-
-isInstructionChunk
-	^false
-! !
-
-Chunk subclass: #InstructionChunk
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!InstructionChunk methodsFor: 'testing'!
-
-isInstructionChunk
-	^true
-! !
-
-Chunk subclass: #EmptyChunk
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!EmptyChunk methodsFor: 'testing'!
-
-isEmptyChunk
-	^true
-! !
-
-Object subclass: #ChunkParser
-	instanceVariableNames: 'parser separator eof ws chunk emptyChunk instructionChunk'
-	category: 'Parser'!
-
-!ChunkParser methodsFor: ''!
-
-instructionChunk
-	^instructionChunk ifNil: [
-	    instructionChunk := self ws, '!!' asParser, self chunk
-	    ==> [:node | InstructionChunk new contents: node last contents]]
-! !
-
-!ChunkParser methodsFor: 'accessing'!
-
-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: '!!') trimBoth]]
-!
-
-emptyChunk
-	^emptyChunk ifNil: [emptyChunk := self separator plus, '!!' asParser, self ws ==> [:node | EmptyChunk new]]
-! !
-
-Object subclass: #Importer
-	instanceVariableNames: 'chunkParser'
-	category: 'Parser'!
-
-!Importer methodsFor: 'accessing'!
-
-chunkParser
-	^chunkParser ifNil: [chunkParser := ChunkParser new parser]
-! !
-
-!Importer methodsFor: 'fileIn'!
-
-import: aStream
-    | nextChunk result |
-    [aStream atEnd] whileFalse: [
-        nextChunk := self chunkParser parse: aStream.
-        nextChunk ifNil: [^self].
-        result := Compiler new loadExpression: nextChunk contents.
-        nextChunk isInstructionChunk 
-            ifTrue: [result scanFrom: aStream]]
-! !
-
-Object subclass: #Exporter
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!Exporter methodsFor: 'fileOut'!
-
-exportCategory: aString
-	| stream |
-	stream := '' writeStream.
-	(Smalltalk current classes 
-	    select: [:each | each category = aString])
-	    do: [:each | stream nextPutAll: (self export: each)].
-	self exportCategoryExtensions: aString on: stream.
-	^stream contents
-!
-
-export: aClass
-	| stream |
-	stream := '' writeStream.
-	self exportDefinitionOf: aClass on: stream.
-	self exportMethodsOf: aClass on: stream.
-	self exportMetaDefinitionOf: aClass on: stream.
-	self exportMethodsOf: aClass class on: stream.
-	^stream contents
-! !
-
-!Exporter methodsFor: 'private'!
-
-exportDefinitionOf: aClass on: aStream
-	aStream 
-	    nextPutAll: 'smalltalk.addClass(';
-	    nextPutAll: '''', (self classNameFor: aClass), ''', ';
-	    nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
-	    nextPutAll: ', ['.
-	aClass instanceVariableNames 
-	    do: [:each | aStream nextPutAll: '''', each, '''']
-	    separatedBy: [aStream nextPutAll: ', '].
-	aStream	
-	    nextPutAll: '], ''';
-	    nextPutAll: aClass category, '''';
-	    nextPutAll: ');'.
-	aClass comment notEmpty ifTrue: [
-	    aStream 
-	    	lf;
-		nextPutAll: 'smalltalk.';
-		nextPutAll: (self classNameFor: aClass);
-		nextPutAll: '.comment=';
-		nextPutAll: 'unescape(''', aClass comment escaped, ''')'].
-	aStream lf
-!
-
-exportMetaDefinitionOf: aClass on: aStream
-	aClass class instanceVariableNames isEmpty ifFalse: [
-	    aStream 
-		nextPutAll: 'smalltalk.', (self classNameFor: aClass class);
-		nextPutAll: '.iVarNames = ['.
-	    aClass class instanceVariableNames
-		do: [:each | aStream nextPutAll: '''', each, '''']
-		separatedBy: [aStream nextPutAll: ','].
-	    aStream nextPutAll: '];', String lf]
-!
-
-exportMethodsOf: aClass on: aStream
-	aClass methodDictionary values do: [:each |
-		(each category match: '^\*') ifFalse: [
-			self exportMethod: each of: aClass on: aStream]].
-	aStream lf
-!
-
-classNameFor: aClass
-	^aClass isMetaclass
-	    ifTrue: [aClass instanceClass name, '.klass']
-	    ifFalse: [
-		aClass isNil
-		    ifTrue: ['nil']
-		    ifFalse: [aClass name]]
-!
-
-exportMethod: aMethod of: aClass on: aStream
-	aStream 
-		nextPutAll: 'smalltalk.addMethod(';lf;
-		nextPutAll: '''', aMethod selector asSelector, ''',';lf;
-		nextPutAll: 'smalltalk.method({';lf;
-		nextPutAll: 'selector: ''', aMethod selector, ''',';lf;
-		nextPutAll: 'category: ''', aMethod category, ''',';lf;
-		nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
-		nextPutAll: 'source: unescape(''', aMethod source escaped, '''),';lf;
-		nextPutAll: 'messageSends: ', aMethod messageSends asJavascript, ',';lf;
-		nextPutAll: 'referencedClasses: ['.
-	    		aMethod referencedClasses 
-				do: [:each | aStream nextPutAll: 'smalltalk.', (self classNameFor: each)]
-				separatedBy: [aStream nextPutAll: ','].
-	aStream
-		nextPutAll: ']';lf;
-		nextPutAll: '}),';lf;
-		nextPutAll: 'smalltalk.', (self classNameFor: aClass);
-		nextPutAll: ');';lf;lf
-!
-
-exportCategoryExtensions: aString on: aStream
-	Smalltalk current classes, (Smalltalk current classes collect: [:each | each class]) do: [:each |
-		each methodDictionary values do: [:method |
-			method category = ('*', aString) ifTrue: [
-				self exportMethod: method of: each on: aStream]]]
-! !
-
-Exporter subclass: #ChunkExporter
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!ChunkExporter methodsFor: 'not yet classified'!
-
-exportDefinitionOf: aClass on: aStream
-	"Chunk format."
-
-	aStream 
-	    nextPutAll: (self classNameFor: aClass superclass);
-	    nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
-	    nextPutAll: '	instanceVariableNames: '''.
-	aClass instanceVariableNames 
-	    do: [:each | aStream nextPutAll: each]
-	    separatedBy: [aStream nextPutAll: ' '].
-	aStream	
-	    nextPutAll: ''''; lf;
-	    nextPutAll: '	category: ''', aClass category, '''!!'; lf.
- 	aClass comment notEmpty ifTrue: [
-	    aStream 
-		nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
-		nextPutAll: (self chunkEscape: aClass comment), '!!';lf].
-	aStream lf
-!
-
-exportMethod: aMethod of: aClass on: aStream
-	aStream 
-		lf; lf; nextPutAll: (self chunkEscape: aMethod source); lf;
-		nextPutAll: '!!'
-!
-
-exportMethodsOf: aClass on: aStream
-
-   aClass protocolsDo: [:category :methods |
-	(category match: '^\*') ifFalse: [ 
-		self
-			exportMethods: methods
-			category: category
-			of: aClass
-			on: aStream]]
-!
-
-exportMetaDefinitionOf: aClass on: aStream
-
-	aClass class instanceVariableNames isEmpty ifFalse: [
-		aStream 
-		    nextPutAll: (self classNameFor: aClass class);
-		    nextPutAll: ' instanceVariableNames: '''.
-		aClass class instanceVariableNames 
-		    do: [:each | aStream nextPutAll: each]
-		    separatedBy: [aStream nextPutAll: ' '].
-		aStream	
-		    nextPutAll: '''!!'; lf; lf]
-!
-
-classNameFor: aClass
-	^aClass isMetaclass
-	    ifTrue: [aClass instanceClass name, ' class']
-	    ifFalse: [
-		aClass isNil
-		    ifTrue: ['nil']
-		    ifFalse: [aClass name]]
-!
-
-chunkEscape: aString
-	"Replace all occurrences of !! with !!!! and trim at both ends."
-
-	^(aString replace: '!!' with: '!!!!') trimBoth
-!
-
-exportCategoryExtensions: aString on: aStream
-	"We need to override this one too since we need to group
-	all methods in a given protocol under a leading methodsFor: chunk
-	for that class."
-
-	Smalltalk current classes, (Smalltalk current classes collect: [:each | each class]) do: [:each |
-		each protocolsDo: [:category :methods |
-			category = ('*', aString) ifTrue: [
-				self exportMethods: methods category: category of: each on: aStream]]]
-!
-
-exportMethods: methods category: category of: aClass on: aStream
-
-	aStream
-		nextPutAll: '!!', (self classNameFor: aClass);
-		nextPutAll: ' methodsFor: ''', category, '''!!'.
-    	methods do: [:each |
-		self exportMethod: each of: aClass on: aStream].
-	aStream nextPutAll: ' !!'; lf; lf
-! !
-
-Exporter subclass: #StrippedExporter
-	instanceVariableNames: ''
-	category: 'Parser'!
-
-!StrippedExporter methodsFor: 'private'!
-
-exportDefinitionOf: aClass on: aStream
-	aStream 
-	    nextPutAll: 'smalltalk.addClass(';
-	    nextPutAll: '''', (self classNameFor: aClass), ''', ';
-	    nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
-	    nextPutAll: ', ['.
-	aClass instanceVariableNames 
-	    do: [:each | aStream nextPutAll: '''', each, '''']
-	    separatedBy: [aStream nextPutAll: ', '].
-	aStream	
-	    nextPutAll: '], ''';
-	    nextPutAll: aClass category, '''';
-	    nextPutAll: ');'.
-	aStream lf
-!
-
-exportMethod: aMethod of: aClass on: aStream
-	aStream 
-		nextPutAll: 'smalltalk.addMethod(';lf;
-		nextPutAll: '''', aMethod selector asSelector, ''',';lf;
-		nextPutAll: 'smalltalk.method({';lf;
-		nextPutAll: 'selector: ''', aMethod selector, ''',';lf;
-		nextPutAll: 'fn: ', aMethod fn compiledSource;lf;
-		nextPutAll: '}),';lf;
-		nextPutAll: 'smalltalk.', (self classNameFor: aClass);
-		nextPutAll: ');';lf;lf
-! !
-

Kaikkia tiedostoja ei voida näyttää, sillä liian monta tiedostoa muuttui tässä diffissä