| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827 | Smalltalk current createPackage: 'Compiler-Interpreter'!BlockClosure subclass: #AIBlockClosure	instanceVariableNames: 'node outerContext'	package: 'Compiler-Interpreter'!!AIBlockClosure commentStamp!I am a special `BlockClosure` subclass used by an interpreter to interpret a block node.While I am polymorphic with `BlockClosure`, some methods such as `#new` will raise interpretation errors. Unlike a `BlockClosure`, my instance are not JavaScript functions.Evaluating an instance will result in interpreting the `node` instance variable (instance of `BlockNode`).!!AIBlockClosure methodsFor: 'accessing'!compiledSource	"Unlike blocks, the receiver doesn't represent a JS function"		^ '[ AST Block closure ]'!numArgs	^ node temps size! !!AIBlockClosure methodsFor: 'converting'!currySelf	self interpreterError! !!AIBlockClosure methodsFor: 'error handling'!interpreterError	ASTInterpreterError signal: 'Method cannot be interpreted by the interpreter.'! !!AIBlockClosure methodsFor: 'evaluating'!applyTo: anObject arguments: aCollection	self interpreterError!value	^ self valueWithPossibleArguments: #()!value: anArgument	^ self valueWithPossibleArguments: {anArgument}!value: firstArgument value: secondArgument	^ self valueWithPossibleArguments: {firstArgument . secondArgument}!value: firstArgument value: secondArgument value: thirdArgument	^ self valueWithPossibleArguments: {firstArgument . secondArgument . thirdArgument}!valueWithPossibleArguments: aCollection	| context sequenceNode |	context := outerContext newBlockContext.	"Interpret a copy of the sequence node to avoid creating a new AIBlockClosure"	sequenceNode := node nodes first copy		parent: nil;		yourself.	"Populate the arguments into the context locals"		node parameters withIndexDo: [ :each :index |		context localAt: each put: (aCollection at: index ifAbsent: [ nil ]) ].	"Interpret the first node of the BlockSequenceNode"	context interpreter		node: sequenceNode nextChild;		proceed.			outerContext interpreter		setNonLocalReturnFromContext: context.			^ context interpreter pop! !!AIBlockClosure methodsFor: 'initialization'!initializeWithContext: aContext node: aNode	node := aNode.	outerContext := aContext! !!AIBlockClosure class methodsFor: 'instance creation'!forContext: aContext node: aNode	^ self new		initializeWithContext: aContext node: aNode;		yourself! !MethodContext subclass: #AIContext	instanceVariableNames: 'outerContext innerContext pc locals selector index ast interpreter'	package: 'Compiler-Interpreter'!!AIContext commentStamp!I am like a `MethodContext`, used by the `ASTInterpreter`.Unlike a `MethodContext`, my instances are not read-only.When debugging, my instances are created by copying the current `MethodContext` (thisContext)!!AIContext methodsFor: 'accessing'!index	^ index ifNil: [ 0 ]!index: anInteger	index := anInteger!innerContext	^ innerContext!innerContext: anAIContext	innerContext := anAIContext!localAt: aString	"Lookup the local value up to the method context"	^ self locals at: aString ifAbsent: [ 		self outerContext ifNotNil: [ :context | 			context localAt: aString ] ]!localAt: aString ifAbsent: aBlock	"Lookup the local value up to the method context"	^ self locals at: aString ifAbsent: [ 		self outerContext 			ifNotNil: [ :context | context localAt: aString ifAbsent: aBlock ]			ifNil: [aBlock value] ]!localAt: aString put: anObject	self locals at: aString put: anObject!locals	locals ifNil: [ self initializeLocals ].		^ locals!method	^ self methodContext ifNotNil: [		self methodContext receiver class lookupSelector: self methodContext selector ]!outerContext	^ outerContext!outerContext: anAIContext	outerContext := anAIContext.	outerContext innerContext: self!selector	^ selector!selector: aString	selector := aString! !!AIContext methodsFor: 'factory'!newBlockContext	^ self class new		outerContext: self;		yourself! !!AIContext methodsFor: 'initialization'!initializeAST	ast := self method ast.	(SemanticAnalyzer on: self method methodClass)		visit: ast!initializeFromMethodContext: aMethodContext	self 		pc: aMethodContext pc;		index: aMethodContext index;		receiver: aMethodContext receiver;		selector: aMethodContext selector.			aMethodContext outerContext ifNotNil: [ :outer |		"If the method context is nil, the block was defined in JS, so ignore it"		outer methodContext ifNotNil: [			self outerContext: (self class fromMethodContext: aMethodContext outerContext) ].			aMethodContext locals keysAndValuesDo: [ :key :value |				self locals at: key put: value ] ]!initializeInterpreter	interpreter := ASTInterpreter new		context: self;		node: self retrieveNode;		yourself.		(self innerContext notNil and: [ 		self innerContext isBlockContext not ]) ifTrue: [			self setupInterpreter: interpreter ]!initializeLocals	locals := Dictionary new.	locals at: 'thisContext' put: self.! !!AIContext methodsFor: 'interpreting'!arguments	^ self ast arguments collect: [ :each |		self localAt: each ]!ast	self isBlockContext ifTrue: [ 		^ self outerContext ifNotNil: [ :context | context ast ] ].	ast ifNil: [ self initializeAST ].	^ ast!interpreter	interpreter ifNil: [ self initializeInterpreter ].	^ interpreter!interpreter: anInterpreter	interpreter := anInterpreter!pc	^ pc ifNil: [ pc := 0 ]!pc: anInteger	pc := anInteger!receiver	^ self localAt: 'self'!receiver: anObject	self localAt: 'self' put: anObject!retrieveNode	^ self ast ifNotNil: [		ASTPCNodeVisitor new			context: self;			visit: self ast;			currentNode ]!setupInterpreter: anInterpreter	"Push the send args and receiver to the interpreter stack"		self innerContext arguments reversed do: [ :each | 		anInterpreter push: each ].			anInterpreter push: (self innerContext receiver)! !!AIContext class methodsFor: 'instance creation'!fromMethodContext: aMethodContext	^ self new		initializeFromMethodContext: aMethodContext;		yourself! !Object subclass: #ASTDebugger	instanceVariableNames: 'interpreter context'	package: 'Compiler-Interpreter'!!ASTDebugger commentStamp!I am a stepping debugger interface for Amber code.I internally use an instance of `ASTSteppingInterpreter` to actually step through node and interpret them.My instances are created from a `MethodContext` with `ASTDebugger class >> context:`.They hold an `AIContext` instance internally, recursive copy of the `MethodContext`.## APIUse the methods of the `'stepping'` protocol to do stepping.!!ASTDebugger methodsFor: 'accessing'!context	^ context!context: aContext	context := aContext!interpreter	^ interpreter ifNil: [ interpreter := self defaultInterpreterClass new ]!interpreter: anInterpreter	interpreter := anInterpreter!method	^ self context method!nextNode	^ self interpreter nextNode! !!ASTDebugger methodsFor: 'defaults'!defaultInterpreterClass	^ ASTInterpreter! !!ASTDebugger methodsFor: 'initialization'!buildAST	"Build the AST tree from the method source code.	The AST is annotated with a SemanticAnalyzer,	to know the semantics and bindings of each node needed for later debugging"		| ast |		ast := Smalltalk current parse: self method source.	(SemanticAnalyzer on: self context receiver class)		visit: ast.		^ ast!initializeInterpreter	| ast next |	ast := self buildAST.	next := ASTPCNodeVisitor new		context: self context;		visit: ast;		currentNode.	self interpreter node: next!initializeWithContext: aContext	"TODO: do we need to handle block contexts?"		self context: aContext.	self initializeInterpreter! !!ASTDebugger methodsFor: 'stepping'!proceed	self shouldBeImplemented!restart	self interpreter restart!stepInto	self shouldBeImplemented!stepOver	self interpreter stepOver! !!ASTDebugger methodsFor: 'testing'!atEnd	^ self interpreter atEnd! !!ASTDebugger class methodsFor: 'instance creation'!context: aContext	^ self new		initializeWithContext: aContext;		yourself! !NodeVisitor subclass: #ASTInterpreter	instanceVariableNames: 'node context stack returnValue returned'	package: 'Compiler-Interpreter'!!ASTInterpreter commentStamp!I visit an AST, interpreting (evaluating) nodes one after the other, using a small stack machine.## APIWhile my instances should be used from within an `ASTDebugger`, which provides a more high level interface,you can use methods from the `interpreting` protocol:- `#step` evaluates the current `node` only- `#stepOver` evaluates the AST from the current `node` up to the next stepping node (most likely the next send node)- `#proceed` evaluates eagerly the AST- `#restart` select the first node of the AST- `#skip` skips the current node, moving to the next one if any!!ASTInterpreter methodsFor: 'accessing'!context	^ context!context: aContext	context := aContext!node	"Answer the next node, ie the node to be evaluated in the next step"		^ node!node: aNode	node := aNode!result	^ self hasReturned 		ifTrue: [ self returnValue ] 		ifFalse: [ self context receiver ]!returnValue	^ returnValue!returnValue: anObject	returnValue := anObject!stack	^ stack ifNil: [ stack := OrderedCollection new ]! !!ASTInterpreter methodsFor: 'interpreting'!interpret	"Interpret the next node to be evaluated"		self visit: self node!interpret: aNode	self node: aNode.	self interpret!next	self node: self node nextNode!proceed	"Eagerly evaluate the ast"		[ self atEnd ] whileFalse: [ 		self step ]!restart	self node: self context ast nextChild!setNonLocalReturnFromContext: aContext	aContext interpreter hasReturned ifTrue: [		returned := true.		self returnValue: aContext interpreter returnValue ]!skip	self next!step	self 		interpret; 		next!stepOver	self step.		[ self node isSteppingNode ] whileFalse: [ 		self step ]! !!ASTInterpreter methodsFor: 'private'!assign: aNode to: anObject	aNode binding isInstanceVar		ifTrue: [ self context receiver instVarAt: aNode value put: anObject ]		ifFalse: [ self context localAt: aNode value put: anObject ]!eval: aString	"Evaluate aString as JS source inside an JS function.	aString is not sandboxed."		| source function |		source := String streamContents: [ :str |		str nextPutAll: '(function('.		self context locals keys			do: [ :each | str nextPutAll: each ]			separatedBy: [ str nextPutAll: ',' ].		str			nextPutAll: '){ return (function() {';			nextPutAll: aString;			nextPutAll: '})() })' ].				function := Compiler new eval: source.		^ function valueWithPossibleArguments: self context locals values!messageFromSendNode: aSendNode arguments: aCollection	^ Message new		selector: aSendNode selector;		arguments: aCollection;		yourself!messageNotUnderstood: aMessage receiver: anObject	MessageNotUnderstood new		meesage: aMessage;		receiver: anObject;		signal!sendMessage: aMessage to: anObject superSend: aBoolean	| method |		aBoolean ifFalse: [ ^ aMessage sendTo: anObject ].	anObject class superclass ifNil: [ ^ self messageNotUnderstood: aMessage receiver: anObject ].		method := anObject class superclass methodDictionary		at: aMessage selector		ifAbsent: [ ^ self messageNotUnderstood: aMessage receiver: anObject ].			^ method sendTo: anObject arguments: aMessage arguments! !!ASTInterpreter methodsFor: 'stack'!peek	"Peek the top object of the context stack"		self stack ifEmpty: [ ^ nil ].		^ self stack last!pop	"Pop an object from the context stack"		| peekedValue |		peekedValue := self peek.	self stack removeLast.	^ peekedValue!push: anObject	"Push an object to the context stack"		^ self stack add: anObject! !!ASTInterpreter methodsFor: 'testing'!atEnd	^ self hasReturned or: [ self node isNil ]!hasReturned	^ returned ifNil: [ false ]! !!ASTInterpreter methodsFor: 'visiting'!visit: aNode	self hasReturned ifFalse: [ super visit: aNode ]!visitAssignmentNode: aNode	| poppedValue |		poppedValue := self pop.		"Pop the left side of the assignment.	It already has been visited, and we don't need its value."	self pop.		self push: poppedValue.	self assign: aNode left to: poppedValue!visitBlockNode: aNode	"Do not evaluate the block node.	Instead, put all instructions into a block that we push to the stack for later evaluation"		| block |		block := AIBlockClosure forContext: self context node: aNode.		self push: block!visitDynamicArrayNode: aNode	| array |		array := #().	aNode nodes do: [ :each |		array addFirst: self pop ].		self push: array!visitDynamicDictionaryNode: aNode	| associations hashedCollection |		associations := OrderedCollection new.	hashedCollection := HashedCollection new.		aNode nodes do: [ :each | 		associations add: self pop ].		associations reversed do: [ :each |		hashedCollection add: each ].		self push: hashedCollection!visitJSStatementNode: aNode	returned := true.	self returnValue: (self eval: aNode source)!visitNode: aNode	"Do nothing by default. Especially, do not visit children recursively."!visitReturnNode: aNode	returned := true.	self returnValue: self pop!visitSendNode: aNode	| receiver args message result |		args := aNode arguments collect: [ :each | self pop ].	receiver := self pop.		message := self		messageFromSendNode: aNode		arguments: args reversed.		result := self sendMessage: message to: receiver superSend: aNode superSend.		self context pc: self context pc + 1.		"For cascade sends, push the reciever if the send is not the last one"	(aNode isCascadeSendNode and: [ aNode isLastChild not ])		ifTrue: [ self push: receiver ]		ifFalse: [ self push: result ]!visitValueNode: aNode	self push: aNode value!visitVariableNode: aNode	aNode binding isUnknownVar ifTrue: [		^ self push: (PlatformInterface globals at: aNode value ifAbsent: [ self error: 'Unknown variable' ]) ].			self push: (aNode binding isInstanceVar		ifTrue: [ self context receiver instVarAt: aNode value ]		ifFalse: [ self context 			localAt: aNode value			ifAbsent: [				aNode value isCapitalized					ifTrue: [						Smalltalk current 							at: aNode value 							ifAbsent: [ PlatformInterface globals at: aNode value ]]]])! !Error subclass: #ASTInterpreterError	instanceVariableNames: ''	package: 'Compiler-Interpreter'!!ASTInterpreterError commentStamp!I get signaled when an AST interpreter is unable to interpret a node.!NodeVisitor subclass: #ASTPCNodeVisitor	instanceVariableNames: 'useInlinings pc context blockIndex currentNode'	package: 'Compiler-Interpreter'!!ASTPCNodeVisitor commentStamp!I visit an AST until I get to the current pc node and answer it.## APIMy instances must be filled with a context object using `#context:`.After visiting the AST the current node corresponding to the `pc` is answered by `#currentNode`!!ASTPCNodeVisitor methodsFor: 'accessing'!blockIndex	^ blockIndex ifNil: [ blockIndex := 0 ]!context	^ context!context: aContext	context := aContext!currentNode	^ currentNode!increaseBlockIndex	blockIndex := self blockIndex + 1!pc	^ pc ifNil: [ 0 ]!pc: anInteger	pc := anInteger!useInlinings	^ useInlinings ifNil: [ true ]!useInlinings: aBoolean	useInlinings := aBoolean! !!ASTPCNodeVisitor methodsFor: 'visiting'!visitBlockNode: aNode	"Inlined send node. Assume that the block is inlined"	(aNode parent isSendNode and: [ aNode parent shouldBeInlined ])		ifFalse: [			self blockIndex >= self context index ifFalse: [				self increaseBlockIndex.				super visitBlockNode: aNode ] ]		ifTrue: [ super visitBlockNode: aNode ]!visitJSStatementNode: aNode	currentNode := aNode!visitSendNode: aNode	super visitSendNode: aNode.		self pc = self context pc ifFalse: [		aNode shouldBeInlined ifFalse: [			self blockIndex = self context index ifTrue: [				self pc: self pc + 1.				currentNode := aNode ] ] ]! !!Node methodsFor: '*Compiler-Interpreter'!isSteppingNode	^ false! !!AssignmentNode methodsFor: '*Compiler-Interpreter'!isSteppingNode	^ true! !!BlockNode methodsFor: '*Compiler-Interpreter'!isSteppingNode	^ true! !!DynamicArrayNode methodsFor: '*Compiler-Interpreter'!isSteppingNode	^ true! !!DynamicDictionaryNode methodsFor: '*Compiler-Interpreter'!isSteppingNode	^ true! !!JSStatementNode methodsFor: '*Compiler-Interpreter'!isSteppingNode	^ true! !!SendNode methodsFor: '*Compiler-Interpreter'!isSteppingNode	^ true! !
 |