| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290 | Smalltalk current createPackage: 'Compiler-Core'!Object subclass: #Compiler	instanceVariableNames: 'currentClass source unknownVariables codeGeneratorClass'	package: 'Compiler-Core'!!Compiler commentStamp!I provide the public interface for compiling Amber source code into JavaScript.The code generator used to produce JavaScript can be plugged with `#codeGeneratorClass`. The default code generator is an instance of `InlinedCodeGenerator`!!Compiler methodsFor: 'accessing'!codeGeneratorClass	^codeGeneratorClass ifNil: [InliningCodeGenerator]!codeGeneratorClass: aClass	codeGeneratorClass := aClass!currentClass	^currentClass!currentClass: aClass	currentClass := aClass!source	^source ifNil: ['']!source: aString	source := aString!unknownVariables	^unknownVariables!unknownVariables: aCollection	unknownVariables := aCollection! !!Compiler methodsFor: 'compiling'!compile: aString	^self compileNode: (self parse: aString)!compile: aString forClass: aClass	self currentClass: aClass.	self source: aString.	^self compile: aString!compileExpression: aString	self currentClass: DoIt.	self source: 'doIt ^[', aString, '] value'.	^self compileNode: (self parse: self source)!compileNode: aNode	| generator result |	generator := self codeGeneratorClass new.	generator		source: self source;		currentClass: self currentClass.	result := generator compileNode: aNode.	self unknownVariables: #().	^result!eval: aString	<return eval(aString)>!evaluateExpression: aString	"Unlike #eval: evaluate a Smalltalk expression and answer the returned object"	| result |	DoIt addCompiledMethod: (self eval: (self compileExpression: aString)).	result := DoIt new doIt.	DoIt removeCompiledMethod: (DoIt methodDictionary at: 'doIt').	^result!install: aString forClass: aBehavior category: anotherString   	^ ClassBuilder new    	installMethod: (self eval: (self compile: aString forClass: aBehavior))        forClass: aBehavior        category: anotherString!parse: aString    ^Smalltalk current parse: aString!parseExpression: aString    ^self parse: 'doIt ^[', aString, '] value'!recompile: aClass	aClass methodDictionary do: [:each |		console log: aClass name, ' >> ', each selector.		self install: each source forClass: aClass category: each category].	"self setupClass: aClass."	aClass isMetaclass ifFalse: [self recompile: aClass class]!recompileAll	Smalltalk current classes do: [:each |		Transcript show: each; cr.		[self recompile: each] valueWithTimeout: 100]! !!Compiler class methodsFor: 'compiling'!recompile: aClass	self new recompile: aClass!recompileAll	Smalltalk current classes do: [:each |		self recompile: each]! !Object subclass: #DoIt	instanceVariableNames: ''	package: 'Compiler-Core'!!DoIt commentStamp!`DoIt` is the class used to compile and evaluate expressions. See `Compiler >> evaluateExpression:`.!Object subclass: #NodeVisitor	instanceVariableNames: ''	package: 'Compiler-Core'!!NodeVisitor commentStamp!I am the abstract super class of all AST node visitors.!!NodeVisitor methodsFor: 'visiting'!visit: aNode	^ aNode accept: self!visitAll: aCollection	^ aCollection collect: [ :each | self visit: each ]!visitAssignmentNode: aNode	^ self visitNode: aNode!visitBlockNode: aNode	^ self visitNode: aNode!visitBlockSequenceNode: aNode	^ self visitSequenceNode: aNode!visitCascadeNode: aNode	^ self visitNode: aNode!visitClassReferenceNode: aNode	^ self visitVariableNode: aNode!visitDynamicArrayNode: aNode	^ self visitNode: aNode!visitDynamicDictionaryNode: aNode	^ self visitNode: aNode!visitJSStatementNode: aNode	^ self visitNode: aNode!visitMethodNode: aNode	^ self visitNode: aNode!visitNode: aNode	^ self visitAll: aNode nodes!visitReturnNode: aNode	^ self visitNode: aNode!visitSendNode: aNode	^ self visitNode: aNode!visitSequenceNode: aNode	^ self visitNode: aNode!visitValueNode: aNode	^ self visitNode: aNode!visitVariableNode: aNode	^ self visitNode: aNode! !NodeVisitor subclass: #AbstractCodeGenerator	instanceVariableNames: 'currentClass source'	package: 'Compiler-Core'!!AbstractCodeGenerator commentStamp!I am the abstract super class of all code generators and provide their common API.!!AbstractCodeGenerator methodsFor: 'accessing'!classNameFor: aClass	^aClass isMetaclass	    ifTrue: [aClass instanceClass name, '.klass']	    ifFalse: [		aClass isNil		    ifTrue: ['nil']		    ifFalse: [aClass name]]!currentClass	^currentClass!currentClass: aClass	currentClass := aClass!pseudoVariables	^#('self' 'super' 'true' 'false' 'nil' 'thisContext')!safeVariableNameFor: aString	^(Smalltalk current reservedWords includes: aString)		ifTrue: [aString, '_']		ifFalse: [aString]!source	^source ifNil: ['']!source: aString	source := aString! !!AbstractCodeGenerator methodsFor: 'compiling'!compileNode: aNode	self subclassResponsibility! !AbstractCodeGenerator subclass: #CodeGenerator	instanceVariableNames: ''	package: 'Compiler-Core'!!CodeGenerator commentStamp!I am a basic code generator. I generate a valid JavaScript output, but no not perform any inlining.See `InliningCodeGenerator` for an optimized JavaScript code generation.!!CodeGenerator methodsFor: 'compiling'!compileNode: aNode	| ir stream |	self semanticAnalyzer visit: aNode.	ir := self translator visit: aNode.	^ self irTranslator		visit: ir;		contents!irTranslator	^ IRJSTranslator new!semanticAnalyzer	^ SemanticAnalyzer on: self currentClass!translator	^ IRASTTranslator new		source: self source;		theClass: self currentClass;		yourself! !
 |