| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731 | Smalltalk createPackage: 'Compiler-Semantic'!Object subclass: #LexicalScope	slots: {#node. #instruction. #temps. #args. #outerScope. #blockIndex}	package: 'Compiler-Semantic'!!LexicalScope commentStamp!I represent a lexical scope where variable names are associated with ScopeVarsInstances are used for block scopes. Method scopes are instances of MethodLexicalScope.I am attached to a ScopeVar and method/block nodes.Each context (method/closure) get a fresh scope that inherits from its outer scope.!!LexicalScope methodsFor: 'accessing'!alias	^ '$ctx', self scopeLevel asString!allVariableNames	^ self args keys, self temps keys!args	^ args ifNil: [ args := Dictionary new ]!bindingFor: aStringOrNode	^ self pseudoVars at: aStringOrNode value ifAbsent: [		self args at: aStringOrNode value ifAbsent: [			self temps at: aStringOrNode value ifAbsent: [ nil ]]]!blockIndex	^ blockIndex ifNil: [ 0 ]!blockIndex: anInteger 	blockIndex := anInteger!instruction	^ instruction!instruction: anIRInstruction	instruction := anIRInstruction!lookupVariable: aNode	| lookup |	lookup := (self bindingFor: aNode).	lookup ifNil: [		lookup := self outerScope ifNotNil: [			(self outerScope lookupVariable: aNode) ]].	^ lookup!methodScope	^ self outerScope ifNotNil: [		self outerScope methodScope ]!node	"Answer the node in which I am defined"		^ node!node: aNode	node := aNode!outerScope	^ outerScope!outerScope: aLexicalScope	outerScope := aLexicalScope!pseudoVars	^ self methodScope pseudoVars!scopeLevel	self outerScope ifNil: [ ^ 1 ].	self isInlined ifTrue: [ ^ self outerScope scopeLevel ].		^ self outerScope scopeLevel + 1!temps	^ temps ifNil: [ temps := Dictionary new ]! !!LexicalScope methodsFor: 'adding'!addArg: aString	self args at: aString put: (ArgVar on: aString).	(self args at: aString) scope: self!addTemp: aString	self temps at: aString put: (TempVar on: aString).	(self temps at: aString) scope: self! !!LexicalScope methodsFor: 'testing'!canInlineNonLocalReturns	^ self isInlined and: [ self outerScope canInlineNonLocalReturns ]!isBlockScope	^ self isMethodScope not!isInlined	^ self instruction notNil and: [		self instruction isInlined ]!isMethodScope	^ false! !LexicalScope subclass: #MethodLexicalScope	slots: {#iVars. #pseudoVars. #unknownVariables. #localReturn. #nonLocalReturns}	package: 'Compiler-Semantic'!!MethodLexicalScope commentStamp!I represent a method scope.!!MethodLexicalScope methodsFor: 'accessing'!allVariableNames	^ super allVariableNames, self iVars keys!bindingFor: aNode	^ (super bindingFor: aNode) ifNil: [		self iVars at: aNode value ifAbsent: [ nil ]]!iVars	^ iVars ifNil: [ iVars := Dictionary new ]!localReturn	^ localReturn ifNil: [ false ]!localReturn: aBoolean	localReturn := aBoolean!methodScope	^ self!nonLocalReturns	^ nonLocalReturns ifNil: [ nonLocalReturns := OrderedCollection new ]!pseudoVars	pseudoVars ifNil: [		pseudoVars := Dictionary new.		Smalltalk pseudoVariableNames do: [ :each |			pseudoVars at: each put: ((PseudoVar on: each)				scope: self methodScope;				yourself) ].		pseudoVars at: #super put: ((SuperVar on: #super) scope: self methodScope; yourself) ].	^ pseudoVars!unknownVariables	^ unknownVariables ifNil: [ unknownVariables := OrderedCollection new ]! !!MethodLexicalScope methodsFor: 'adding'!addIVar: aString	self iVars at: aString put: (InstanceVar on: aString).	(self iVars at: aString) scope: self!addNonLocalReturn: aScope	self nonLocalReturns add: aScope!removeNonLocalReturn: aScope	self nonLocalReturns remove: aScope ifAbsent: []! !!MethodLexicalScope methodsFor: 'testing'!canInlineNonLocalReturns	^ true!hasLocalReturn	^ self localReturn!hasNonLocalReturn	^ self nonLocalReturns notEmpty!isMethodScope	^ true! !Object subclass: #ScopeVar	slots: {#scope. #name}	package: 'Compiler-Semantic'!!ScopeVar commentStamp!I am an entry in a LexicalScope that gets associated with variable nodes of the same name.There are 4 different subclasses of vars: temp vars, local vars, args, and unknown/global vars.!!ScopeVar methodsFor: 'accessing'!alias	^ self name asVariableName!name	^ name!name: aString	name := aString!scope	^ scope!scope: aScope	scope := aScope! !!ScopeVar methodsFor: 'testing'!isArgVar	^ false!isClassRefVar	^ false!isImmutable	^ false!isInstanceVar	^ false!isPseudoVar	^ false!isSelf	^ false!isSuper	^ false!isTempVar	^ false!isUnknownVar	^ false!validateAssignment	(self isArgVar or: [ self isPseudoVar ]) ifTrue: [		InvalidAssignmentError new			variableName: self name;			signal]! !!ScopeVar class methodsFor: 'instance creation'!on: aString	^ self new		name: aString;		yourself! !ScopeVar subclass: #AliasVar	slots: {#node}	package: 'Compiler-Semantic'!!AliasVar commentStamp!I am an internally defined variable by the compiler!!AliasVar methodsFor: 'accessing'!node	^ node!node: aNode	node := aNode! !!AliasVar methodsFor: 'testing'!isImmutable	^ true! !ScopeVar subclass: #ArgVar	slots: {}	package: 'Compiler-Semantic'!!ArgVar commentStamp!I am an argument of a method or block.!!ArgVar methodsFor: 'testing'!isArgVar	^ true!isImmutable	^ true! !ScopeVar subclass: #ClassRefVar	slots: {}	package: 'Compiler-Semantic'!!ClassRefVar commentStamp!I am an class reference variable!!ClassRefVar methodsFor: 'accessing'!alias	"Fixes issue #190.	A function is created in the method definition, answering the class or nil.	See JSStream >> #nextPutClassRefFunction:"		^ '$globals.', self name! !!ClassRefVar methodsFor: 'testing'!isClassRefVar	^ true!isImmutable	^ true! !ScopeVar subclass: #InstanceVar	slots: {}	package: 'Compiler-Semantic'!!InstanceVar commentStamp!I am an instance variable of a method or block.!!InstanceVar methodsFor: 'testing'!alias	^ '$self.', self name!isInstanceVar	^ true! !ScopeVar subclass: #PseudoVar	slots: {}	package: 'Compiler-Semantic'!!PseudoVar commentStamp!I am an pseudo variable.The five Smalltalk pseudo variables are: 'self', 'super', 'nil', 'true' and 'false'!!PseudoVar methodsFor: 'accessing'!alias	^ self name! !!PseudoVar methodsFor: 'testing'!isImmutable	^ true!isPseudoVar	^ true!isSelf	^ name = 'self'! !PseudoVar subclass: #SuperVar	slots: {}	package: 'Compiler-Semantic'!!SuperVar commentStamp!I am a 'super' pseudo variable.!!SuperVar methodsFor: 'accessing'!alias	^ 'self'! !!SuperVar methodsFor: 'testing'!isSuper	^ true! !ScopeVar subclass: #TempVar	slots: {}	package: 'Compiler-Semantic'!!TempVar commentStamp!I am an temporary variable of a method or block.!!TempVar methodsFor: 'testing'!isTempVar	^ true! !ScopeVar subclass: #UnknownVar	slots: {}	package: 'Compiler-Semantic'!!UnknownVar commentStamp!I am an unknown variable. Amber uses unknown variables as JavaScript globals!!UnknownVar methodsFor: 'testing'!isUnknownVar	^ true! !NodeVisitor subclass: #SemanticAnalyzer	slots: {#currentScope. #blockIndex. #thePackage. #theClass. #classReferences. #messageSends}	package: 'Compiler-Semantic'!!SemanticAnalyzer commentStamp!I semantically analyze the abstract syntax tree and annotate it with informations such as non local returns and variable scopes.!!SemanticAnalyzer methodsFor: 'accessing'!classReferences	^ classReferences ifNil: [ classReferences := Set new ]!messageSends	^ messageSends ifNil: [ messageSends := Dictionary new ]!theClass	^ theClass!theClass: aClass	theClass := aClass!thePackage	^ thePackage!thePackage: aPackage	thePackage := aPackage! !!SemanticAnalyzer methodsFor: 'error handling'!errorShadowingVariable: aString	ShadowingVariableError new		variableName: aString;		signal!errorUnknownVariable: aNode	"Throw an error if the variable is undeclared in the global JS scope (i.e. window).	We allow all variables listed by Smalltalk>>#globalJsVariables.	This list includes: `window`, `document`,  `process` and `global`	for nodejs and browser environments.		This is only to make sure compilation works on both browser-based and nodejs environments.	The ideal solution would be to use a pragma instead"	| identifier |	identifier := aNode value.		((Smalltalk globalJsVariables includes: identifier) not		and: [ self isVariableUndefined: identifier inPackage: self thePackage ])			ifTrue: [				UnknownVariableError new					variableName: aNode value;					signal ]			ifFalse: [				currentScope methodScope unknownVariables add: aNode value ]! !!SemanticAnalyzer methodsFor: 'factory'!newBlockScope	^ self newScopeOfClass: LexicalScope!newMethodScope	^ self newScopeOfClass: MethodLexicalScope!newScopeOfClass: aLexicalScopeClass	^ aLexicalScopeClass new		outerScope: currentScope;		yourself! !!SemanticAnalyzer methodsFor: 'private'!nextBlockIndex	blockIndex ifNil: [ blockIndex := 0 ].		blockIndex := blockIndex + 1.	^ blockIndex! !!SemanticAnalyzer methodsFor: 'scope'!popScope	currentScope ifNotNil: [		currentScope := currentScope outerScope ]!pushScope: aScope	aScope outerScope: currentScope.	currentScope := aScope!validateVariableScope: aString	"Validate the variable scope in by doing a recursive lookup, up to the method scope"	(currentScope lookupVariable: aString) ifNotNil: [		self errorShadowingVariable: aString ]! !!SemanticAnalyzer methodsFor: 'testing'!isVariableUndefined: aString inPackage: aPackage	aPackage ifNotNil: [		| packageKnownVars |		packageKnownVars := (aPackage imports			reject: #isString)			collect: #key.		(packageKnownVars includes: aString) ifTrue: [ ^ false ]].	^ Compiler eval: 'typeof ', aString, ' === "undefined"'! !!SemanticAnalyzer methodsFor: 'visiting'!visitAssignmentNode: aNode	super visitAssignmentNode: aNode.	aNode left beAssigned!visitBlockNode: aNode	self pushScope: self newBlockScope.	aNode scope: currentScope.	currentScope node: aNode.	currentScope blockIndex: self nextBlockIndex.	aNode parameters do: [ :each |		self validateVariableScope: each.		currentScope addArg: each ].	super visitBlockNode: aNode.	self popScope!visitCascadeNode: aNode	aNode receiver: aNode dagChildren first receiver.	super visitCascadeNode: aNode!visitMethodNode: aNode	self pushScope: self newMethodScope.	aNode scope: currentScope.	currentScope node: aNode.	self theClass allInstanceVariableNames do: [ :each |		currentScope addIVar: each ].	aNode arguments do: [ :each |		self validateVariableScope: each.		currentScope addArg: each ].	super visitMethodNode: aNode.	aNode		classReferences: self classReferences;		sendIndexes: self messageSends.	self popScope.	^ aNode!visitReturnNode: aNode	aNode scope: currentScope.	currentScope isMethodScope		ifTrue: [ currentScope localReturn: true ]		ifFalse: [ currentScope methodScope addNonLocalReturn: currentScope ].	super visitReturnNode: aNode!visitSendNode: aNode	| sends |	sends := self messageSends at: aNode selector ifAbsentPut: [ OrderedCollection new ].	sends add: aNode.	aNode index: sends size.	super visitSendNode: aNode!visitSequenceNode: aNode	aNode temps do: [ :each |		self validateVariableScope: each.		currentScope addTemp: each ].	super visitSequenceNode: aNode!visitVariableNode: aNode	"Bind a ScopeVar to aNode by doing a lookup in the current scope.	If no ScopeVar is found, bind a UnknowVar and throw an error."	| binding |	binding := currentScope lookupVariable: aNode.		binding ifNil: [		aNode value isCapitalized			ifTrue: [ "Capital letter variables might be globals."				binding := ClassRefVar new name: aNode value; yourself.				self classReferences add: aNode value]			ifFalse: [				self errorUnknownVariable: aNode.				binding := UnknownVar new name: aNode value; yourself ] ].			aNode binding: binding.! !!SemanticAnalyzer class methodsFor: 'instance creation'!on: aClass	^ self new		theClass: aClass;		yourself! !CompilerError subclass: #SemanticError	slots: {}	package: 'Compiler-Semantic'!!SemanticError commentStamp!I represent an abstract semantic error thrown by the SemanticAnalyzer.Semantic errors can be unknown variable errors, etc.See my subclasses for concrete errors.The IDE should catch instances of Semantic error to deal with them when compiling!SemanticError subclass: #InvalidAssignmentError	slots: {#variableName}	package: 'Compiler-Semantic'!!InvalidAssignmentError commentStamp!I get signaled when a pseudo variable gets assigned.!!InvalidAssignmentError methodsFor: 'accessing'!messageText	^ ' Invalid assignment to variable: ', self variableName!variableName	^ variableName!variableName: aString	variableName := aString! !SemanticError subclass: #ShadowingVariableError	slots: {#variableName}	package: 'Compiler-Semantic'!!ShadowingVariableError commentStamp!I get signaled when a variable in a block or method scope shadows a variable of the same name in an outer scope.!!ShadowingVariableError methodsFor: 'accessing'!messageText	^ 'Variable shadowing error: ', self variableName, ' is already defined'!variableName	^ variableName!variableName: aString	variableName := aString! !SemanticError subclass: #UnknownVariableError	slots: {#variableName}	package: 'Compiler-Semantic'!!UnknownVariableError commentStamp!I get signaled when a variable is not defined.The default behavior is to allow it, as this is how Amber currently is able to seamlessly send messages to JavaScript objects.!!UnknownVariableError methodsFor: 'accessing'!messageText	^ 'Unknown Variable error: ', self variableName, ' is not defined'!variableName	^ variableName!variableName: aString	variableName := aString! !
 |