[Vm-dev] VM Maker: VMMakerJS-bf.1.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Oct 10 13:24:55 UTC 2014


Bert Freudenberg uploaded a new version of VMMakerJS to project VM Maker:
http://source.squeak.org/VMMaker/VMMakerJS-bf.1.mcz

==================== Summary ====================

Name: VMMakerJS-bf.1
Author: bf
Time: 3 October 2014, 4:23:53.315 am
UUID: bf4d839f-b54e-4569-b6b1-a3d2348ab9f7
Ancestors: 

Initial version: can translate LargeIntegersPlugin using

JSCodeGenerator isActive: true.
LargeIntegersPlugin translateInDirectory: (FileDirectory on: '/Users/bert/SqueakJS/plugins') doInlining: false

==================== Snapshot ====================

SystemOrganization addCategory: #'VMMakerJS-Translation to JS'!
SystemOrganization addCategory: #'VMMakerJS-SmartSyntaxPlugins'!

----- Method: TParseNode>>emitJSCodeAsArgumentOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen
	^self emitJSCodeOn: aStream level: level generator: aCodeGen!

----- Method: TParseNode>>emitJSCodeAsExpressionOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsExpressionOn: aStream level: level generator: aCodeGen
	^self emitJSCodeOn: aStream level: level generator: aCodeGen!

----- Method: TParseNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: lev generator: gen
	self subclassResponsibility.!

----- Method: TParseNode>>emitJSCommentOn:level: (in category '*vmmakerjs') -----
emitJSCommentOn: aStream level: level
	"Emit the transferred Smalltalk comments as C comments."

	comment ifNotNil: [
		comment isString ifTrue: [^self].	"safety catch"
		aStream cr.
		1 to: comment size do: [:index | 
			aStream 
				tab: level;
				nextPutAll: '/* ';
				nextPutAll: (comment at: index);
				nextPutAll: ' */';
				cr].
		aStream cr]!

----- Method: SmallInteger class>>jscg:generateCoerceToOopFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToOopFrom: aNode on: aStream
	"N.B.  The is used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToSmallIntegerObjectFrom: aNode on: aStream!

----- Method: SmallInteger class>>jscg:generateCoerceToValueFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToValueFrom: aNode on: aStream
	"N.B.  The could be used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToSmallIntegerValueFrom: aNode on: aStream!

----- Method: SmallInteger class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg jscgLoad: aBlock expr: aString asIntegerValueFrom: anInteger!

----- Method: SmallInteger class>>jscgCanConvertFrom: (in category '*vmmakerjs') -----
jscgCanConvertFrom: anObject

	^anObject class == self!

----- Method: TDefineNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	"Emit a C literal."

	aStream nextPutAll: name.!

----- Method: Float class>>jscg:generateCoerceToOopFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToOopFrom: aNode on: aStream
	"N.B.  The is used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToFloatObjectFrom: aNode on: aStream!

----- Method: Float class>>jscg:generateCoerceToValueFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToValueFrom: aNode on: aStream
	"N.B.  The could be used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToFloatValueFrom: aNode on: aStream!

----- Method: Float class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg jscgLoad: aBlock expr: aString asFloatValueFrom: anInteger!

----- Method: Float class>>jscgCanConvertFrom: (in category '*vmmakerjs') -----
jscgCanConvertFrom: anObject

	^anObject class == self!

----- Method: TReturnNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen

	(expression isSwitch
	 or: [expression isCaseStmt]) ifTrue:
		[^expression emitJSCodeOn: aStream addToEndOfCases: self level: level generator: aCodeGen].

	('void' = aCodeGen currentMethod returnType) ifTrue: [
		"If the function is void, don't say 'return x' instead say ' x; return' "
		expression isLeaf ifFalse: [
			expression emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen.	
			aStream nextPutAll: ';'; space.
		].
		aStream nextPutAll: 'return'.
	] ifFalse: [
		aStream nextPutAll: 'return'.
		aStream space.
		expression emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen
	].!

----- Method: CCodeGenerator class>>new (in category '*vmmakerjs') -----
new
	JSCodeGenerator isActive ifTrue: [^JSCodeGenerator new].
	^super new!

----- Method: TCaseStmtNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen

	| indent |
	indent := (String new: level) collect: [ :ch | Character tab ].
	aStream nextPutAll: 'switch ('.
	expression asExpression emitJSCodeOn: aStream level: level generator: aCodeGen.
	aStream nextPutAll: ') {'; cr.
	1 to: cases size do: [ :i |
		(firsts at: i) to: (lasts at: i) do: [ :caseIndex |
			aStream nextPutAll: indent, 'case ', caseIndex printString, ':'; cr.
		].
		(cases at: i) emitJSCodeOn: aStream level: level + 1 generator: aCodeGen.
		aStream nextPutAll: indent; tab; nextPutAll: 'break;'.
		aStream cr.
	].
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '}'.!

----- Method: FloatArray class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg jscgLoad: aBlock expr: aString asWBFloatPtrFrom: anInteger!

----- Method: TGoToNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	"Emit a C goto statement."

	aStream nextPutAll: 'goto '.
	aStream nextPutAll: label.!

----- Method: TLabeledCommentNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	"Emit a C comment with optional label."

	self printOptionalLabelOn: aStream.
	aStream nextPutAll: '/* '.
	aStream nextPutAll: comment.
	aStream nextPutAll: ' */'.!

----- Method: Oop class>>jscg:generateCoerceToOopFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToOopFrom: aNode on: aStream
	"N.B.  The is used both for generation and simulation so answer the result (for interpretation)"
	^cg emitJSExpression: aNode on: aStream!

----- Method: Oop class>>jscg:generateCoerceToValueFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToValueFrom: aNode on: aStream
	"N.B.  The could be used both for generation and simulation so answer the result (for interpretation)"
	^cg emitJSExpression: aNode on: aStream!

----- Method: Oop class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg jscgLoad: aBlock expr: aString asRawOopFrom: anInteger!

----- Method: Oop class>>jscgCanConvertFrom: (in category '*vmmakerjs') -----
jscgCanConvertFrom: anObject

	^(anObject isKindOf: SmallInteger) not!

----- Method: ArrayedCollection class>>jscg:generateCoerceToOopFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToOopFrom: aNode on: aStream
	"N.B.  The is used both for generation and simulation so answer the result (for interpretation)"
	self instSize > 0 ifTrue: 
		[self error: 'cannot auto-coerce arrays with named instance variables'].
	^cg generateCoerceToObjectFromPtr: aNode on: aStream!

----- Method: ArrayedCollection class>>jscg:generateCoerceToValueFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToValueFrom: aNode on: aStream
	"N.B.  The could be used both for generation and simulation so answer the result (for interpretation)"
	^cg 
		generateCoerceToPtr: (self jscgDeclareJSForVar: '')
		fromObject: aNode on: aStream!

----- Method: TStmtListNode>>emitJSCodeAsArgumentOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen

	| statementWasComment |
	statementWasComment := false.
	statements
		do:
			[:s |
			s emitJSCommentOn: aStream level: level.
			s emitJSCodeAsArgumentOn: aStream level: 0 generator: aCodeGen.
			statementWasComment := s isComment]
		separatedBy:
			[((self endsWithCloseBracket: aStream)
			  or: [statementWasComment]) ifFalse: [aStream nextPut: $,]]!

----- Method: TStmtListNode>>emitJSCodeAsExpressionOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsExpressionOn: aStream level: level generator: aCodeGen
	^self emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen!

----- Method: TStmtListNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen

	self emitJSCommentOn: aStream level: level.
	statements do: [:s |
		s emitJSCommentOn: aStream level: level.
		aStream tab: level.
		s emitJSCodeOn: aStream level: level generator: aCodeGen.
		(((self endsWithCloseBracket: aStream) not
			and: [(s isComment) not])
				and: [s requiresCLineTerminator])
			ifTrue: [aStream nextPut: $;].
		aStream cr].
!

----- Method: String class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg 
		jscgLoad: aBlock 
		expr: aString 
		asCharPtrFrom: anInteger
		andThen: (cg jscgValBlock: 'isBytes')!

Object subclass: #JSCodeGenerator
	instanceVariableNames: 'translationDict inlineList constants variables variableDeclarations scopeStack methods macros preparedMethodList variablesSetCache headerFiles globalVariableUsage useSymbolicConstants generateDeadCode doNotRemoveMethodList asArgumentTranslationDict receiverDict vmClass currentMethod logger declareMethodsStatic permitMethodPruning pools abstractDeclarations uncheckedAbstractMethods cCodeTranslationDict'
	classVariableNames: 'IsActive UseRightShiftForDivide'
	poolDictionaries: ''
	category: 'VMMakerJS-Translation to JS'!

!JSCodeGenerator commentStamp: 'bf 10/3/2014 04:17' prior: 0!
This class is a copy of CCodeGenerator hacked to generate JavaScript instead of C for use with the SqueakJS virtual machine.

C and JS semantics are pretty close except for pointers, types, and shift operations. !

----- Method: JSCodeGenerator class>>initialize (in category 'class initialization') -----
initialize
	"JSCodeGenerator initialize"

	UseRightShiftForDivide := true.
		"If UseRightShiftForDivide is true, the translator will generate a right-shift when it encounters a division by a constant that is a small power of two. For example, 'x / 8' will generate '((int) x >> 3)'. The coercion to int is done to make it clear that the C compiler should generate a signed shift."
		"Note: The Kernighan and Ritchie 2nd Edition C manual, p. 49, leaves the semantics of right-shifting a negative number open to the discretion of the compiler implementor. However, it strongly suggests that most compilers should generate an arithmetic right shift (i.e., shifting in the sign bit), which is the same as dividing by a power of two. If your compiler does not generate or simulate an arithmetic shift, then make this class variable false and re-translate."
!

----- Method: JSCodeGenerator class>>isActive (in category 'preferences') -----
isActive
	"should I be used instead of CCodeGenerator?"
	^IsActive == true!

----- Method: JSCodeGenerator class>>isActive: (in category 'preferences') -----
isActive: aBoolean
	"should I be used instead of CCodeGenerator?"
	IsActive := aBoolean!

----- Method: JSCodeGenerator class>>monticelloDescriptionFor: (in category 'JS code generator') -----
monticelloDescriptionFor: aClass
	"Answer a suitable Monticello package stamp to include in the header."
	| pkgInfo pkg uuid |
	pkgInfo := PackageOrganizer default packageOfClass: aClass.
	pkg := MCWorkingCopy allManagers detect: [:ea| ea packageName = pkgInfo packageName].
	pkg ancestry ancestors isEmpty ifFalse:
		[uuid := pkg ancestry ancestors first id].
	^aClass name, (pkg modified ifTrue: [' * '] ifFalse: [' ']), pkg ancestry ancestorString, ' uuid: ', uuid asString!

----- Method: JSCodeGenerator class>>removeCompilerMethods (in category 'removing from system') -----
removeCompilerMethods
	"Before removing the C code generator classes from the system, use this method to remove the compiler node methods that support it. This avoids leaving dangling references to C code generator classes in the compiler node classes."

	ParseNode withAllSubclasses do: [ :nodeClass |
		nodeClass removeCategory: 'C translation'.
	].
	Smalltalk at: #AbstractSound ifPresent: [:abstractSound |
		 abstractSound class removeCategory: 'primitive generation'].
!

----- Method: JSCodeGenerator>>addAllClassVarsFor: (in category 'public') -----
addAllClassVarsFor: aClass
	"Add the class variables for the given class (and its superclasses) to the code base as constants."

	| allClasses |
	allClasses := aClass withAllSuperclasses.
	allClasses do: [:c | self addClassVarsFor: c].
!

----- Method: JSCodeGenerator>>addClass: (in category 'public') -----
addClass: aClass
	"Add the variables and methods of the given class to the code base."

	aClass prepareToBeAddedToCodeGenerator: self.
	self checkClassForNameConflicts: aClass.
	self addClassVarsFor: aClass.
	"ikp..."
	self addPoolVarsFor: aClass.
	variables addAll: aClass instVarNames.
	self retainMethods: aClass requiredMethodNames.

	"The identity of the translated class is kept in vmClass for use in identifying the
	translated source. Unless otherwise overridden, the first class to be added to the
	code generator will provide this identifier."
	vmClass ifNil: [self vmClass: aClass].
	'Adding Class ' , aClass name , '...'
		displayProgressAt: Sensor cursorPoint
		from: 0
		to: aClass selectors size
		during:
			[:bar |
			 aClass selectors doWithIndex: [:sel :i |
				bar value: i.
				self addMethodFor: aClass selector: sel]].
	aClass declareCVarsIn: self!

----- Method: JSCodeGenerator>>addClass:selectorPrefix: (in category 'composition') -----
addClass: aClass selectorPrefix: prefix
	"Incorporate the methods of aClass, and rename with prefixes reflecting the
	variable name. This is a simple transformation intended to support MemoryAccess,
	with renaming to avoid conflict with standard sqMemoryAccess.h macros."

	self addClass: aClass.
	aClass selectors do: [:sel |
		self renameSelector: sel
			as: (prefix, '_', sel) asSymbol].
!

----- Method: JSCodeGenerator>>addClass:upTo:asInstanceVariable: (in category 'composition') -----
addClass: aClass upTo: aSuperclass asInstanceVariable: varName
	"For an instance variable var in one of the classes that has been added to
	this code generator, assume that an instance of aClass would normally be
	assigned to that variable. Arrange for the methods in aClass and all superclasses
	up to but not including aSuperclass to be incorporated into the generated C source
	module as if they had been methods in the class with instance variable var.
	
	n.b. See #addStructureClass: mechanism in Cog."

	| cls |
	cls := aClass.
	[cls == aSuperclass]
		whileFalse: [self addClass: cls.
				self mapVar: varName asInstanceOf: cls to: 'self'.
				cls := cls superclass]
!

----- Method: JSCodeGenerator>>addClassVarsFor: (in category 'public') -----
addClassVarsFor: aClass
	"Add the class variables for the given class to the code base as constants."
	| val node |
	aClass classPool associationsDo: [:assoc | 
		val := assoc value.
		(useSymbolicConstants and:[self isCLiteral: val])
			ifTrue:[node := TDefineNode new setName: assoc key asString value: assoc value]
			ifFalse:[node := TConstantNode new setValue: assoc value].
		constants at: assoc key asString put: node].
!

----- Method: JSCodeGenerator>>addHeaderFile: (in category 'public') -----
addHeaderFile: aString
	"Add a header file. The argument must be a quoted string!!"
	headerFiles addLast: aString.!

----- Method: JSCodeGenerator>>addMacro:for: (in category 'public') -----
addMacro: aString for: selector
	"Add a macro. aString must be the macro arguments and body without the leading #define or name"
	macros at: selector put: aString!

----- Method: JSCodeGenerator>>addMethod: (in category 'utilities') -----
addMethod: aJSMethod
	"Add the given method to the code base."

	(methods includesKey:  aJSMethod selector) ifTrue: [
		self error: 'Method name conflict: ', aJSMethod selector.
	].
	methods at: aJSMethod selector put: aJSMethod.!

----- Method: JSCodeGenerator>>addMethodFor:selector: (in category 'utilities') -----
addMethodFor: aClass selector: selector
	"Add the given method to the code base and answer its translation
	 or nil if it shouldn't be translated."

	| method tmethod |
	method := aClass compiledMethodAt: selector.
	method requiresConcreteImplementation ifTrue: [abstractDeclarations add: selector].
	method isAbstract ifTrue: [^nil].
	(method pragmaAt: #doNotGenerate) ifNotNil: [^nil].
	"process optional methods by interpreting the argument to the option: pragma as either
	 a Cogit class name or a class variable name or a variable name in VMBasicConstants."
	(method pragmaAt: #option:) ifNotNil:
		[:pragma| | key |
		key := pragma argumentAt: 1.
		"((Cogit withAllSubclasses anySatisfy: [:c| c name = key])
		and: [VMClass getVMMaker cogitClassName ~= key]) ifTrue:
			[^nil]."
		(aClass bindingOf: key) ifNotNil:
			[:binding|
			binding value ifFalse: [^nil]].
		(VMBasicConstants bindingOf: key) ifNotNil:
			[:binding|
			binding value ifFalse: [^nil]]].
	tmethod := self compileToJSMethodSelector: selector in: aClass.
	tmethod hasDoNotGenerateStatement ifTrue: [^nil].
	self addMethod: tmethod.
	"If the method has a macro then add the macro.  But keep the method
	 for analysis purposes (e.g. its variable accesses)."
	(method pragmaAt: #cmacro:) ifNotNil:
		[:pragma|
		self addMacro: (pragma argumentAt: 1) for: selector].
	(method propertyValueAt: #cmacro:) ifNotNil:
		[:macro|
		self addMacro: macro for: selector].
	^tmethod!

----- Method: JSCodeGenerator>>addMethodsForPrimitives: (in category 'public') -----
addMethodsForPrimitives: classAndSelectorList 
	| sel aClass source verbose meth |
	classAndSelectorList do:[:classAndSelector | 
		aClass := Smalltalk at: (classAndSelector at: 1) ifAbsent:[nil].
		aClass ifNotNil:[
			self addAllClassVarsFor: aClass.
			"TPR - should pool vars also be added here?"

			"find the method in either the class or the metaclass"
			sel := classAndSelector at: 2.
			(aClass includesSelector: sel)
				ifTrue: [source := aClass sourceCodeAt: sel ifAbsent:[nil]]
				ifFalse: [source := aClass class sourceCodeAt: sel ifAbsent:[nil]].
		].
		source ifNil:[
			Transcript cr; show: 'WARNING: Compiled primitive ', classAndSelector first, '>>', classAndSelector last, ' not present'.
		] ifNotNil:[
			"compile the method source and convert to a suitable translation 
			method "
			meth := (Compiler new
						parse: source
						in: aClass
						notifying: nil)
						asTranslationMethodOfClass: self translationMethodClass.

			(aClass includesSelector: sel)
				ifTrue: [meth definingClass: aClass]
				ifFalse: [meth definingClass: aClass class].
			meth primitive > 0 ifTrue:[meth preparePrimitiveName].
			"for old-style array accessing: 
			meth covertToZeroBasedArrayReferences."
			meth replaceSizeMessages.
			self addMethod: meth.
		].
	].
	"method preparation"
	verbose := false.
	self prepareMethods.
	verbose
		ifTrue: 
			[self printUnboundCallWarnings.
			self printUnboundVariableReferenceWarnings.
			Transcript cr].

	"code generation"
	self doInlining: true.

	methods do:[:m|
		"if this method is supposed to be a primitive (rather than a helper 
		routine), add assorted prolog and epilog items"
		m primitive > 0 ifTrue: [m preparePrimitivePrologue]].!

----- Method: JSCodeGenerator>>addPoolVarsFor: (in category 'public') -----
addPoolVarsFor: aClass 
	"Add the pool variables for the given class to the code base as constants."

	(aClass sharedPools reject: [:pool| pools includes: pool]) do:
		[:pool |
		pools add: pool.
		pool bindingsDo: [:assoc | | val node |
			val := assoc value.
			node := (useSymbolicConstants and:[self isCLiteral: val])
						ifTrue:[TDefineNode new setName: assoc key asString value: assoc value]
						ifFalse:[TConstantNode new setValue: assoc value].
			constants at: assoc key asString put: node]].!

----- Method: JSCodeGenerator>>builtin: (in category 'utilities') -----
builtin: sel 
	"Answer true if the given selector is one of the builtin selectors."
	^ sel = #error:
		or: [(self memoryAccessSelectors includes: sel)
				or: [translationDict includesKey: sel]]!

----- Method: JSCodeGenerator>>cCodeForMethod: (in category 'utilities') -----
cCodeForMethod: selector
	"Answer a string containing the C code for the given method."
	"Example:
		((JSCodeGenerator new initialize addClass: TestCClass1; prepareMethods)
			cCodeForMethod: #ifTests)"

	| m s |
	m := self methodNamed: selector.
	m = nil ifTrue: [ self error: 'method not found in code base: ', selector ].

	s := (ReadWriteStream on: '').
	m emitJSCodeOn: s generator: self.
	^ s contents!

----- Method: JSCodeGenerator>>cFunctionNameFor: (in category 'JS code generator') -----
cFunctionNameFor: aSelector
	"Create a C function name from the given selector by omitting colons
	and prefixing with the plugin name if the method is exported."
	^aSelector copyWithout: $:!

----- Method: JSCodeGenerator>>cLiteralFor: (in category 'JS code generator') -----
cLiteralFor: anObject
	"Return a string representing the C literal value for the given object."
	(anObject isKindOf: Integer) ifTrue: [^ anObject printString].
	(anObject isKindOf: String) ifTrue: [^ '"', anObject, '"' ].
	(anObject isKindOf: Float) ifTrue: [^ anObject printString ].
	anObject == nil ifTrue: [^ 'null' ].
	anObject == true ifTrue: [^ 'true' ].
	anObject == false ifTrue: [^ 'false' ].
	self error:
		'Warning: A Smalltalk literal could not be translated into a C constant: ', anObject printString.
	^'"XXX UNTRANSLATABLE CONSTANT XXX"'!

----- Method: JSCodeGenerator>>checkAbstractMethods (in category 'error notification') -----
checkAbstractMethods
	"For each method that has been declared abstract, ensure that a concrete
	implementation has been provided. This check should be performed prior to
	inlining because methods may be removed during the inlining process."

	| selectors |
	selectors := methods keys, self uncheckedAbstractMethods.
	abstractDeclarations do: [:sel |
		(selectors includes: sel)
			ifFalse: [self notify: 'missing implementation for ', sel]]
!

----- Method: JSCodeGenerator>>checkClassForNameConflicts: (in category 'error notification') -----
checkClassForNameConflicts: aClass
	"Verify that the given class does not have constant, variable, or method names that conflict with
	 those of previously added classes. Raise an error if a conflict is found, otherwise just return."

	"check for constant name collisions in class pools"
	aClass classPool associationsDo:
		[:assoc |
		(constants includesKey: assoc key asString) ifTrue:
			[self error: 'Constant ', assoc key, ' was defined in a previously added class']].

	"and in shared pools"
	(aClass sharedPools reject: [:pool| pools includes: pool]) do:
		[:pool |
		pool bindingsDo:
			[:assoc |
			(constants includesKey: assoc key asString) ifTrue:
				[self error: 'Constant ', assoc key, ' was defined in a previously added class']]].

	"check for instance variable name collisions"
	(aClass inheritsFrom: VMStructType) ifFalse:
		[aClass instVarNames do:
			[:varName |
			(variables includes: varName) ifTrue:
				[self error: 'Instance variable ', varName, ' was defined in a previously added class']]].

	"check for method name collisions"
	aClass selectors do:
		[:sel |
		((methods includesKey: sel) and:
			[ | meth |
			meth := aClass compiledMethodAt: sel.
			meth isAbstract not and: [(meth pragmaAt: #doNotGenerate) isNil]]) ifTrue:
				[self error: 'Method ', sel, ' was defined in a previously added class.']]!

----- Method: JSCodeGenerator>>checkDeleteVariable: (in category 'utilities') -----
checkDeleteVariable: aName
	"Hook for debugging variable deletion."!

----- Method: JSCodeGenerator>>checkForGlobalUsage:in: (in category 'utilities') -----
checkForGlobalUsage: vars in: aJSMethod 
	| item |
	vars
		do: [:var | 
			"TPR - why the use of globalsAsSet here instead of globalVariables? 
			JMM - globalVariables is not initialized yet, variables is an OrderedCollection, 
				globalsAsSet returns variables as needed set"
			(self globalsAsSet includes: var)
				ifTrue: ["find the set of method names using this global var"
					item := globalVariableUsage
								at: var
								ifAbsent: [globalVariableUsage at: var put: Set new].
					"add this method name to that set"
					item add: aJSMethod selector]].
	aJSMethod referencesGlobalStructMakeZero!

----- Method: JSCodeGenerator>>checkNonPointer:op: (in category 'private') -----
checkNonPointer: node op: op
	node isVariable
		ifTrue: [(self typeOfVariable: node name) ifNotNil: [:type |
			(type includes: $*) ifTrue: [self halt: 'cannot do ', op, ' with ', type]]].!

----- Method: JSCodeGenerator>>codeString (in category 'public') -----
codeString
	"Return a string containing all the C code for the code base. Used for testing."

	| stream |
	stream := ReadWriteStream on: (String new: 1000).
	self emitJSCodeOn: stream doInlining: true doAssertions: true.
	^stream contents!

----- Method: JSCodeGenerator>>collectInlineList (in category 'inlining') -----
collectInlineList
	"Make a list of methods that should be inlined."
	"Details: The method must not include any inline C, since the translator cannot
	currently map variable names in inlined C code. The #inline: directive may be
	used to override this for cases in which the C code or declarations are harmless.
	Methods to be inlined must be small or called from only one place."

	| methodsNotToInline callsOf inlineIt hasCCode nodeCount senderCount
sel |
	methodsNotToInline := Set new: methods size.

	"build dictionary to record the number of calls to each method"
	callsOf := Dictionary new: methods size * 2.
	methods keys do: [ :s | callsOf at: s put: 0 ].

	"For each method, scan its parse tree once to:
		1. determine if the method contains C code or declarations
		2. determine how many nodes it has
		3. increment the sender counts of the methods it calls
		4. determine if it includes any C declarations or code"
	inlineList := Set new: methods size * 2.
	methods do: [ :m |
		inlineIt := #dontCare.
		(translationDict includesKey: m selector) ifTrue: [
			hasCCode := true.
		] ifFalse: [
			hasCCode := m declarations size > 0.
			nodeCount := 0.
			m parseTree nodesDo: [ :node |
				node isSend ifTrue: [
					sel := node selector.
					(sel = #cCode: or: [sel = #cCode:inSmalltalk:])
						ifTrue: [ hasCCode := true ].
					senderCount := callsOf at: sel ifAbsent: [ nil ].
					nil = senderCount ifFalse: [
						callsOf at: sel put: senderCount + 1.
					].
				].
				nodeCount := nodeCount + 1.
			].
			inlineIt := m extractInlineDirective.  "may be true, false, or
#dontCare"
		].
		(inlineIt ~= true and: [hasCCode or: [inlineIt = false]]) ifTrue: [
			"Don't inline if method has C code or if it contains a negative inline
			directive. If it contains a positive inline directive, permit inlining even
			if C code is present."
			methodsNotToInline add: m selector.
		] ifFalse: [
			((nodeCount < 40) or: [inlineIt = true]) ifTrue: [
				"inline if method has no C code and is either small or contains
inline directive"
				inlineList add: m selector.
			].
		].
	].

	callsOf associationsDo: [ :assoc |
		((assoc value = 1) and: [(methodsNotToInline includes: assoc key)
not]) ifTrue: [
			inlineList add: assoc key.
		].
	].!

----- Method: JSCodeGenerator>>compileToJSMethodSelector:in: (in category 'utilities') -----
compileToJSMethodSelector: selector in: aClass
	"Compile a method to a JSMethod"

	^(Compiler new
		parse: (aClass sourceCodeAt: selector)
		in: aClass
		notifying: nil)
			asTranslationMethodOfClass: self translationMethodClass!

----- Method: JSCodeGenerator>>currentMethod (in category 'accessing') -----
currentMethod
	^currentMethod!

----- Method: JSCodeGenerator>>currentMethod: (in category 'accessing') -----
currentMethod: aJSMethod
	currentMethod := aJSMethod!

----- Method: JSCodeGenerator>>declareMethodsStatic (in category 'accessing') -----
declareMethodsStatic
	"If true generated methods will be declared static. Default is true,
	appropriate for plugins."
	^ declareMethodsStatic
		ifNil: [declareMethodsStatic := true]!

----- Method: JSCodeGenerator>>declareMethodsStatic: (in category 'accessing') -----
declareMethodsStatic: aBoolean
	"If set false, generated methods will be not declared static.
	Default value is true."
	declareMethodsStatic := aBoolean!

----- Method: JSCodeGenerator>>declareModuleName: (in category 'public') -----
declareModuleName: nameString
	"add the declaration of a module name, version and local/external tag"

	self var: #moduleName declareC: 'var moduleName = "', nameString,' (e)"'.!

----- Method: JSCodeGenerator>>declareVar:type: (in category 'public') -----
declareVar: varName type: type
	"This both creates a varable and provides its type"
	self var: (variables add: varName asString) type: type!

----- Method: JSCodeGenerator>>doBasicInlining: (in category 'inlining') -----
doBasicInlining: inlineFlag
	"Inline the bodies of all methods that are suitable for inlining.
	This method does only the basic inlining suitable for both the core VM and plugins - no bytecode inlining etc"

	| pass progress max |
	inlineFlag ifFalse: [^self].
	self collectInlineList.
	pass := 0.
	max := 12. "More than this is probably due to infinite recursion" 
	progress := true.
	[progress] whileTrue: [
		"repeatedly attempt to inline methods until no further progress is made"
		progress := false.
		pass > max
			ifTrue: [self notify: 'too many inlining steps, inlining terminated']
			ifFalse: [('Inlining pass ', (pass := pass + 1) printString, '...')
						displayProgressAt: Sensor cursorPoint
						from: 0 to: methods size
						during: [:bar |
							(self sortMethods: methods) doWithIndex: [:m :i |
								bar value: i.
								currentMethod := m.
								(m tryToInlineMethodsIn: self)
									ifTrue: [progress := true]]]]].

!

----- Method: JSCodeGenerator>>doInlining: (in category 'inlining') -----
doInlining: inlineFlag
	"Inline the bodies of all methods that are suitable for inlining."
	"Modified slightly for the core VM translator, since the first level of inlining for the interpret loop must be performed in order that the instruction implementations can easily discover their addresses. Remember to inline the bytecode routines as well"

	inlineFlag ifFalse: [
		self inlineDispatchesInMethodNamed: #interpret localizingVars: #().
		^ self].
	self doBasicInlining: inlineFlag.
	self inlineCaseStatementBranchesInMethodNamed: #interpret localizingVars: #().
	'Inlining bytecodes'
		displayProgressAt: Sensor cursorPoint
		from: 1 to: 2
		during: [:bar |
			self inlineDispatchesInMethodNamed: #interpret
				localizingVars: #(currentBytecode localIP localSP localHomeContext localReturnContext localReturnValue).
			bar value: 1.
			self removeMethodsReferingToGlobals: #(
					currentBytecode localIP localSP localHomeContext)
				except: #(interpret).
			bar value: 2].
	self permitMethodPruning
		ifTrue: [self pruneUnreachableMethods]
!

----- Method: JSCodeGenerator>>emitBuiltinConstructAsArgumentFor:on:level: (in category 'utilities') -----
emitBuiltinConstructAsArgumentFor: msgNode on: aStream level: level
	"If the given selector is in the translation dictionary, translate it into a target code construct and return true. Otherwise, do nothing and return false."

	| action |
	action := asArgumentTranslationDict
				at: msgNode selector
				ifAbsent: [translationDict at: msgNode selector ifAbsent: [ ^false ]].
	self perform: action with: msgNode with: aStream with: level.
	^true!

----- Method: JSCodeGenerator>>emitBuiltinConstructFor:on:level: (in category 'utilities') -----
emitBuiltinConstructFor: msgNode on: aStream level: level
	"If the given selector is in the translation dictionary, translate it into a target code construct and return true. Otherwise, do nothing and return false."

	| action |
	action := translationDict at: msgNode selector ifAbsent: [ ^false ].
	self perform: action with: msgNode with: aStream with: level.
	^true!

----- Method: JSCodeGenerator>>emitDefaultMacrosOn: (in category 'JS code generator') -----
emitDefaultMacrosOn: aStream
	"Emit macros to provide default implementations of certain functions used by
	the interpreter. If not previously defined in config.h they will be defined here.
	The definitions will be available to any module that includes sqMemoryAccess.h.
	The default macros are chosen for backward compatibility with existing platform
	support code."

	"Reduce the obscurity of these macros by flagging some selectors to
	make this method show up as a sender."

	self flag: #assert:.
	"If assert() has not been defined e.g. by sqAssert.h, then use the standard clib version"
	aStream cr;
		nextPutAll: '#ifndef assert'; cr;
		nextPutAll: ' #include <assert.h>'; cr;
		nextPutAll: '#endif'; cr.

	self flag: #allocateMemory:minimum:imageFile:headerSize:.
	aStream cr;
		nextPutAll: '#ifndef allocateMemoryMinimumImageFileHeaderSize'; cr;
		nextPutAll: ' /* Called by Interpreter>>allocateMemory:minimum:imageFile:headerSize: */'; cr;
		nextPutAll: ' /* Default definition if not previously defined in config.h */'; cr;
		nextPutAll: ' #define allocateMemoryMinimumImageFileHeaderSize(',
						'heapSize, minimumMemory, fileStream, headerSize) \'; cr;
		nextPutAll: '    sqAllocateMemory(minimumMemory, heapSize)'; cr;
		nextPutAll: '#endif'; cr.

	self flag: #sqImage:read:size:length:.
	aStream cr;
		nextPutAll: '#ifndef sqImageFileReadEntireImage'; cr;
		nextPutAll: ' /* Called by Interpreter>>sqImage:read:size:length: */'; cr;
		nextPutAll: ' /* Default definition if not previously defined in config.h */'; cr;
		nextPutAll: ' #define sqImageFileReadEntireImage(memoryAddress, ',
						'elementSize,  length, fileStream) \'; cr;
		nextPutAll: '    sqImageFileRead(memoryAddress, elementSize,  length, fileStream)'; cr;
		nextPutAll: '#endif'; cr.

	self flag: #error:.
	aStream cr;
		nextPutAll: '#ifndef error'; cr;
		nextPutAll: ' /* error() function called from Interpreter */'; cr;
		nextPutAll: ' /* Default definition if not previously defined in config.h */'; cr;
		nextPutAll: ' #define error(str) defaultErrorProc(str)'; cr;
		nextPutAll: '#endif'; cr.

	self flag: #primitiveMicrosecondClock; flag: #ioMicroSecondClock.
	aStream cr;
		nextPutAll: '#ifndef ioMicroSecondClock'; cr;
		nextPutAll: ' /* Called by Interpreter>>primitiveMicrosecondClock and GC methods */'; cr;
		nextPutAll: ' /* Default definition if not previously defined in config.h */'; cr;
		nextPutAll: ' #define ioMicroSecondClock ioMSecs'; cr;
		nextPutAll: '#endif'; cr.

	self flag: #primitiveUtcWithOffset; flag: #setMicroSeconds:andOffset:.
	aStream cr;
		nextPutAll: '#ifndef ioUtcWithOffset'; cr;
		nextPutAll: ' /* Called by Interpreter>>primitiveUtcWithOffset */'; cr;
		nextPutAll: ' /* Default definition if not previously defined in config.h */'; cr;
		nextPutAll: ' #define ioUtcWithOffset(clock, offset) setMicroSecondsandOffset(clock, offset)'; cr;
		nextPutAll: '#endif'; cr.
!

----- Method: JSCodeGenerator>>emitDefineBytesPerWordOn: (in category 'JS code generator') -----
emitDefineBytesPerWordOn: aStream
	"Define word size dependent constants. These are mirrored by class
	variables in ObjectMemory. The macro definitions here are used at compile
	time to permit building a VM for either 32-bit or 64-bit object memory from
	a single generated code base.
	
	If SQ_VI_BYTES_PER_WORD is defined as 8 (e.g. in config.h), then a VM for
	64-bit image will be built. Otherwise, a VM for 32-bit image is built."

	aStream cr;
		nextPutAll: '/*'; cr;
		nextPutAll: ' * define SQ_VI_BYTES_PER_WORD 8 for a 64-bit word size VM'; cr;
		nextPutAll: ' * and default to SQ_VI_BYTES_PER_WORD 4 for a 32-bit word size VM'; cr;
		nextPutAll: ' */'; cr;
		nextPutAll: '#ifndef SQ_VI_BYTES_PER_WORD'; cr;
		nextPutAll: '# define SQ_VI_BYTES_PER_WORD ';
		print: 4; cr; "default to word size 4"
		nextPutAll: '#endif'; cr; cr;
		nextPutAll: '#define BYTES_PER_WORD SQ_VI_BYTES_PER_WORD'; cr;
		nextPutAll: '#define BASE_HEADER_SIZE SQ_VI_BYTES_PER_WORD'; cr;

		"Define various constants that depend on BytesPerWord"
		nextPutAll: '#if (BYTES_PER_WORD == 4) // 32-bit object memory'; cr;
		nextPutAll: '# define WORD_MASK 0xffffffff'; cr; "(1 bitShift: BytesPerWord*8) - 1"
		nextPutAll: '# define SHIFT_FOR_WORD 2'; cr; "(BytesPerWord log: 2) rounded"
		nextPutAll: '# define SMALL_CONTEXT_SIZE 92'; cr; "ContextFixedSizePlusHeader + 16 * BytesPerWord"
		"Large contexts have 56 indexable fileds.  Max with single header word."
		"However note that in 64 bits, for now, large contexts have 3-word headers"
		nextPutAll: '# define LARGE_CONTEXT_SIZE 252'; cr; "ContextFixedSizePlusHeader + 56 * BytesPerWord."
		nextPutAll: '# define SIZE_MASK 0xfc'; cr; "Base header word bit field"
		nextPutAll: '# define LONG_SIZE_MASK 0xfffffffc'; cr; "Base header word bit field"
		nextPutAll: '# define SIZE_4_BIT 0'; cr;
		nextPutAll: '# define MARK_BIT 0x80000000'; cr; "Top bit, 1 bitShift: BytesPerWord*8 - 1"
		nextPutAll: '# define ROOT_BIT 0x40000000'; cr; "Next-to-top bit, 1 bitShift: BytesPerWord*8 - 2"
		nextPutAll: '# define ALL_BUT_MARK_BIT 0x7fffffff'; cr; "WordMask - MarkBit."
		nextPutAll: '# define ALL_BUT_ROOT_BIT 0xbfffffff'; cr; "WordMask - RootBit"
		nextPutAll: '# define ALL_BUT_TYPE_MASK 0xfffffffc'; cr; "WordMask - TypeMask"
		nextPutAll: '# define ALL_BUT_MARK_BIT_AND_TYPE_MASK 0x7ffffffc'; cr; "AllButTypeMask - MarkBit"
		nextPutAll: '# define ALL_BUT_HASH_BITS 0xe001ffff'; cr;
		nextPutAll: '# define SMALL_CONTEXT_SIZE 92'; cr; "16 indexable fields"
		nextPutAll: '# define LARGE_CONTEXT_SIZE 252'; cr; "56 indexable fields"

		nextPutAll: '#else // 64-bit object memory'; cr;
		nextPutAll: '# define WORD_MASK 0xffffffffffffffff'; cr;
		nextPutAll: '# define SHIFT_FOR_WORD 3'; cr;
		nextPutAll: '# define SMALL_CONTEXT_SIZE 184'; cr;
		nextPutAll: '# define LARGE_CONTEXT_SIZE 504'; cr;
		nextPutAll: '# define SIZE_MASK 0xf8'; cr; "Lose the 4 bit in temp 64-bit chunk format"
		nextPutAll: '# define LONG_SIZE_MASK 0xfffffffffffffff8'; cr;
		"The 4 bit is excluded from SIZE_MASK for 64-bit object memory, but need it"
		"for ST size, so define SIZE_4_BIT."
		nextPutAll: '# define SIZE_4_BIT 4'; cr;
		nextPutAll: '# define MARK_BIT 0x8000000000000000'; cr;
		nextPutAll: '# define ROOT_BIT 0x4000000000000000'; cr;
		nextPutAll: '# define ALL_BUT_MARK_BIT 0x7fffffffffffffff'; cr;
		nextPutAll: '# define ALL_BUT_ROOT_BIT 0xbfffffffffffffff'; cr;
		nextPutAll: '# define ALL_BUT_TYPE_MASK 0xfffffffffffffffc'; cr;
		nextPutAll: '# define ALL_BUT_MARK_BIT_AND_TYPE_MASK 0x7ffffffffffffffc'; cr;
		nextPutAll: '# define ALL_BUT_HASH_BITS 0xffffffffe001ffff'; cr;
		nextPutAll: '# define SMALL_CONTEXT_SIZE 184'; cr;
		nextPutAll: '# define LARGE_CONTEXT_SIZE 504'; cr;
		nextPutAll: '#endif //  (BYTES_PER_WORD == 4)'; cr
	
!

----- Method: JSCodeGenerator>>emitDefineMemoryAccessInImageOn: (in category 'JS code generator') -----
emitDefineMemoryAccessInImageOn: aStream
	"If MemoryAccess is present in the image, then define MEMORY_ACCESS_IN_IMAGE as
	a C preprocessor macro. When MEMORY_ACCESS_IN_IMAGE is defined, the traditional
	C preprocessor macros for low level memory access are ignored and will be replaced
	by directly translated (and inlined) SLANG versions of the same. This enables visibility
	of the memory access functions for debuggers and profilers."

	(Smalltalk classNamed: #MemoryAccess)
		ifNotNilDo: [:ma | ma isEnabled
			ifTrue: [aStream nextPutAll: '#define MEMORY_ACCESS_IN_IMAGE 1'; cr]]!

----- Method: JSCodeGenerator>>emitExportsOn: (in category 'JS code generator') -----
emitExportsOn: aStream
	"Store all the exported primitives in a form to be used by the internal named prim system"
	aStream nextPutAll:'

void* vm_exports[][3] = {'.
	self exportedPrimitiveNames do:[:primName|
		aStream cr;
			nextPutAll:'	{"", "'; 
			nextPutAll: primName; 
			nextPutAll:'", (void*)'; 
			nextPutAll: primName;
			nextPutAll:'},'.
	].
	aStream nextPutAll:'
	{NULL, NULL, NULL}
};
'.!

----- Method: JSCodeGenerator>>emitGlobalStructFlagOn: (in category 'JS code generator') -----
emitGlobalStructFlagOn: aStream
	"Default: do nothing.  Overridden in CCGenGlobalStruct."
!

----- Method: JSCodeGenerator>>emitJSCodeOn:doAssertions: (in category 'JS code generator') -----
emitJSCodeOn: aStream doAssertions: assertionFlag
	"Emit C code for all methods in the code base onto the given stream. All inlined method calls should already have been expanded."

	self emitJSHeaderOn: aStream.
	self emitJSTypesOn: aStream.
	self emitJSConstantsOn: aStream.
	self emitJSVariablesOn: aStream.
"'Writing Translated Code...'
displayProgressAt: Sensor cursorPoint
from: 0 to: methods size
during: [:bar |"
	preparedMethodList doWithIndex: [ :m :i | "bar value: i."
		m emitJSCodeOn: aStream generator: self].
"]."
	self emitExportsOn: aStream.
!

----- Method: JSCodeGenerator>>emitJSCodeOn:doInlining:doAssertions: (in category 'JS code generator') -----
emitJSCodeOn: aStream doInlining: inlineFlag doAssertions: assertionFlag
	"Emit C code for all methods in the code base onto the given stream. All inlined method calls should already have been expanded."

	self prepareMethodsInlined: inlineFlag doAssertions: assertionFlag.
	^ self emitJSCodeOn: aStream doAssertions: assertionFlag
!

----- Method: JSCodeGenerator>>emitJSConstantsOn: (in category 'JS code generator') -----
emitJSConstantsOn: aStream
	"Store the global variable declarations on the given stream."
	| unused constList node |
	unused := constants keys asSet.
	methods do: [ :meth |
		meth parseTree nodesDo: [ :n |
			n isConstant ifTrue: [ unused remove: n name ifAbsent: []]]].
	constList := constants keys reject: [ :any | unused includes: any].
	constList isEmpty ifTrue: [^self].
	aStream nextPutAll: '/*** Constants ***/';
		 cr.
	constList asSortedCollection do: [ :varName |
		node := constants at: varName.
		node name isEmpty ifFalse: [
			aStream nextPutAll: '#define '.
			aStream nextPutAll: node name.
			aStream space.
			aStream nextPutAll: (self cLiteralFor: node value).
			aStream cr
		].
	].
	aStream cr.!

----- Method: JSCodeGenerator>>emitJSExpression:on: (in category 'JS code generator') -----
emitJSExpression: aParseNode on: aStream 
	"Emit C code for the expression described by the given parse node."

	aParseNode isLeaf 
		ifTrue: 
			["omit parens"
			 aParseNode emitJSCodeAsExpressionOn: aStream level: 0 generator: self]
		ifFalse: 
			[aStream nextPut: $(.
			 aParseNode emitJSCodeAsExpressionOn: aStream level: 0 generator: self.
			 aStream nextPut: $)]!

----- Method: JSCodeGenerator>>emitJSHeaderForPrimitivesOn: (in category 'JS code generator') -----
emitJSHeaderForPrimitivesOn: aStream
	"Write a C file header for compiled primitives onto the given stream."

	aStream
		nextPutAll: '/* Automatically generated from Squeak (';
		nextPutAll: VMMaker versionString;
		nextPutAll: ') on '.
	Time dateAndTimeNow do: [:e | aStream nextPutAll: e asString; nextPut: Character space].
	aStream
		nextPutAll: '*/';
		cr; cr;
		nextPutAll: '#include "sq.h"'; cr; cr.

	"Additional header files"
	headerFiles do:[:hdr|
		aStream nextPutAll:'#include '; nextPutAll: hdr; cr].

	aStream nextPutAll: '
#include "sqMemoryAccess.h"

/*** Imported Functions/Variables ***/
extern sqInt stackValue(sqInt);
extern sqInt stackIntegerValue(sqInt);
extern sqInt successFlag;

/* allows accessing Strings in both C and Smalltalk */
#define asciiValue(c) c
'.
	aStream cr.!

----- Method: JSCodeGenerator>>emitJSHeaderOn: (in category 'JS code generator') -----
emitJSHeaderOn: aStream
	"Write a C file header onto the given stream."

	aStream nextPutAll: '/* '.
	aStream nextPutAll: VMMaker headerNotice.
	aStream nextPutAll: ' */'; cr.
	self emitGlobalStructFlagOn: aStream.
	aStream nextPutAll: '#include "sq.h"'; cr.

	"Additional header files"
	headerFiles do:[:hdr|
		aStream nextPutAll:'#include '; nextPutAll: hdr; cr].

	"Default definitions for optional functions, provided for backward compatibility"
	self emitDefaultMacrosOn: aStream.

	aStream nextPutAll: '
#include "sqMemoryAccess.h"

sqInt printCallStack(void);
void defaultErrorProc(char *s) {
	/* Print an error message and exit. */
	static sqInt printingStack = false;

	printf("\n%s\n\n", s);
	if (!!printingStack) {
		/* flag prevents recursive error when trying to print a broken stack */
		printingStack = true;
		printCallStack();
	}
	exit(-1);
}
'.
	aStream cr.!

----- Method: JSCodeGenerator>>emitJSTestBlock:on: (in category 'JS code generator') -----
emitJSTestBlock: aBlockNode on: aStream
	"Emit C code for the given block node to be used as a loop test."

	aBlockNode statements size > 1 ifTrue: [
		aBlockNode emitJSCodeOn: aStream level: 0 generator: self.
	] ifFalse: [
		aBlockNode statements first asExpression emitJSCodeOn: aStream level: 0 generator: self.
	].!

----- Method: JSCodeGenerator>>emitJSTypesOn: (in category 'JS code generator') -----
emitJSTypesOn: aStream 
	"Store local type declarations on the given stream."
	vmClass ifNotNil:
		[vmClass ancilliaryStructClasses do:
			[:structClass|
			(vmClass shouldGenerateTypedefFor: structClass) ifTrue:
				[structClass printTypedefOn: aStream.
				 aStream cr; cr]]]!

----- Method: JSCodeGenerator>>emitJSVariablesOn: (in category 'JS code generator') -----
emitJSVariablesOn: aStream 
	"Store the global variable declarations on the given stream."
	aStream nextPutAll: '/*** Variables ***/'; cr.
	variables asSortedCollection
		do: [:var | 	| varString varDecl |
			varString := var asString.
			aStream nextPutAll: 'var ', varString.
			varDecl := variableDeclarations at: varString ifAbsent: [''].
			(varDecl includes: $=)
				ifTrue: [aStream nextPutAll: ' =', (varDecl copyAfter: $=)].
			aStream nextPutAll: ';'; cr].
	aStream cr.
!

----- Method: JSCodeGenerator>>emitVmmVersionOn: (in category 'JS code generator') -----
emitVmmVersionOn: aStream
	"Emit a version string macro suitable for identifying source code version
	of this interpreter. This is expected to be used in conjunction with a similar
	identifier for platform source code version, such the the VM can identify
	the source code version for its platform source and matching VMMaker source."

	aStream nextPutAll: '#define VMMAKER_VERSION "';
		nextPutAll: VMMaker versionString;
		nextPut: $";
		cr
!

----- Method: JSCodeGenerator>>exportedPrimitiveNames (in category 'public') -----
exportedPrimitiveNames
	"Return an array of all exported primitives"
	^methods select:[:m| m export] thenCollect:[:m| m selectorForCodeGeneration copyWithout: $:].
!

----- Method: JSCodeGenerator>>fileHeaderVersionStampForSourceClass: (in category 'JS code generator') -----
fileHeaderVersionStampForSourceClass: sourceClass
	"Answer a suitable version stamp to include in the header."
	|  slangDescription sourceDescription |
	slangDescription := self class monticelloDescriptionFor: self class.
	sourceClass ifNotNil:
		[sourceDescription := [sourceClass monticelloDescription]
								on: MessageNotUnderstood
								do: [:ex| self class monticelloDescriptionFor: sourceClass]].
	^String streamContents:
		[:s|
		s nextPutAll: '/* Automatically generated by\	' withCRs.
		s nextPutAll: slangDescription.
		sourceDescription ifNotNil:
			[s nextPutAll: '\   from\	' withCRs; nextPutAll: (sourceDescription copyReplaceAll: '\' withCRs with: '\	' withCRs)].
		s cr; nextPutAll: ' */'; cr]!

----- Method: JSCodeGenerator>>generateAddressOf:on:indent: (in category 'JS translation') -----
generateAddressOf: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPut: $(; nextPut: $&.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPut: $)!

----- Method: JSCodeGenerator>>generateAnd:on:indent: (in category 'JS translation') -----
generateAnd: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' && '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateAsFloat:on:indent: (in category 'JS translation') -----
generateAsFloat: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll:'((double) '.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' )'.!

----- Method: JSCodeGenerator>>generateAsInteger:on:indent: (in category 'JS translation') -----
generateAsInteger: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll:'((sqInt)'.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $)!

----- Method: JSCodeGenerator>>generateAsSymbol:on:indent: (in category 'JS translation') -----
generateAsSymbol: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream.
	 The receiver is expected to be a JSConstantNode."

	aStream nextPutAll: (self cFunctionNameFor: msgNode receiver nameOrValue)!

----- Method: JSCodeGenerator>>generateAsUnsignedInteger:on:indent: (in category 'JS translation') -----
generateAsUnsignedInteger: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll:'((usqInt)'.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $)!

----- Method: JSCodeGenerator>>generateAt:on:indent: (in category 'JS translation') -----
generateAt: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $[.
	msgNode args first emitJSCodeAsExpressionOn: aStream level: level + 1 generator: self.
	aStream nextPut: $]!

----- Method: JSCodeGenerator>>generateAtPut:on:indent: (in category 'JS translation') -----
generateAtPut: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $[.
	msgNode args first emitJSCodeAsExpressionOn: aStream level: level + 1 generator: self.
	aStream nextPutAll: '] = '.
	self emitJSExpression: msgNode args last on: aStream!

----- Method: JSCodeGenerator>>generateBaseHeaderSize:on:indent: (in category 'JS translation') -----
generateBaseHeaderSize: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll: 'BASE_HEADER_SIZE'

!

----- Method: JSCodeGenerator>>generateBetweenAnd:on:indent: (in category 'JS translation') -----
generateBetweenAnd: msgNode on: aStream indent: level
	"Generate the JS code for the between:and: message onto the given stream."

	aStream nextPutAll: '(('.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' >= '.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPutAll: ') && ('.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' <= '.
	self emitJSExpression: msgNode args second on: aStream.
	aStream nextPutAll: '))'!

----- Method: JSCodeGenerator>>generateBitAnd:on:indent: (in category 'JS translation') -----
generateBitAnd: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' & '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateBitClear:on:indent: (in category 'JS translation') -----
generateBitClear: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: '(('.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' | '.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPutAll: ') - '.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPut: '|0))'!

----- Method: JSCodeGenerator>>generateBitInvert32:on:indent: (in category 'JS translation') -----
generateBitInvert32: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPut: $~.
	self emitJSExpression: msgNode receiver on: aStream!

----- Method: JSCodeGenerator>>generateBitOr:on:indent: (in category 'JS translation') -----
generateBitOr: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' | '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateBitShift:on:indent: (in category 'JS translation') -----
generateBitShift: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	| arg rcvr |
	arg := msgNode args first.
	rcvr := msgNode receiver.
	arg isConstant ifTrue: [
		"bit shift amount is a constant"
		aStream nextPutAll: '('.
		self emitJSExpression: rcvr on: aStream.
		arg value < 0 ifTrue: [
			aStream nextPutAll: ' >>> ', arg value negated printString.
		] ifFalse: [
			aStream nextPutAll: ' << ', arg value printString.
		].
		aStream nextPutAll: ')'.
	] ifFalse: [
		"bit shift amount is an expression"
		aStream nextPutAll: '('.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ' < 0 ? '.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' >>> (0 - '.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ') : '.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' << '.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ')'.
	].!

----- Method: JSCodeGenerator>>generateBitXor:on:indent: (in category 'JS translation') -----
generateBitXor: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' ^ '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateByteSizeOfBytes:on:indent: (in category 'JS hacks') -----
generateByteSizeOfBytes: msgNode on: aStream indent: level
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.bytes ? '.
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.bytes.length : 0'.
!

----- Method: JSCodeGenerator>>generateBytesPerWord:on:indent: (in category 'JS translation') -----
generateBytesPerWord: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll: 'BYTES_PER_WORD'
!

----- Method: JSCodeGenerator>>generateCCoercion:on:indent: (in category 'JS translation') -----
generateCCoercion: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
	| expr |.
	expr := msgNode args first.
	(expr isSend and: [expr receiver name = 'interpreterProxy' and: [expr selector = #firstIndexableField:]]) ifTrue: [
		| cType |
		cType := msgNode args second.
		cType value = 'unsigned char *' ifTrue: [
			self emitJSExpression: expr args first on: aStream.
			^aStream nextPutAll: '.bytes'.
		].
		self halt.
	] ifFalse: [
		self halt.
		self emitJSExpression: expr on: aStream.
	]
!

----- Method: JSCodeGenerator>>generateCDigitCopy:on:indent: (in category 'JS hacks') -----
generateCDigitCopy: msgNode on: aStream indent: level
	"LargeIntegerPlugin>>cDigitReplace:from:to:with:startingAt: uses pointer arithmetic. Replace it here"
	msgNode args first selector = #+ ifFalse: [
		^msgNode emitJSCodeAsFunctionCallOn: aStream level: level generator: self].
	msgNode asString = 'self cDigitCopyFrom: pFrom + repStart to: pTo + start len: stop - start + 1'
		ifFalse: [self halt: 'not handled: ', msgNode asString].
	aStream nextPutAll: 'function() {
		// inlining ', msgNode asString, '
		debugger;
		var len = stop - start + 1;
		for (var i = 0; i < len; i++) {
			pTo[i + start] = pFrom[i + repStart];
		}
		return 0;
	}();
'!

----- Method: JSCodeGenerator>>generateDeadCode (in category 'accessing') -----
generateDeadCode
	"Answer whether we should generate 'dead code' branches. This can be useful for hacking the VM when used in conjunction with #useSymbolicConstants, e.g., for code like:
		DoAssertionChecks ifTrue:[
			...
		].

	we will generate

		#define DoAssertionChecks 0
		...
		if(DoAssertionChecks) {
			...
		}.

	allowing us to change the #define (or redefine it as a variable) for later use."
	^generateDeadCode!

----- Method: JSCodeGenerator>>generateDeadCode: (in category 'accessing') -----
generateDeadCode: aBool
	"Indicate whether we should generate 'dead code' branches."
	generateDeadCode := aBool!

----- Method: JSCodeGenerator>>generateDivide:on:indent: (in category 'JS translation') -----
generateDivide: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	| rcvr arg divisor |
	rcvr := msgNode receiver.
	arg := msgNode args first.
	(arg isConstant and:
	 [UseRightShiftForDivide and:
	 [(divisor := arg value) isInteger and:
	 [divisor isPowerOfTwo and:
	 [divisor > 0 and:
	 [divisor <= (1 bitShift: 31)]]]]])
	ifTrue: [
		"use signed (arithmetic) right shift instead of divide"
		aStream nextPutAll: '('.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' >> ', (divisor log: 2) asInteger printString.
		aStream nextPutAll: ')'.
	] ifFalse: [
		"use float divide and coerce to integer"
		aStream nextPutAll: '('.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' / '.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: '|0)'.
	].
!

----- Method: JSCodeGenerator>>generateDoWhileFalse:on:indent: (in category 'JS translation') -----
generateDoWhileFalse: msgNode on: aStream indent: level
	"Generate do {stmtList} while(!!(cond))"

	| stmts testStmt |
	stmts := msgNode receiver statements asOrderedCollection.
	testStmt := stmts removeLast.
	msgNode receiver setStatements: stmts.
	aStream nextPutAll: 'do {'; cr.
	msgNode receiver emitJSCodeOn: aStream level: level + 1 generator: self.
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '} while(!!('.
	testStmt asExpression emitJSCodeOn: aStream level: 0 generator: self.
	aStream nextPutAll: '))'.!

----- Method: JSCodeGenerator>>generateDoWhileTrue:on:indent: (in category 'JS translation') -----
generateDoWhileTrue: msgNode on: aStream indent: level
	"Generate do {stmtList} while(cond)"

	| stmts testStmt |
	stmts := msgNode receiver statements asOrderedCollection.
	testStmt := stmts removeLast.
	msgNode receiver setStatements: stmts.
	aStream nextPutAll: 'do {'; cr.
	msgNode receiver emitJSCodeOn: aStream level: level + 1 generator: self.
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '} while('.
	testStmt asExpression emitJSCodeOn: aStream level: 0 generator: self.
	aStream nextPutAll: ')'.!

----- Method: JSCodeGenerator>>generateEqual:on:indent: (in category 'JS translation') -----
generateEqual: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' === '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateFetchClassOf:on:indent: (in category 'JS hacks') -----
generateFetchClassOf: msgNode on: aStream indent: level
	aStream nextPut: $(.
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.sqClass ? '.
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.sqClass : interpreterProxy.classSmallInteger()'.
	aStream nextPut: $).
!

----- Method: JSCodeGenerator>>generateFirstIndexableField:on:indent: (in category 'JS hacks') -----
generateFirstIndexableField: msgNode on: aStream indent: level
	| parent cType accessor |
	"HACK: detect cType from parent node"
	parent := thisContext sender sender sender.
	cType := parent method == (TAssignmentNode>>#emitJSCodeOn:level:generator:) 
			ifTrue: [self typeOfVariable: parent receiver variable name] ifFalse: [
		parent method == (TSendNode>>#emitJSCodeAsFunctionCallOn:level:generator:)
			ifTrue: [self typeOfArgument: (parent receiver args indexOf: msgNode) in: parent receiver selector] ifFalse: [
		self halt]].
	cType ifNotNil: [
		accessor := (cType beginsWith: 'unsigned char *') ifTrue: ['.bytes']
			ifFalse: [(cType beginsWith: 'char *') ifTrue: ['.bytes']
			ifFalse: [self halt: 'need to handle ', cType]].
		accessor ifNotNil: [msgNode args first emitJSCodeOn: aStream level: level generator: self.
			^aStream nextPutAll: accessor]].
	"generic code below, not needed ever hopefully"
	aStream nextPutAll: 'interpreterProxy.'.
	^ msgNode emitJSCodeAsFunctionCallOn: aStream level: level generator: self!

----- Method: JSCodeGenerator>>generateGreaterThan:on:indent: (in category 'JS translation') -----
generateGreaterThan: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' > '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateGreaterThanOrEqual:on:indent: (in category 'JS translation') -----
generateGreaterThanOrEqual: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' >= '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateIfFalse:on:indent: (in category 'JS translation') -----
generateIfFalse: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPutAll: 'if (!!('.
			msgNode receiver emitJSCodeAsExpressionOn: aStream level: level + 1 generator: self.
			aStream nextPutAll: ')) {'; cr.
			msgNode args last emitJSCodeOn: aStream level: level + 1 generator: self.
			level timesRepeat: [aStream tab].
			aStream nextPut: $}]
		ifNotNil:
			[:const |
			const ifFalse:
				[msgNode args first emitJSCodeOn: aStream level: level generator: self]]!

----- Method: JSCodeGenerator>>generateIfFalseAsArgument:on:indent: (in category 'JS translation') -----
generateIfFalseAsArgument: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPut: $(.
			 msgNode receiver emitJSCodeAsArgumentOn: aStream level: level generator: self.
			 aStream crtab: level + 1; nextPutAll: ' ? 0 : '.
			 msgNode args first emitJSCodeAsArgumentOn: aStream level: level + 2 generator: self.
			 aStream crtab: level + 1; nextPut: $)]
		ifNotNil:
			[:const|
			const ifFalse:
				[msgNode args first emitJSCodeAsArgumentOn: aStream level: level generator: self]]!

----- Method: JSCodeGenerator>>generateIfFalseIfTrue:on:indent: (in category 'JS translation') -----
generateIfFalseIfTrue: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPutAll: 'if ('.
			msgNode receiver emitJSCodeAsExpressionOn: aStream level: level generator: self.
			aStream nextPutAll: ') {'; cr.
			msgNode args last emitJSCodeOn: aStream level: level + 1 generator: self.
			aStream tab: level; nextPut: $}; nextPutAll: ' else {'; cr.
			msgNode args first emitJSCodeOn: aStream level: level + 1 generator: self.
			aStream tab: level; nextPut: $}]
		ifNotNil:
			[:const |
			 (const ifTrue: [msgNode args last] ifFalse: [msgNode args first])
				emitJSCodeOn: aStream level: level generator: self]!

----- Method: JSCodeGenerator>>generateIfFalseIfTrueAsArgument:on:indent: (in category 'JS translation') -----
generateIfFalseIfTrueAsArgument: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPut: $(.
			msgNode receiver emitJSCodeAsArgumentOn: aStream level: level generator: self.
			aStream crtab: level + 1; nextPut: $?; space.
			msgNode args last emitJSCodeAsArgumentOn: aStream level: level + 2 generator: self.
			aStream crtab: level + 1; nextPut: $:; space.
			msgNode args first emitJSCodeAsArgumentOn: aStream level: level + 2 generator: self.
			aStream nextPut: $)]
		ifNotNil:
			[:const|
			(const
				ifTrue: [msgNode args last]
				ifFalse: [msgNode args first])
					emitJSCodeAsArgumentOn: aStream level: level generator: self]!

----- Method: JSCodeGenerator>>generateIfTrue:on:indent: (in category 'JS translation') -----
generateIfTrue: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPutAll: 'if ('.
			msgNode receiver emitJSCodeAsExpressionOn: aStream level: level generator: self.
			aStream nextPutAll: ') {'; cr.
			msgNode args first emitJSCodeOn: aStream level: level + 1 generator: self.
			level timesRepeat: [ aStream tab ].
			aStream nextPut: $}]
		ifNotNil:
			[:const |
			const ifTrue:
				[msgNode args first emitJSCodeOn: aStream level: level generator: self]]!

----- Method: JSCodeGenerator>>generateIfTrueAsArgument:on:indent: (in category 'JS translation') -----
generateIfTrueAsArgument: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPut: $(.
			 msgNode receiver emitJSCodeAsArgumentOn: aStream level: level generator: self.
			 aStream crtab: level + 1; nextPut: $?; space.
			 msgNode args first emitJSCodeAsArgumentOn: aStream level: level + 2 generator: self.
			 aStream crtab: level + 1; nextPutAll: ': 0)']
		ifNotNil:
			[:const|
			const ifTrue:
				[msgNode args first emitJSCodeAsArgumentOn: aStream level: level generator: self]]!

----- Method: JSCodeGenerator>>generateIfTrueIfFalse:on:indent: (in category 'JS translation') -----
generateIfTrueIfFalse: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPutAll: 'if ('.
			msgNode receiver emitJSCodeAsExpressionOn: aStream level: level generator: self.
			aStream nextPutAll: ') {'; cr.
			msgNode args first emitJSCodeOn: aStream level: level + 1 generator: self.
			aStream tab: level; nextPut: $}; nextPutAll: ' else {'; cr.
			msgNode args last emitJSCodeOn: aStream level: level + 1 generator: self.
			aStream tab: level; nextPut: $}]
		ifNotNil:
			[:const |
			(const ifTrue: [msgNode args first] ifFalse: [msgNode args last])
				emitJSCodeOn: aStream level: level generator: self]!

----- Method: JSCodeGenerator>>generateIfTrueIfFalseAsArgument:on:indent: (in category 'JS translation') -----
generateIfTrueIfFalseAsArgument: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	(self nilOrBooleanConstantReceiverOf: msgNode)
		ifNil:
			[aStream nextPut: $(.
			msgNode receiver emitJSCodeAsArgumentOn: aStream level: level generator: self.
			aStream crtab: level + 1; nextPut: $?; space.
			msgNode args first emitJSCodeAsArgumentOn: aStream level: level + 2 generator: self.
			aStream crtab: level + 1; nextPut: $:; space.
			msgNode args last emitJSCodeAsArgumentOn: aStream level: level + 2 generator: self.
			aStream nextPut: $)]
		ifNotNil:
			[:const|
			(const ifTrue: [msgNode args first] ifFalse: [msgNode args last])
				emitJSCodeAsArgumentOn: aStream level: level generator: self]!

----- Method: JSCodeGenerator>>generateInlineCCode:on:indent: (in category 'JS translation') -----
generateInlineCCode: msgNode on: aStream indent: level
	"Generate the C code for this message onto the given stream.
	 There are two forms, self cCode: aString ... and self cCode: aBlock."
	msgNode args first isConstant
		ifTrue: [
			self generateJSCodeForCcode: msgNode args first value on: aStream indent: level]
		ifFalse: [
			msgNode args first
					emitCCodeOn: aStream
					level: level
					generator: self]!

----- Method: JSCodeGenerator>>generateInlineCCodeAsArgument:on:indent: (in category 'JS translation') -----
generateInlineCCodeAsArgument: msgNode on: aStream indent: level
	"Generate the C code for this message onto the given stream.
	 There are two forms, self cCode: aString ... and self cCode: aBlock."

	msgNode args first isConstant
		ifTrue: [self generateJSCodeForCcode: msgNode args first value
			on: aStream indent: level]
		ifFalse: [msgNode args first
					emitCCodeAsArgumentOn: aStream
					level: level
					generator: self]!

----- Method: JSCodeGenerator>>generateInlineCPreprocessorDirective:on:indent: (in category 'JS translation') -----
generateInlineCPreprocessorDirective: msgNode on: aStream indent: level
	"Generate the C preprocessor directive for this message onto the given stream."
self halt.
	aStream cr; nextPutAll: msgNode args first value!

----- Method: JSCodeGenerator>>generateInlineCppDirective:on:indent: (in category 'JS translation') -----
generateInlineCppDirective: msgNode on: aStream indent: level
	"Generate the C code for this message onto the given stream."
self halt.
	aStream cr; nextPutAll: '# ', msgNode args first value.!

----- Method: JSCodeGenerator>>generateInlineCppIfDef:on:indent: (in category 'JS translation') -----
generateInlineCppIfDef: msgNode on: aStream indent: level
	"Generate the C code for this message onto the given stream."

	| comment |
self halt.
	aStream cr; nextPutAll: '# ifdef ', msgNode args first value.
	comment := msgNode args third value.
	(comment isKindOf: String)
		ifTrue: [aStream nextPutAll: '  // ', comment]
		ifFalse: ["nil argument, ignore it"].
	aStream cr.
	msgNode isExpression
		ifTrue:
			[aStream tab: level + 1; nextPut: $(.
			msgNode args fourth asExpression
				emitJSCodeOn: aStream level: level + 1 generator: self.
			aStream nextPut: $); cr]
		ifFalse:
			[msgNode args fourth
				emitJSCodeOn: aStream level: level generator: self].
	aStream nextPutAll: '# endif  // ', msgNode args first value; cr; tab: level!

----- Method: JSCodeGenerator>>generateInlineCppIfDefElse:on:indent: (in category 'JS translation') -----
generateInlineCppIfDefElse: msgNode on: aStream indent: level
	"Generate the C code for this message onto the given stream."

	| comment alternateBlock alternateBlockIsNil |
self halt.
	aStream cr; nextPutAll: '# ifdef ', msgNode args first value.
	comment := msgNode args third value.
	(comment isKindOf: String)
		ifTrue: [aStream nextPutAll: '  // ', comment]
		ifFalse: ["nil argument, ignore it"].
	aStream cr.
	msgNode isExpression
		ifTrue:
			[aStream tab: level + 1; nextPut: $(.
			msgNode args fourth asExpression
				emitJSCodeOn: aStream level: level + 1 generator: self.
			aStream nextPut: $); cr]
		ifFalse:
			[msgNode args fourth
				emitJSCodeOn: aStream level: level generator: self].
	alternateBlock := msgNode args fifth.
	alternateBlockIsNil := true. "check for nil #else clause"
	alternateBlock nodesDo: [:n |
		(n ~= alternateBlock and: [n name ~= 'nil'])
			ifTrue: [alternateBlockIsNil := false ]].
	(alternateBlockIsNil) ifFalse:
		[aStream nextPutAll: '# else'; cr.
		msgNode isExpression
			ifTrue:
				[aStream tab: level + 1; nextPut: $(.
				alternateBlock asExpression
					emitJSCodeOn: aStream level: level + 1 generator: self.
				aStream nextPut: $); cr]
			ifFalse:
				[alternateBlock
					emitJSCodeOn: aStream level: level generator: self]].
	aStream nextPutAll: '# endif  // ', msgNode args first value; cr; tab: level
!

----- Method: JSCodeGenerator>>generateInlineCppIfElse:on:indent: (in category 'JS translation') -----
generateInlineCppIfElse: msgNode on: aStream indent: level
	"Generate the C code for this message onto the given stream."

	| comment alternateBlock alternateBlockIsNil |
self halt.
	aStream cr; nextPutAll: '# if (', msgNode args first value, ')'.
	comment := msgNode args third value.
	(comment isKindOf: String)
		ifTrue: [aStream nextPutAll: '  // ', comment]
		ifFalse: ["nil argument, ignore it"].
	aStream cr.
	msgNode isExpression
		ifTrue:
			[aStream tab: level + 1; nextPut: $(.
			msgNode args fourth asExpression
				emitJSCodeOn: aStream level: level + 1 generator: self.
			aStream nextPut: $); cr]
		ifFalse:
			[msgNode args fourth
				emitJSCodeOn: aStream level: level generator: self].
	alternateBlock := msgNode args fifth.
	alternateBlockIsNil := true. "check for nil #else clause"
	alternateBlock nodesDo: [:n |
		(n ~= alternateBlock and: [n name ~= 'nil'])
			ifTrue: [alternateBlockIsNil := false ]].
	(alternateBlockIsNil) ifFalse:
		[aStream nextPutAll: '# else'; cr.
		msgNode isExpression
			ifTrue:
				[aStream tab: level + 1; nextPut: $(.
				alternateBlock asExpression
					emitJSCodeOn: aStream level: level + 1 generator: self.
				aStream nextPut: $); cr]
			ifFalse:
				[alternateBlock
					emitJSCodeOn: aStream level: level generator: self]].
	aStream nextPutAll: '# endif  // ', msgNode args first value; cr; tab: level
!

----- Method: JSCodeGenerator>>generateInlineDirective:on:indent: (in category 'JS translation') -----
generateInlineDirective: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: '/* inline: '.
	aStream nextPutAll: msgNode args first value asString.
	aStream nextPutAll: ' */'.
!

----- Method: JSCodeGenerator>>generateIntegerObjectOf:on:indent: (in category 'JS translation') -----
generateIntegerObjectOf: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode args first on: aStream.
!

----- Method: JSCodeGenerator>>generateIntegerValueOf:on:indent: (in category 'JS translation') -----
generateIntegerValueOf: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode args first on: aStream.
!

----- Method: JSCodeGenerator>>generateIsIntegerObject:on:indent: (in category 'JS translation') -----
generateIsIntegerObject: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: 'typeof '.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPutAll: ' === "number"'.!

----- Method: JSCodeGenerator>>generateIsNil:on:indent: (in category 'JS translation') -----
generateIsNil: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' === '.
	aStream nextPutAll: (self cLiteralFor: nil).!

----- Method: JSCodeGenerator>>generateJSCodeForCcode:on:indent: (in category 'JS translation') -----
generateJSCodeForCcode: cCode on: aStream indent: level
	cCode = '' ifTrue: [^self].
	aStream nextPutAll: (cCodeTranslationDict at: cCode ifAbsent: [
		"See initializeCTranslationDictionary"
		self error: 'C: ' , cCode]).
!

----- Method: JSCodeGenerator>>generateLessThan:on:indent: (in category 'JS translation') -----
generateLessThan: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' < '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateLessThanOrEqual:on:indent: (in category 'JS translation') -----
generateLessThanOrEqual: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' <= '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateMax:on:indent: (in category 'JS translation') -----
generateMax: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: 'Math.max('.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ', '.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPutAll: ')'.
!

----- Method: JSCodeGenerator>>generateMin:on:indent: (in category 'JS translation') -----
generateMin: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: 'Math.min('.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ', '.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPutAll: ')'.
!

----- Method: JSCodeGenerator>>generateMinus:on:indent: (in category 'JS translation') -----
generateMinus: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
	self checkNonPointer: msgNode receiver op: '-'.
	self checkNonPointer: msgNode args first op: '-'.

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' - '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateModulo:on:indent: (in category 'JS translation') -----
generateModulo: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' % '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateNegated:on:indent: (in category 'JS translation') -----
generateNegated: msgNode on: aStream indent: level
	"Generate the JS code for the negated message onto the given stream."

	"-0 is a float, 0 - 0 an integer"
	aStream nextPutAll: '(0 - '.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ')'.
!

----- Method: JSCodeGenerator>>generateNot:on:indent: (in category 'JS translation') -----
generateNot: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: '!!'.
	self emitJSExpression: msgNode receiver on: aStream.!

----- Method: JSCodeGenerator>>generateNotEqual:on:indent: (in category 'JS translation') -----
generateNotEqual: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' !!== '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateNotNil:on:indent: (in category 'JS translation') -----
generateNotNil: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' !!== '.
	aStream nextPutAll: (self cLiteralFor: nil).!

----- Method: JSCodeGenerator>>generateOr:on:indent: (in category 'JS translation') -----
generateOr: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' || '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generatePerform:on:indent: (in category 'JS translation') -----
generatePerform: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPut: $(.
	(msgNode args copyFrom: 2 to: msgNode args size) do:[:arg|
		self emitJSExpression: arg on: aStream.
	] separatedBy:[aStream nextPutAll:', '].
	aStream nextPut: $)!

----- Method: JSCodeGenerator>>generatePlus:on:indent: (in category 'JS translation') -----
generatePlus: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
	self checkNonPointer: msgNode receiver op: '+'.
	self checkNonPointer: msgNode args first op: '+'.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' + '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generatePreDecrement:on:indent: (in category 'JS translation') -----
generatePreDecrement: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	| varNode |
	varNode := msgNode receiver.
	varNode isVariable
		ifFalse: [ self error: 'preDecrement can only be applied to variables' ].
	self checkNonPointer: varNode op: '--'.
	aStream nextPutAll: '--'.
	aStream nextPutAll: (self returnPrefixFromVariable: varNode name).
!

----- Method: JSCodeGenerator>>generatePreIncrement:on:indent: (in category 'JS translation') -----
generatePreIncrement: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	| varNode |
	varNode := msgNode receiver.
	varNode isVariable
		ifFalse: [ self error: 'preIncrement can only be applied to variables' ].
	aStream nextPutAll: '++'.
	self checkNonPointer: varNode op: '++'.
	aStream nextPutAll: (self returnPrefixFromVariable: varNode name).
!

----- Method: JSCodeGenerator>>generateRaisedTo:on:indent: (in category 'JS translation') -----
generateRaisedTo: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll:'Math.pow('.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPutAll:')'.!

----- Method: JSCodeGenerator>>generateRepeat:on:indent: (in category 'JS translation') -----
generateRepeat: msgNode on: aStream indent: level
	"Generate while(true) { stmtList } "

	aStream nextPutAll: 'while(true) {'; cr.
	msgNode receiver emitJSCodeOn: aStream level: level + 1 generator: self.
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '}'
!

----- Method: JSCodeGenerator>>generateSequentialAnd:on:indent: (in category 'JS translation') -----
generateSequentialAnd: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' && ('.
	self emitJSTestBlock: msgNode args first on: aStream.
	aStream nextPut: $)!

----- Method: JSCodeGenerator>>generateSequentialOr:on:indent: (in category 'JS translation') -----
generateSequentialOr: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' || ('.
	self emitJSTestBlock: msgNode args last on: aStream.
	aStream nextPutAll: ')'!

----- Method: JSCodeGenerator>>generateSharedCodeDirective:on:indent: (in category 'JS translation') -----
generateSharedCodeDirective: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: '/* common code: '.
	aStream nextPutAll: msgNode args first value.
	aStream nextPutAll: ' */'.
!

----- Method: JSCodeGenerator>>generateShiftLeft:on:indent: (in category 'JS translation') -----
generateShiftLeft: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
	| arg rcvr |
	rcvr := msgNode receiver.
	arg := msgNode args first.
	arg isConstant ifTrue: [
		"bit shift amount is a constant"
		arg value < 31 ifTrue: [
			aStream nextPutAll: '('.
			self emitJSExpression: rcvr on: aStream.
				aStream nextPutAll: ' << ', arg value printString.
			aStream nextPutAll: ')'.
		] ifFalse: [
			self error: 'cannot shift by more than 31'
		].
	] ifFalse: [
		"bit shift amount is an expression"
		aStream nextPutAll: '('.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ' > 31 ? 0 : '.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' << '.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ')'.
	].!

----- Method: JSCodeGenerator>>generateShiftRight:on:indent: (in category 'JS translation') -----
generateShiftRight: msgNode on: aStream indent: level
	"Generate the JS code for unsigned right-shift onto the given stream."
	| rcvr arg |

	rcvr := msgNode receiver.
	arg := msgNode args first.
	arg isConstant ifTrue: [
		"bit shift amount is a constant"
		arg value < 31 ifTrue: [
			aStream nextPutAll: '('.
			self emitJSExpression: rcvr on: aStream.
				aStream nextPutAll: ' >>> ', arg value printString.
			aStream nextPutAll: ')'.
		] ifFalse: [
			self error: 'cannot shift by more than 31'
		].
	] ifFalse: [
		"bit shift amount is an expression"
		aStream nextPutAll: '('.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ' > 31 ? 0 : '.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' >>> '.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ')'.
	].!

----- Method: JSCodeGenerator>>generateSignedBitShift:on:indent: (in category 'JS translation') -----
generateSignedBitShift: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	| arg rcvr |
	arg := msgNode args first.
	rcvr := msgNode receiver.
	arg isConstant ifTrue: [
		"bit shift amount is a constant"
		aStream nextPutAll: '('.
		self emitJSExpression: rcvr on: aStream.
		arg value < 0 ifTrue: [
			aStream nextPutAll: ' >> ', arg value negated printString.
		] ifFalse: [
			aStream nextPutAll: ' << ', arg value printString.
		].
		aStream nextPutAll: ')'.
	] ifFalse: [
		"bit shift amount is an expression"
		aStream nextPutAll: '('.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ' < 0 ? '.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' >> (0 - '.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ') : '.
		self emitJSExpression: rcvr on: aStream.
		aStream nextPutAll: ' << '.
		self emitJSExpression: arg on: aStream.
		aStream nextPutAll: ')'.
	].!

----- Method: JSCodeGenerator>>generateSignedIntFromLong:on:indent: (in category 'JS translation') -----
generateSignedIntFromLong: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll: '((sqInt) '.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $)

!

----- Method: JSCodeGenerator>>generateSignedIntFromShort:on:indent: (in category 'JS translation') -----
generateSignedIntFromShort: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll: '((short)'.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $)

!

----- Method: JSCodeGenerator>>generateSignedIntToLong:on:indent: (in category 'JS translation') -----
generateSignedIntToLong: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll: '((usqInt) '.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $)

!

----- Method: JSCodeGenerator>>generateSignedIntToShort:on:indent: (in category 'JS translation') -----
generateSignedIntToShort: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
self halt.
	aStream nextPutAll: '((usqInt) (short)'.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPut: $)

!

----- Method: JSCodeGenerator>>generateSlotSizeOf:on:indent: (in category 'JS hacks') -----
generateSlotSizeOf: msgNode on: aStream indent: level
	aStream nextPut: $(.
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.bytes ? '.
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.bytes.length : '.
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.words ? '.
	msgNode args first emitJSCodeOn: aStream level: level generator: self.
	aStream nextPutAll: '.words.length : interpreterProxy.'.
	msgNode emitJSCodeAsFunctionCallOn: aStream level: level generator: self.
	aStream nextPut: $).
!

----- Method: JSCodeGenerator>>generateSmalltalkMetaError:on:indent: (in category 'JS translation') -----
generateSmalltalkMetaError: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aStream nextPutAll: 'throw Error("'; nextPutAll: msgNode selector; nextPutAll: '")'!

----- Method: JSCodeGenerator>>generateTimes:on:indent: (in category 'JS translation') -----
generateTimes: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: ' * '.
	self emitJSExpression: msgNode args first on: aStream.!

----- Method: JSCodeGenerator>>generateToByDo:on:indent: (in category 'JS translation') -----
generateToByDo: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."
	"N.B. MessageNode>>asTranslatorNodeIn: adds the limit var as a hidden fourth argument."
	| blockExpr iterationVar limitExpr mayHaveSideEffects limitVar step negative |
	blockExpr := msgNode args third.
	blockExpr args size = 1 ifFalse:
		[self error: 'wrong number of block arguments'].
	iterationVar := blockExpr args first.
	limitExpr := msgNode args first.
	aStream nextPutAll: 'for (', iterationVar, ' = '.
	self emitJSExpression: msgNode receiver on: aStream.
	mayHaveSideEffects := msgNode args size = 4. "See TMethod>>prepareMethodIn:"
	mayHaveSideEffects ifTrue:
		[limitVar := msgNode args last.
		 aStream nextPutAll: ', ', limitVar name, ' = '.
		 self emitJSExpression: limitExpr on: aStream.
		 limitExpr := limitVar].
	aStream nextPutAll: '; ', iterationVar.
	negative := ((step := msgNode args at: 2) isConstant and: [step value < 0])
				or: [step isSend and: [step selector == #negated
					and: [step receiver isConstant and: [step receiver value >= 0]]]].
	aStream nextPutAll: (negative ifTrue: [' >= '] ifFalse: [' <= ']).
	self emitJSExpression: limitExpr on: aStream.
	aStream nextPutAll: '; ', iterationVar, ' += '.
	self emitJSExpression: step on: aStream.
	aStream nextPutAll: ') {'; cr.
	blockExpr emitJSCodeOn: aStream level: level + 1 generator: self.
	aStream tab: level.
	aStream nextPut: $}!

----- Method: JSCodeGenerator>>generateToDo:on:indent: (in category 'JS translation') -----
generateToDo: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	| iterationVar |
	(msgNode args last args size = 1) ifFalse: [
		self error: 'wrong number of block arguments'.
	].
	iterationVar := msgNode args last args first.
	aStream nextPutAll: 'for (', iterationVar, ' = '.
	self emitJSExpression: msgNode receiver on: aStream.
	aStream nextPutAll: '; ', iterationVar, ' <= '.
	self emitJSExpression: msgNode args first on: aStream.
	aStream nextPutAll: '; ', iterationVar, '++) {'; cr.
	msgNode args last emitJSCodeOn: aStream level: level + 1 generator: self.
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '}'.!

----- Method: JSCodeGenerator>>generateTouch:on:indent: (in category 'JS translation') -----
generateTouch: msgNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream - which is to say absolutely nothing"
!

----- Method: JSCodeGenerator>>generateWhileFalse:on:indent: (in category 'JS translation') -----
generateWhileFalse: msgNode on: aStream indent: level
	"Generate JS code for a loop in one of the following formats, as appropriate:
		while(!!(cond)) { stmtList }
		do {stmtList} while(!!(cond))
		while(true) {stmtListA; if (cond) break; stmtListB}"

	msgNode receiver statements size <= 1
		ifTrue: [^self generateWhileFalseLoop: msgNode on: aStream indent: level].
	msgNode args first isNilStmtListNode
		ifTrue: [^self generateDoWhileFalse: msgNode on: aStream indent: level].
	^self generateWhileForeverBreakTrueLoop: msgNode on: aStream indent: level!

----- Method: JSCodeGenerator>>generateWhileFalseLoop:on:indent: (in category 'JS translation') -----
generateWhileFalseLoop: msgNode on: aStream indent: level
	"Generate while(!!(cond)) {stmtList}."

	aStream nextPutAll: 'while (!!('.
	self emitJSTestBlock: msgNode receiver on: aStream.
	aStream nextPutAll: ')) {'; cr.
	msgNode args first isNilStmtListNode ifFalse:
		[msgNode args first emitJSCodeOn: aStream level: level + 1 generator: self].
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '}'.!

----- Method: JSCodeGenerator>>generateWhileForeverBreakFalseLoop:on:indent: (in category 'JS translation') -----
generateWhileForeverBreakFalseLoop: msgNode on: aStream indent: level
	"Generate while(true) {stmtListA; if(!!(cond)) break; stmtListB}."

	| stmts testStmt |
	stmts := msgNode receiver statements asOrderedCollection.
	testStmt := stmts removeLast.
	msgNode receiver setStatements: stmts.
	level - 1 timesRepeat: [ aStream tab ].
	aStream nextPutAll: 'while (true) {'; cr.
	msgNode receiver emitJSCodeOn: aStream level: level + 1 generator: self.
	(level + 1) timesRepeat: [ aStream tab ].
	aStream nextPutAll: 'if (!!('.
	testStmt asExpression emitJSCodeOn: aStream level: 0 generator: self.
	aStream nextPutAll: ')) break;'; cr.
	msgNode args first emitJSCodeOn: aStream level: level + 1 generator: self.
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '}'.!

----- Method: JSCodeGenerator>>generateWhileForeverBreakTrueLoop:on:indent: (in category 'JS translation') -----
generateWhileForeverBreakTrueLoop: msgNode on: aStream indent: level
	"Generate while(true) {stmtListA; if(cond) break; stmtListB}."

	| stmts testStmt |
	stmts := msgNode receiver statements asOrderedCollection.
	testStmt := stmts removeLast.
	msgNode receiver setStatements: stmts.
	level - 1 timesRepeat: [ aStream tab ].
	aStream nextPutAll: 'while (true) {'; cr.
	msgNode receiver emitJSCodeOn: aStream level: level + 1 generator: self.
	(level + 1) timesRepeat: [ aStream tab ].
	aStream nextPutAll: 'if ('.
	testStmt asExpression emitJSCodeOn: aStream level: 0 generator: self.
	aStream nextPutAll: ') break;'; cr.
	msgNode args first emitJSCodeOn: aStream level: level + 1 generator: self.
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '}'.!

----- Method: JSCodeGenerator>>generateWhileTrue:on:indent: (in category 'JS translation') -----
generateWhileTrue: msgNode on: aStream indent: level
	"Generate C code for a loop in one of the following formats, as appropriate:
		while(cond) { stmtList }
		do {stmtList} while(cond)
		while(true) {stmtListA; if (!!(cond)) break; stmtListB}"

	msgNode receiver statements size <= 1
		ifTrue: [^self generateWhileTrueLoop: msgNode on: aStream indent: level].
	msgNode args first isNilStmtListNode
		ifTrue: [^self generateDoWhileTrue: msgNode on: aStream indent: level].
	^self generateWhileForeverBreakFalseLoop: msgNode on: aStream indent: level!

----- Method: JSCodeGenerator>>generateWhileTrueLoop:on:indent: (in category 'JS translation') -----
generateWhileTrueLoop: msgNode on: aStream indent: level
	"Generate while(cond) {stmtList}."

	aStream nextPutAll: 'while ('.
	self emitJSTestBlock: msgNode receiver on: aStream.
	aStream nextPutAll: ') {'; cr.
	msgNode args first isNilStmtListNode ifFalse:
		[msgNode args first emitJSCodeOn: aStream level: level + 1 generator: self].
	level timesRepeat: [ aStream tab ].
	aStream nextPutAll: '}'.!

----- Method: JSCodeGenerator>>globalsAsSet (in category 'public') -----
globalsAsSet
	"Used by the inliner to avoid name clashes with global variables."

	((variablesSetCache == nil) or:
	 [variablesSetCache size ~= variables size]) ifTrue: [
		variablesSetCache := variables asSet.
	].
	^ variablesSetCache!

----- Method: JSCodeGenerator>>initialize (in category 'public') -----
initialize
	translationDict := Dictionary new.
	inlineList := Array new.
	constants := Dictionary new: 100.
	variables := OrderedCollection new: 100.
	variableDeclarations := Dictionary new: 100.
	methods := Dictionary new: 500.
	macros := Dictionary new.
	self initializeCTranslationDictionary.
	receiverDict := Dictionary new.
	headerFiles := OrderedCollection new.
	globalVariableUsage := Dictionary new.
	useSymbolicConstants := true.
	generateDeadCode := false.
	scopeStack := OrderedCollection new.
	logger := (ProvideAnswerNotification new tag: #logger; signal) ifNil: [Transcript].
	pools := IdentitySet new.
	abstractDeclarations := IdentitySet new.
	uncheckedAbstractMethods := OrderedCollection new.
!

----- Method: JSCodeGenerator>>initializeCTranslationDictionary (in category 'JS translation') -----
initializeCTranslationDictionary 
	"Initialize the dictionary mapping message names to actions for C code generation."

	| pairs |
	translationDict := Dictionary new: 200.
	pairs := #(
	#&				#generateAnd:on:indent:
	#|				#generateOr:on:indent:
	#and:			#generateSequentialAnd:on:indent:
	#or:			#generateSequentialOr:on:indent:
	#not			#generateNot:on:indent:

	#+				#generatePlus:on:indent:
	#-				#generateMinus:on:indent:
	#negated		#generateNegated:on:indent:
	#*				#generateTimes:on:indent:
	#/				#generateDivide:on:indent:
	#//				#generateDivide:on:indent:
	#\\				#generateModulo:on:indent:
	#<<			#generateShiftLeft:on:indent:
	#>>			#generateShiftRight:on:indent:
	#min:			#generateMin:on:indent:
	#max:			#generateMax:on:indent:
	#between:and:	#generateBetweenAnd:on:indent:

	#bitAnd:		#generateBitAnd:on:indent:
	#bitOr:			#generateBitOr:on:indent:
	#bitXor:		#generateBitXor:on:indent:
	#bitShift:		#generateBitShift:on:indent:
	#signedBitShift:	#generateSignedBitShift:on:indent:
	#bitInvert32		#generateBitInvert32:on:indent:
	#bitClear:			#generateBitClear:on:indent:

	#<				#generateLessThan:on:indent:
	#<=			#generateLessThanOrEqual:on:indent:
	#=				#generateEqual:on:indent:
	#>				#generateGreaterThan:on:indent:
	#>=			#generateGreaterThanOrEqual:on:indent:
	#~=			#generateNotEqual:on:indent:
	#==			#generateEqual:on:indent:
	#~~			#generateNotEqual:on:indent:
	#isNil			#generateIsNil:on:indent:
	#notNil			#generateNotNil:on:indent:

	#whileTrue: 	#generateWhileTrue:on:indent:
	#whileFalse:	#generateWhileFalse:on:indent:
	#whileTrue 		#generateDoWhileTrue:on:indent:
	#whileFalse		#generateDoWhileFalse:on:indent:
	#to:do:			#generateToDo:on:indent:
	#to:by:do:		#generateToByDo:on:indent:
	#repeat 		#generateRepeat:on:indent:

	#ifTrue:			#generateIfTrue:on:indent:
	#ifFalse:		#generateIfFalse:on:indent:
	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:

	#at:			#generateAt:on:indent:
	#at:put:			#generateAtPut:on:indent:
	#basicAt:		#generateAt:on:indent:
	#basicAt:put:	#generateAtPut:on:indent:

	#integerValueOf:			#generateIntegerValueOf:on:indent:
	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
	#cCode:					#generateInlineCCode:on:indent:
	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
	#preprocessorExpression:	#generateInlineCppDirective:on:indent:
	#isDefined:inSmalltalk:comment:ifTrue:	#generateInlineCppIfDef:on:indent:
	#isDefined:inSmalltalk:comment:ifTrue:ifFalse:	#generateInlineCppIfDefElse:on:indent:
	#isDefinedTrueExpression:inSmalltalk:comment:ifTrue:ifFalse:	#generateInlineCppIfElse:on:indent:
	#cCoerce:to:				#generateCCoercion:on:indent:
	#cCoerceSimple:to:			#generateCCoercion:on:indent:
	#addressOf:				#generateAddressOf:on:indent:
	#signedIntFromLong			#generateSignedIntFromLong:on:indent:
	#signedIntToLong			#generateSignedIntToLong:on:indent:
	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
	#signedIntToShort			#generateSignedIntToShort:on:indent:
	#preIncrement				#generatePreIncrement:on:indent:
	#preDecrement				#generatePreDecrement:on:indent:
	#inline:						#generateInlineDirective:on:indent:
	#asFloat					#generateAsFloat:on:indent:
	#asInteger					#generateAsInteger:on:indent:
	#asUnsignedInteger			#generateAsUnsignedInteger:on:indent:
	#asSymbol					#generateAsSymbol:on:indent:
	#anyMask:					#generateBitAnd:on:indent:
	#raisedTo:					#generateRaisedTo:on:indent:
	#touch:						#generateTouch:on:indent:
	#bytesPerWord		#generateBytesPerWord:on:indent:
	#baseHeaderSize		#generateBaseHeaderSize:on:indent:

	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:

	#perform:							#generatePerform:on:indent:
	#perform:with:						#generatePerform:on:indent:
	#perform:with:with:					#generatePerform:on:indent:
	#perform:with:with:with:				#generatePerform:on:indent:
	#perform:with:with:with:with:		#generatePerform:on:indent:
	#perform:with:with:with:with:with:	#generatePerform:on:indent:

	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
	#shouldBeImplemented				#generateSmalltalkMetaError:on:indent:

	"optimized interpreterProxy calls"
	#firstIndexableField:				#generateFirstIndexableField:on:indent:
	#slotSizeOf:						#generateSlotSizeOf:on:indent:
	#byteSizeOfBytes:					#generateByteSizeOfBytes:on:indent:
	#fetchClassOf:						#generateFetchClassOf:on:indent:
	#is:KindOf: 							#generateIsKindOf:on:indent:
	#cDigitCopyFrom:to:len:				#generateCDigitCopy:on:indent:
	).

	1 to: pairs size by: 2 do: [:i |
		translationDict at: (pairs at: i) put: (pairs at: i + 1)].

	pairs := #(
	#ifTrue:				#generateIfTrueAsArgument:on:indent:	
	#ifFalse:			#generateIfFalseAsArgument:on:indent:
	#ifTrue:ifFalse:		#generateIfTrueIfFalseAsArgument:on:indent:
	#ifFalse:ifTrue:		#generateIfFalseIfTrueAsArgument:on:indent:
	#cCode:			#generateInlineCCodeAsArgument:on:indent:
	#cCode:inSmalltalk:	#generateInlineCCodeAsArgument:on:indent:
	).

	asArgumentTranslationDict := Dictionary new: 8.
	1 to: pairs size by: 2 do: [:i |
		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].

	cCodeTranslationDict := Dictionary new: 8.
	pairs := #(
		'fprintf(stderr, "\n%s: %s", moduleName, s)'					'console.log(moduleName + ": " + s)'
		'interpreterProxy->majorVersion() == VM_PROXY_MAJOR'	'interpreterProxy.majorVersion() == VM_PROXY_MAJOR'
		'interpreterProxy->minorVersion() >= VM_PROXY_MINOR'	'interpreterProxy.minorVersion() >= VM_PROXY_MINOR'
	).
	1 to: pairs size by: 2 do: [:i |
		cCodeTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
!

----- Method: JSCodeGenerator>>inlineCaseStatementBranchesInMethodNamed:localizingVars: (in category 'inlining') -----
inlineCaseStatementBranchesInMethodNamed: selector localizingVars: varsList 
	"Inline case statement branches in the method with the given name."
	(self methodNamed: selector)
		ifNotNilDo: [:m | m inlineCaseStatementBranchesIn: self localizingVars: varsList]!

----- Method: JSCodeGenerator>>inlineDispatchesInMethodNamed:localizingVars: (in category 'inlining') -----
inlineDispatchesInMethodNamed: selector localizingVars: varsList
	"Inline dispatches (case statements) in the method with the given name."

	| m varString |
	m := self methodNamed: selector.
	m = nil ifFalse: [
		m inlineCaseStatementBranchesIn: self localizingVars: varsList.
		m parseTree nodesDo: [ :n |
			n isCaseStmt ifTrue: [
				n customizeShortCasesForDispatchVar: 'currentBytecode' in: self method: m.
			].
		].
	].
	variables := variables asOrderedCollection.
	varsList do: [ :v |
		varString := v asString.
		variables remove: varString ifAbsent: [].
		(variableDeclarations includesKey: varString) ifTrue: [
			m declarations at: v asString put: (variableDeclarations at: varString).
			variableDeclarations removeKey: varString.
		].
	].
!

----- Method: JSCodeGenerator>>isAssertSelector: (in category 'inlining') -----
isAssertSelector: selector
	^#(assert: asserta: assert:l: asserta:l:) includes: selector!

----- Method: JSCodeGenerator>>isCLiteral: (in category 'JS code generator') -----
isCLiteral: anObject
	(anObject isKindOf: Integer) ifTrue: [^true].
	(anObject isKindOf: String) ifTrue: [^true].
	(anObject isKindOf: Float) ifTrue: [^true].
	anObject == nil ifTrue: [^true].
	anObject == true ifTrue: [^true].
	anObject == false ifTrue: [^true].
	^false!

----- Method: JSCodeGenerator>>isGeneratingPluginCode (in category 'utilities') -----
isGeneratingPluginCode
	^false!

----- Method: JSCodeGenerator>>isGlobalStructureBuild (in category 'public') -----
isGlobalStructureBuild
	^false!

----- Method: JSCodeGenerator>>isNonArgumentImplicitReceiverVariableName: (in category 'JS code generator') -----
isNonArgumentImplicitReceiverVariableName: aString
	^(self typeOfVariable: aString) == #implicit
	    or: [vmClass
			ifNil: [#('interpreterProxy' 'self') includes: aString]
	 		ifNotNil: [vmClass isNonArgumentImplicitReceiverVariableName: aString]]!

----- Method: JSCodeGenerator>>isPointer: (in category 'private') -----
isPointer: node
	node isVariable ifFalse: [^false].
	(self typeOfVariable: node name) ifNotNil: [:type | ^type includes: $*].
	^false!

----- Method: JSCodeGenerator>>isPointerToStructVariableName: (in category 'JS code generator') -----
isPointerToStructVariableName: varName "<String>"
	^self isTypePointerToStruct: (self typeOfVariable: varName)!

----- Method: JSCodeGenerator>>isTypePointerToStruct: (in category 'JS code generator') -----
isTypePointerToStruct: type "<String>"
	^vmClass notNil
	  and: [vmClass isTypePointerToStruct: type]!

----- Method: JSCodeGenerator>>localizeGlobalVariables (in category 'utilities') -----
localizeGlobalVariables
	| candidates procedure |

	"find all globals used in only one method"
	candidates := globalVariableUsage select: [:e | e size = 1].
	(candidates keys select: [:k| vmClass mustBeGlobal: k]) do:
		[:k| candidates removeKey: k].
	variables removeAllFoundIn: candidates keys.

	"move any suitable global to be local to the single method using it"
	candidates keysAndValuesDo: [:key :targets | 
		targets do: [:name |
			procedure := methods at: name.
			procedure locals add: key.
			variableDeclarations at: key ifPresent: [:v | 
				procedure declarations at: key put: v.
				variableDeclarations removeKey: key]]].!

----- Method: JSCodeGenerator>>logger (in category 'utilities') -----
logger
	^logger!

----- Method: JSCodeGenerator>>logger: (in category 'utilities') -----
logger: aTranscriptStream
	logger := aTranscriptStream!

----- Method: JSCodeGenerator>>mapVar:asInstanceOf:to: (in category 'composition') -----
mapVar: instanceVarName asInstanceOf: aClass to: newName
	"A class that has been added to this code generator has an instance variable
	instanceVarName that should point to an instance of aClass. Treat sends to
	that object as if they were sends to newName. When newName is 'self', all
	such methods are translated to C as functions in the current C module."

	receiverDict at: instanceVarName asString
		ifPresent: [ :previousMapping |
			previousMapping = newName
				ifFalse: [ self error: aClass name,'>>', instanceVarName, ' previously mapped to ',
					previousMapping, ' by another class, cannot be remapped to ', newName ]]
		ifAbsent: [ receiverDict at: instanceVarName asString put: newName.
			variables remove: instanceVarName ifAbsent: [] ]
!

----- Method: JSCodeGenerator>>mayInline: (in category 'inlining') -----
mayInline: sel
	"Answer true if the method with the given selector may be inlined."

	^ inlineList includes: sel!

----- Method: JSCodeGenerator>>memoryAccessSelectors (in category 'utilities') -----
memoryAccessSelectors
	"Answer the selectors used for low level memory access. These are traditionally
	implemented as C preprocessor macros (or static inlined functions) in the external
	support code, but may also be implemented as Smalltalk methods for translation to C."

	^ { #byteAt: . #byteAt:put: .
		#shortAt: . #shortAt:put: .
		#intAt: . #intAt:put: .
		#longAt: . #longAt:put: .
		#byteAtPointer: . #byteAtPointer:put: .
		#shortAtPointer: . #shortAtPointer:put: .
		#intAtPointer: . #intAtPointer:put: .
		#longAtPointer: . #longAtPointer:put: }!

----- Method: JSCodeGenerator>>methodNamed: (in category 'utilities') -----
methodNamed: selector
	"Answer the method in the code base with the given selector."

	^ methods at: selector ifAbsent: [ nil ]!

----- Method: JSCodeGenerator>>methodStatsString (in category 'inlining') -----
methodStatsString
	"Return a string describing the size, # of locals, and # of senders of
each method. Note methods that have inline C code or C declarations."

	| methodsWithCCode sizesOf callsOf hasCCode nodeCount senderCount s
calls registers selr m |
	methodsWithCCode := Set new: methods size.
	sizesOf := Dictionary new: methods size * 2.  "selector -> nodeCount"
	callsOf := Dictionary new: methods size * 2.  "selector -> senderCount"

	"For each method, scan its parse tree once to:
		1. determine if the method contains C code or declarations
		2. determine how many nodes it has
		3. increment the sender counts of the methods it calls
		4. determine if it includes any C declarations or code"

	methods do: [ :m0 |  m := m0.
		(translationDict includesKey: m selector) ifTrue: [
			hasCCode := true.
		] ifFalse: [
			hasCCode := m declarations size > 0.
			nodeCount := 0.
			m parseTree nodesDo: [ :node |
				node isSend ifTrue: [
					selr := node selector.
					selr = #cCode: ifTrue: [ hasCCode := true ].
					senderCount := callsOf at: selr ifAbsent: [ 0 ].
					callsOf at: selr put: senderCount + 1.
				].
				nodeCount := nodeCount + 1.
			].
		].
		hasCCode ifTrue: [ methodsWithCCode add: m selector ].
		sizesOf at: m selector put: nodeCount.
	].

	s := WriteStream on: (String new: 5000).
	methods keys asSortedCollection do: [ :sel |
		m := methods at: sel.
		registers := m locals size + m args size.
		calls := callsOf at: sel ifAbsent: [0].
		registers > 11 ifTrue: [
			s nextPutAll: sel; tab.
			s nextPutAll: (sizesOf at: sel) printString; tab.
			s nextPutAll: calls printString; tab.
			s nextPutAll: registers printString; tab.
			(methodsWithCCode includes: sel) ifTrue: [ s nextPutAll: 'CCode' ].
		s cr.
		].
	].
	^ s contents!

----- Method: JSCodeGenerator>>methodsReferringToGlobal: (in category 'utilities') -----
methodsReferringToGlobal: v
	"Return a collection of methods that refer to the given global variable."

	| out |
	out := OrderedCollection new.
	methods associationsDo: [ :assoc |
		(assoc value freeVariableReferences includes: v) ifTrue: [
			out add: assoc key.
		].
	].
	^ out!

----- Method: JSCodeGenerator>>methodsThatCanInvoke: (in category 'utilities') -----
methodsThatCanInvoke: aSelectorList
	"Return a set of methods that can invoke one of the given selectors, either directly or via a sequence of intermediate methods."

	| out todo sel mSelector |
	out := Set new.
	todo := aSelectorList copy asOrderedCollection.
	[todo isEmpty] whileFalse: [
		sel := todo removeFirst.
		out add: sel.
		methods do: [ :m |
			(m allCalls includes: sel) ifTrue: [
				mSelector := m selector.
				((out includes: mSelector) or:
				 [todo includes: mSelector]) ifFalse: [
					todo add: mSelector.
				].
			].
		].
	].
	^ out
	!

----- Method: JSCodeGenerator>>needToGenerateHeader:file:contents: (in category 'JS code generator') -----
needToGenerateHeader: headerName file: interpHdrPath contents: newContentsArg
	"Check if we need to regenerate a header file.  We always need to if the contents have changed.
	 But if not we can avoid needless recompilations by not regenerating.  So only regenerate if the
	 package is clean (version doesn't include a '*').  If we can't find a package version ask the user."
	| newContents oldContents |
	(FileDirectory default fileExists: interpHdrPath) ifFalse:
		[^true].
	newContents := newContentsArg.
	oldContents := (FileDirectory default oldFileNamed: interpHdrPath) contentsOfEntireFile.
	(newContents beginsWith: '/*') = (oldContents beginsWith: '/*') ifFalse:
		[(newContents beginsWith: '/*') ifTrue:
			[newContents := newContents readStream upToAll: '*/'; skipSeparators; upToEnd].
		 (oldContents beginsWith: '/*') ifTrue:
			[oldContents := oldContents readStream upToAll: '*/'; skipSeparators; upToEnd]].
	oldContents := oldContents copyReplaceAll: {Character cr. Character lf} with: {Character cr}.
	oldContents replaceAll: Character lf with: Character cr.
	^oldContents ~= newContents
	 or: [[((self monticelloDescriptionFor: vmClass) includes: $*) not]
			on: Error
			do: [:ex|
				self confirm: headerName, ' contents are unchanged.\Writing the file may cause recompilation of support files.\Do you want to write the header file?\The interpreter will still be written either way.' withCRs]]!

----- Method: JSCodeGenerator>>nilOrBooleanConstantReceiverOf: (in category 'utilities') -----
nilOrBooleanConstantReceiverOf: sendNode
	"Answer nil or the boolean constant that is the receiver of the given message send. Used to suppress conditional code when the condition is a translation-time constant."

	| rcvr val |
	generateDeadCode ifTrue:[^nil].
	rcvr := sendNode receiver.
	rcvr isConstant ifTrue: [
		val := rcvr value.
		((val == true) or: [val == false]) ifTrue: [^ val]].
	^ nil
!

----- Method: JSCodeGenerator>>permitMethodPruning (in category 'accessing') -----
permitMethodPruning
	"If false, pruning unreferenced methods will be disabled"
	^ permitMethodPruning ~= false!

----- Method: JSCodeGenerator>>permitMethodPruning: (in category 'accessing') -----
permitMethodPruning: aBoolean
	"If false, pruning unreferenced methods will be disabled"
	permitMethodPruning := aBoolean!

----- Method: JSCodeGenerator>>prepareMethods (in category 'utilities') -----
prepareMethods
	"Prepare methods for browsing."

	| globals |
	globals := Set new: 200.
	globals addAll: variables.
	methods do: [ :m |
		(m locals, m args) do: [ :var |
			(globals includes: var) ifTrue: [
				self error: 'Local variable name may mask global when inlining: ', var.
			].
			(methods includesKey: var) ifTrue: [
				self error: 'Local variable name may mask method when inlining: ', var.
			].	
		].
		m mapReceiversIn: receiverDict.
		m bindClassVariablesIn: constants.
		m prepareMethodIn: self.
	].!

----- Method: JSCodeGenerator>>prepareMethodsInlined:doAssertions: (in category 'JS code generator') -----
prepareMethodsInlined: inlineFlag doAssertions: assertionFlag
	"Prepare to emit JS code for all methods in the code base. All inlined method calls should be expanded. Answer a list of methods to be emitted as C code."

	| verbose methodList |
	"method preparation"
	verbose := false.
	self prepareMethods.
	verbose ifTrue: [
		self printUnboundCallWarnings.
		self printUnboundVariableReferenceWarnings.
		Transcript cr.
	].
	self checkAbstractMethods.
	assertionFlag ifFalse: [ self removeAssertions ].
	self doInlining: inlineFlag.

	"code generation"

	methodList := methods asSortedCollection: [ :m1 :m2 | m1 selector < m2 selector ].
	"clean out no longer valid variable names and then handle any global
		variable usage in each method"
	methodList do: [:m | self checkForGlobalUsage: m removeUnusedTemps in: m].
	self localizeGlobalVariables.
	^ preparedMethodList := methodList
!

----- Method: JSCodeGenerator>>printArray:on: (in category 'private') -----
printArray: array on: aStream
	| first |
	first := true.
	1 to: array size do:
		[:i |
		first 
			ifTrue: [first := false]
			ifFalse: [aStream nextPutAll: ', '].
		i \\ 16 = 1 ifTrue: [aStream cr].
		self printInt: (array at: i) on: aStream]!

----- Method: JSCodeGenerator>>printInt:on: (in category 'private') -----
printInt: int on: aStream
	aStream print: int.
	(int between: -2147483648 and: 2147483647)
		ifFalse: [(int between: 2147483648 and: 4294967295)
			ifTrue: [aStream nextPut: $U]
			ifFalse: [aStream nextPut: $L]]!

----- Method: JSCodeGenerator>>printUnboundCallWarnings (in category 'error notification') -----
printUnboundCallWarnings
	"Print a warning message for every unbound method call in the code base."

	| knownSelectors undefinedCalls |
	undefinedCalls := Dictionary new.
	knownSelectors := translationDict keys asSet.
	knownSelectors add: #error:.
	methods do: [ :m | knownSelectors add: m selector ].
	methods do: [ :m |
		m allCalls do: [ :sel |
			(knownSelectors includes: sel) ifFalse: [
				(undefinedCalls includesKey: sel)
					ifTrue: [ (undefinedCalls at: sel) add: m selector ]
					ifFalse: [ undefinedCalls at: sel put: (OrderedCollection with: m selector) ].
			].
		].
	].

	Transcript cr.
	undefinedCalls keys asSortedCollection do: [ :undefined |
		Transcript show: undefined, ' -- undefined method sent by:'; cr.
		(undefinedCalls at: undefined) do: [ :caller |
			Transcript tab; show: caller; cr.
		].
	].!

----- Method: JSCodeGenerator>>printUnboundVariableReferenceWarnings (in category 'error notification') -----
printUnboundVariableReferenceWarnings
	"Print a warning message for every unbound variable reference in the code base."

	| undefinedRefs globalVars knownVars |
	undefinedRefs := Dictionary new.
	globalVars := Set new: 100.
	globalVars addAll: variables.
	methods do: [ :m |
		knownVars := globalVars copy.
		m args do: [ :var | knownVars add: var ].
		m locals do: [ :var | knownVars add: var ].
		m freeVariableReferences do: [ :varName |
			(knownVars includes: varName) ifFalse: [
				(undefinedRefs includesKey: varName)
					ifTrue: [ (undefinedRefs at: varName) add: m selector ]
					ifFalse: [ undefinedRefs at: varName put: (OrderedCollection with: m selector) ].
			].
		].
	].

	Transcript cr.
	undefinedRefs keys asSortedCollection do: [ :var |
		Transcript show: var, ' -- undefined variable used in:'; cr.
		(undefinedRefs at: var) do: [ :sel |
			Transcript tab; show: sel; cr.
		].
	].!

----- Method: JSCodeGenerator>>pruneMethods: (in category 'inlining') -----
pruneMethods: selectorList
	"Explicitly prune some methods"
	selectorList do:[:sel| methods removeKey: sel ifAbsent:[]].!

----- Method: JSCodeGenerator>>pruneUnreachableMethods (in category 'inlining') -----
pruneUnreachableMethods
	"Remove any methods that are not reachable. Retain methods needed by the translated classes - see implementors of requiredMethodNames"
 	
	| newMethods |
	"add all the exported methods and all the called methods to the dNRML"
	methods do: [ :m |
		m export ifTrue:[doNotRemoveMethodList add: m selector].
		doNotRemoveMethodList addAll: m allCalls].

	"build a new dictionary of methods from the collection of all the ones to keep"			
	newMethods := Dictionary new: doNotRemoveMethodList size.
	doNotRemoveMethodList do:[:sel|
		methods at: sel ifPresent:[:meth| newMethods at: sel put: meth]].
	methods := newMethods!

----- Method: JSCodeGenerator>>pushScope:while: (in category 'JS code generator') -----
pushScope: variableToType "<Dictionary>" while: aBlock
	scopeStack addLast: variableToType.
	^aBlock ensure: [scopeStack removeLast]!

----- Method: JSCodeGenerator>>removeAssertions (in category 'inlining') -----
removeAssertions
	"Remove all assertions in method bodies.  This is for the benefit of inlining, which
	fails to recognise and disregard empty method bodies when checking the inlinability
	of sends."

	| newMethods |
	newMethods := Dictionary new.
	'Removing assertions...'
		displayProgressAt: Sensor cursorPoint
		from: 0 to: methods size
		during: [ :bar |
			methods doWithIndex: [ :m :i |
				bar value: i.
				m isAssertion ifFalse: [
					newMethods at: m selector put: m.
					m removeAssertions]]].
	methods := newMethods.!

----- Method: JSCodeGenerator>>removeMethodForSelector: (in category 'utilities') -----
removeMethodForSelector: aSelector
	"Remove the given method from the code base"
	methods removeKey:  aSelector ifAbsent: []!

----- Method: JSCodeGenerator>>removeMethodsReferingToGlobals:except: (in category 'inlining') -----
removeMethodsReferingToGlobals: varList except: methodNames
	"Remove any methods (presumably inlined) that still contain references to the given obsolete global variables."

	| varListAsStrings mVars |
	varListAsStrings := varList collect: [ :sym | sym asString ].
		(methods keys copyWithoutAll: methodNames) do: [ :sel |
			mVars := (self methodNamed: sel) freeVariableReferences asSet.
			(mVars includesAnyOf: varListAsStrings)
				ifTrue: [methods removeKey: sel ifAbsent: []]]
!

----- Method: JSCodeGenerator>>removeVariable: (in category 'utilities') -----
removeVariable: aName
	"Remove the given (instance) variable from the code base."
	self checkDeleteVariable: aName.
	variables
		remove: aName
		ifAbsent:
			[(vmClass notNil
			  and: [vmClass isNonArgumentImplicitReceiverVariableName: aName]) ifFalse:
				[logger
					ensureCr;
					show: 'warning, variable '
						, aName
						, ' doesn''t exist or has already been removed';
						cr]].
	variableDeclarations removeKey: aName ifAbsent: []!

----- Method: JSCodeGenerator>>renameSelector:as: (in category 'composition') -----
renameSelector: selectorName as: newSelectorName
	"Rename selectors such that generated code will use the newSelectorName. This
	is intended to allow methods that may have default implementations in the support
	code to be renamed for code generation, such that the renamed versions will
	be referenced rather than the default platform implementations. For example,
	if #pointerForOop: is implemented in Smalltalk, it may be renamed such that
	the generated pointerForOop() function will be renamed to avoid conflict with
	the standard definitions provided in sqMemoryAccess.h."

	(methods includesKey: selectorName)
		ifFalse: [ self error: 'no such selector: ', selectorName ].
	methods do: [ :m |
		m renameSelector: selectorName as: newSelectorName ].
	methods at: newSelectorName put: (methods at: selectorName).
	methods removeKey: selectorName
!

----- Method: JSCodeGenerator>>reportRecursiveMethods (in category 'utilities') -----
reportRecursiveMethods
	"Report in transcript all methods that can call themselves directly or indirectly or via a chain of N intermediate methods."

	| visited calls newCalls sel called |
	methods do: [: m |
		visited := translationDict keys asSet.
		calls := m allCalls asOrderedCollection.
		5 timesRepeat: [
			newCalls := Set new: 50.
			[calls isEmpty] whileFalse: [
				sel := calls removeFirst.
				sel = m selector ifTrue: [
					Transcript show: m selector, ' is recursive'; cr.
				] ifFalse: [
					(visited includes: sel) ifFalse: [
						called := self methodNamed: sel.
						called = nil ifFalse: [ newCalls addAll: called allCalls ].
					].
					visited add: sel.
				].
			].
			calls := newCalls asOrderedCollection.
		].
	].!

----- Method: JSCodeGenerator>>retainMethods: (in category 'inlining') -----
retainMethods: aListOfMethodsToKeep
"add aListOfMethodsToKeep to doNotRemoveMethodList so that they will not be pruned"
	doNotRemoveMethodList ifNil:[doNotRemoveMethodList := Set new:100].
	doNotRemoveMethodList addAll: aListOfMethodsToKeep.
	^aListOfMethodsToKeep!

----- Method: JSCodeGenerator>>returnPrefixFromVariable: (in category 'utilities') -----
returnPrefixFromVariable: aName
	aName = 'class'
		ifTrue: [^'sq_class'].
	^aName!

----- Method: JSCodeGenerator>>selectorReturnsPointerToStruct: (in category 'JS code generator') -----
selectorReturnsPointerToStruct: selector "<Symbol>"
	| tMethod |
	^vmClass notNil
	  and: [(tMethod := methods at: selector ifAbsent: []) notNil
	  and: [vmClass isTypePointerToStruct: tMethod returnType]]!

----- Method: JSCodeGenerator>>shortMonticelloDescriptionForClass: (in category 'JS code generator') -----
shortMonticelloDescriptionForClass: aClass
	"Answer a suitable Monticello package stamp to include in a moduleName."
	| mdesc |
	mdesc := [self monticelloDescriptionFor: aClass]
				on: Error
				do: [:ex| ^' ', Date today asString].
	^mdesc copyFrom: 1 to: (mdesc indexOfSubCollection: ' uuid:') - 1!

----- Method: JSCodeGenerator>>sortMethods: (in category 'utilities') -----
sortMethods: aJSMethodCollection
	"We need to define this since different Squeak versions answer different results
	 for asSortedCollection and if sort order changes, generated code changes too."
	^aJSMethodCollection asSortedCollection:
		[:a :b| a selector caseSensitiveLessOrEqual: b selector]!

----- Method: JSCodeGenerator>>storeCodeOnFile:doInlining: (in category 'public') -----
storeCodeOnFile: fileName doInlining: inlineFlag
	"Store JS code for this code base on the given file."

	self storeCodeOnFile: fileName doInlining: inlineFlag doAssertions: true!

----- Method: JSCodeGenerator>>storeCodeOnFile:doInlining:doAssertions: (in category 'public') -----
storeCodeOnFile: fileName doInlining: inlineFlag doAssertions: assertionFlag
	"Store JS code for this code base on the given file."

	| stream |
	stream := CrLfFileStream forceNewFileNamed: fileName.
	stream ifNil: [Error signal: 'Could not open JS code file: ', fileName].
	self emitJSCodeOn: stream doInlining: inlineFlag doAssertions: assertionFlag.
	stream close!

----- Method: JSCodeGenerator>>storeHeaderFor:onFile: (in category 'public') -----
storeHeaderFor: interpreterClassName onFile: fileName
	"Store C header code for this interpreter on the given file."

	| aStream |
	aStream := CrLfFileStream forceNewFileNamed: fileName.
	aStream ifNil: [Error signal: 'Could not open C header file: ', fileName].
	aStream
		nextPutAll: '/* ';
		nextPutAll: VMMaker headerNotice;
		nextPutAll: ' */'; cr; cr;
		nextPutAll: '#ifndef HAVE_INTERP_H'; cr;
		nextPutAll: '# define HAVE_INTERP_H'; cr;
		nextPutAll: '#endif'; cr; cr.
	self emitVmmVersionOn: aStream.
	(Smalltalk classNamed: interpreterClassName)
		emitInterpreterProxyVersionOn: aStream.
	self emitDefineBytesPerWordOn: aStream.
	self emitDefineMemoryAccessInImageOn: aStream.
	aStream cr.
	aStream close
!

----- Method: JSCodeGenerator>>storeHeaderOnFile:contents: (in category 'public') -----
storeHeaderOnFile: fileName contents: contents
	"Store C header code on the given file. Evaluate
	 aBlock with the stream to generate its contents."

	| aStream |
	aStream := VMMaker forceNewFileNamed: fileName.
	aStream ifNil: [Error signal: 'Could not open C header file: ', fileName].
	[(contents beginsWith: '/* Automatic') ifFalse:
		[aStream nextPutAll: (self fileHeaderVersionStampForSourceClass: nil); cr].
	 aStream nextPutAll: contents]
		ensure: [aStream close]!

----- Method: JSCodeGenerator>>structTargetKindForVariableName: (in category 'JS code generator') -----
structTargetKindForVariableName: varName "<String>"
	^VMStructType structTargetKindForDeclaration: (self typeOfVariable: varName)!

----- Method: JSCodeGenerator>>translationMethodClass (in category 'utilities') -----
translationMethodClass
	"return the class used to produce JS translation methods from MethodNodes"
	^JSMethod!

----- Method: JSCodeGenerator>>typeOfArgument:in: (in category 'JS code generator') -----
typeOfArgument: argIndex in: selector
	| method |
	method := methods at: selector.
	^method declarations at: (method args at: argIndex).
!

----- Method: JSCodeGenerator>>typeOfVariable: (in category 'JS code generator') -----
typeOfVariable: varName "<String>" 
	scopeStack reverseDo:
		[:dict|
		(dict includesKey: varName) ifTrue:
			[^dict at: varName]].
	^variableDeclarations at: varName ifAbsent: nil!

----- Method: JSCodeGenerator>>uncheckedAbstractMethods (in category 'accessing') -----
uncheckedAbstractMethods
	"Answer the selectors for methods that should not be checked to ensure existence
	of concrete implementations, such as methods that are generated directly by the
	code generator itself."

	^uncheckedAbstractMethods

!

----- Method: JSCodeGenerator>>unreachableMethods (in category 'utilities') -----
unreachableMethods
	"Return a collection of methods that are never invoked."

	| sent out |
	sent := Set new.
	methods do: [ :m |
		m export ifTrue:[sent add: m selector].
		sent addAll: m allCalls.
	].

	out := OrderedCollection new.
	methods keys do: [ :sel |
		(sent includes: sel) ifFalse: [ out add: sel ].
	].
	^ out!

----- Method: JSCodeGenerator>>useSymbolicConstants (in category 'accessing') -----
useSymbolicConstants
	"Answer whether we should generate symbolic constants instead of their actual values"
	^useSymbolicConstants!

----- Method: JSCodeGenerator>>useSymbolicConstants: (in category 'accessing') -----
useSymbolicConstants: aBool
	"Indicate whether we should generate symbolic constants instead of their actual values"
	useSymbolicConstants := aBool!

----- Method: JSCodeGenerator>>var:declareC: (in category 'public') -----
var: varName declareC: declarationString
	"Record the given C declaration for a global variable."

	(declarationString includesSubString: varName) ifFalse:
		[self error: 'declaration omits variable name.  probably an error.  use e.g. var:type:'].
	variableDeclarations at: varName asString put: declarationString.!

----- Method: JSCodeGenerator>>var:type: (in category 'public') -----
var: varName type: type
"Use this in preference to #var:declareC: whenver possible since it avoids typing the varname twice and thus avoids the potential for a typo. See also #var:type:array:"
	self var: varName declareC: type , ' ' , varName!

----- Method: JSCodeGenerator>>var:type:array: (in category 'public') -----
var: varName type: type array: array
"use this in preference to #var:declareC: when possible. This produces a C statment of the form
int * fooArray[]={1,2,3}
See also #var:type: for simple var decls" 
	self
		var: varName
		declareC: (String streamContents: [:s |
			s nextPutAll: type.
			s space.
			s nextPutAll: varName.
			s nextPutAll: '[] = {'.
			self printArray: array on: s.
			s nextPut: $}])!

----- Method: JSCodeGenerator>>vmClass (in category 'public') -----
vmClass
	"Answer the interpreter classs if any.  This is nil other than for the core VM."
	^vmClass!

----- Method: JSCodeGenerator>>vmClass: (in category 'public') -----
vmClass: aClass
	"Set the interpreter class if any.  This is nil other than for the core VM."
	vmClass := aClass!

JSCodeGenerator subclass: #JSPluginCodeGenerator
	instanceVariableNames: 'pluginClass pluginName'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMakerJS-Translation to JS'!

!JSPluginCodeGenerator commentStamp: 'bf 10/3/2014 04:13' prior: 0!
I generate code that can be loaded dynamically from external libraries!

----- Method: JSPluginCodeGenerator>>doInlining: (in category 'inlining') -----
doInlining: inlineFlag
"do inlining for a plugin"
	self doBasicInlining: inlineFlag.
	self permitMethodPruning
		ifTrue: [self pruneUnreachableMethods]
!

----- Method: JSPluginCodeGenerator>>emitExportsOn: (in category 'JS code generator') -----
emitExportsOn: aStream
	"Store all the exported primitives in a form to be used by internal plugins"
	aStream nextPutAll:'

Squeak.registerExternalModule("', pluginName,'", {'.

	self exportedPrimitiveNames do:[:primName|
		aStream crtab: 1;
			nextPutAll: primName; 
			nextPutAll: ': '; 
			nextPutAll: primName;
			nextPutAll:','.
	].

aStream nextPutAll: '
});

}); // end of module
'.
!

----- Method: JSPluginCodeGenerator>>emitJSHeaderForPrimitivesOn: (in category 'JS code generator') -----
emitJSHeaderForPrimitivesOn: aStream
	"Write a C file header for compiled primitives onto the given stream."

	self emitJSHeaderOn: aStream.
	aStream nextPutAll: '
/*** Proxy Functions ***/
#define stackValue(i) (interpreterProxy->stackValue(i))
#define stackIntegerValue(i) (interpreterProxy->stackIntegerValue(i))
#define successFlag (!!interpreterProxy->failed())
#define success(bool) (interpreterProxy->success(bool))
#define arrayValueOf(oop) (interpreterProxy->arrayValueOf(oop))
#define checkedIntegerValueOf(oop) (interpreterProxy->checkedIntegerValueOf(oop))
#define fetchArrayofObject(idx,oop) (interpreterProxy->fetchArrayofObject(idx,oop))
#define fetchFloatofObject(idx,oop) (interpreterProxy->fetchFloatofObject(idx,oop))
#define fetchIntegerofObject(idx,oop) (interpreterProxy->fetchIntegerofObject(idx,oop))
#define floatValueOf(oop) (interpreterProxy->floatValueOf(oop))
#define pop(n) (interpreterProxy->pop(n))
#define pushInteger(n) (interpreterProxy->pushInteger(n))
#define sizeOfSTArrayFromCPrimitive(cPtr) (interpreterProxy->sizeOfSTArrayFromCPrimitive(cPtr))
#define storeIntegerofObjectwithValue(idx,oop,value) (interpreterProxy->storeIntegerofObjectwithValue(idx,oop,value))
#define primitiveFail() interpreterProxy->primitiveFail()
/* allows accessing Strings in both C and Smalltalk */
#define asciiValue(c) c

'.
	aStream cr.!

----- Method: JSPluginCodeGenerator>>emitJSHeaderOn: (in category 'JS code generator') -----
emitJSHeaderOn: aStream
	"Write a JS file header onto the given stream."

	aStream nextPutAll: '/* '.
	aStream nextPutAll: VMMaker headerNotice.
	aStream nextPutAll: ' */';cr.
	aStream nextPutAll: (self fileHeaderVersionStampForSourceClass: vmClass).
	aStream nextPutAll: '
module("users.bert.SqueakJS.plugins.', pluginName, '").requires("users.bert.SqueakJS.vm").toRun(function() {

var VM_PROXY_MAJOR = ', InterpreterPrimitives vmProxyMajorVersion, ';
var VM_PROXY_MINOR = ', InterpreterPrimitives vmProxyMinorVersion, ';

'.!

----- Method: JSPluginCodeGenerator>>generateCodeStringForPrimitives (in category 'public') -----
generateCodeStringForPrimitives
"TPR - moved down from JSCodeGenerator"
	| s methodList |
	s := ReadWriteStream on: (String new: 1000).
	methodList := methods asSortedCollection: [:m1 :m2 | m1 selector < m2 selector].
	self emitJSHeaderForPrimitivesOn: s.
	self emitJSConstantsOn: s.
	self emitJSVariablesOn: s.
	methodList do: [:m | m emitJSCodeOn: s generator: self].
	self emitExportsOn: s.
	^ s contents
!

----- Method: JSPluginCodeGenerator>>isGeneratingPluginCode (in category 'testing') -----
isGeneratingPluginCode
	^true!

----- Method: JSPluginCodeGenerator>>isTypePointerToStruct: (in category 'JS code generator') -----
isTypePointerToStruct: type "<String>"
	^pluginClass notNil
	  and: [[pluginClass isTypePointerToStruct: type]
			on: MessageNotUnderstood
			do: [:ex| ex message selector == #isTypePointerToStruct: ifTrue: [^false].
					ex pass]]!

----- Method: JSPluginCodeGenerator>>localizeGlobalVariables (in category 'public') -----
localizeGlobalVariables
"TPR - we don't do this for plugins"!

----- Method: JSPluginCodeGenerator>>pluginName: (in category 'public') -----
pluginName: aString
"TPR - moved from JSCodeGenerator"
	"Set the plugin name when generating plugins."
	pluginName := aString.!

----- Method: JSPluginCodeGenerator>>storeVirtualMachineProxyHeader:on: (in category 'private') -----
storeVirtualMachineProxyHeader: categoryList on: fileName
	"Store the interpreter definitions on the given file"
	| stream |
	stream := FileStream newFileNamed: fileName.
	stream nextPutAll:
'#ifndef _SqueakVM_H
#define _SqueakVM_H

/* Increment the following number if you change the order of
   functions listed or if you remove functions */
#define VM_PROXY_MAJOR 1

/* Increment the following number if you add functions at the end */
#define VM_PROXY_MINOR 0

typedef struct VirtualMachine {
	int (*minorVersion) (void);
	int (*majorVersion) (void);
'.

	categoryList do:[:assoc|
		stream cr; crtab; nextPutAll:'/* InterpreterProxy methodsFor: ''',assoc key, ''' */'; cr; crtab.
		assoc value asSortedCollection do:[:sel|
			(methods at: sel) emitProxyFunctionPrototype: stream generator: self.
			stream nextPutAll: ';'; crtab]].

	stream nextPutAll:'
} VirtualMachine;

#endif /* _SqueakVM_H */
'.
	stream close.!

----- Method: JSPluginCodeGenerator>>storeVirtualMachineProxyImplementation:on: (in category 'private') -----
storeVirtualMachineProxyImplementation: categoryList on: fileName
	"Store the interpreter definitions on the given file"
	| stream |
	stream := FileStream newFileNamed: fileName.
	stream nextPutAll:'
#include <math.h>
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <time.h>
#include "sqVirtualMachine.h"'; cr;cr.
	stream nextPutAll:'/*** Function prototypes ***/'.

	categoryList do:[:assoc|
		stream cr; cr; nextPutAll:'/* InterpreterProxy methodsFor: ''',assoc key, ''' */'; cr.
		assoc value asSortedCollection do:[:sel|
			(methods at: sel) emitJSFunctionHeader: stream generator: self.
			stream nextPutAll: ';'; cr]].

	stream cr; nextPutAll:'struct VirtualMachine *VM = NULL;'; cr.
	stream cr; nextPutAll:
'static int majorVersion(void) {
	return VM_PROXY_MAJOR;
}

static int minorVersion(void) {
	return VM_PROXY_MINOR;
}

struct VirtualMachine* sqGetInterpreterProxy(void)
{
	if(VM) return VM;
	VM = (struct VirtualMachine *) calloc(1, sizeof(VirtualMachine));
	/* Initialize Function pointers */
	VM->majorVersion = majorVersion;
	VM->minorVersion = minorVersion;
'.
	categoryList do:[:assoc|
		stream cr; crtab; nextPutAll:'/* InterpreterProxy methodsFor: ''',assoc key, ''' */'; crtab.
		assoc value asSortedCollection do:[:sel|
		stream nextPutAll:'VM->';
			nextPutAll: (self cFunctionNameFor: sel);
			nextPutAll:' = ';
			nextPutAll: (self cFunctionNameFor: sel);
			nextPutAll:';';
			crtab]].

	stream cr; crtab; nextPutAll:'return VM;'; cr; nextPutAll:'}'; cr.
	stream close.!

JSPluginCodeGenerator subclass: #JSSmartSyntaxPluginCodeGenerator
	instanceVariableNames: 'debugFlag'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMakerJS-SmartSyntaxPlugins'!

!JSSmartSyntaxPluginCodeGenerator commentStamp: 'bf 10/3/2014 04:18' prior: 0!
Subclass of JSCodeGenerator, used in connection with SmartSyntaxInterpreterPlugin to generate named primitives with type coercion specifications.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asBooleanValueFrom:on: (in category 'linking') -----
emitLoad: aString asBooleanValueFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: ' = interpreterProxy->booleanValueOf(';
		crtab: 2;
		nextPutAll: 'interpreterProxy->stackValue(';
		nextPutAll: anInteger asString;
		nextPutAll: '))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asCharPtrFrom:on: (in category 'linking') -----
emitLoad: aString asCharPtrFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: 	' = (char *) interpreterProxy->firstIndexableField(';
		crtab: 2;
		nextPutAll: 	'interpreterProxy->stackValueOf(';
		nextPutAll: anInteger asString;
		nextPutAll: '))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asFloatPtrFrom:on: (in category 'linking') -----
emitLoad: aString asFloatPtrFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: 	' = (float *) interpreterProxy->firstIndexableField(';
		crtab: 2;
		nextPutAll: 	'interpreterProxy->stackValueOf(';
		nextPutAll: anInteger asString;
		nextPutAll: '))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asFloatValueFrom:on: (in category 'linking') -----
emitLoad: aString asFloatValueFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: 	' = interpreterProxy->stackFloatValue(';
		nextPutAll: anInteger asString;
		nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asIntPtrFrom:on: (in category 'linking') -----
emitLoad: aString asIntPtrFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: 	' = (int *) interpreterProxy->firstIndexableField(';
		crtab: 2;
		nextPutAll: 	'interpreterProxy->stackValueOf(';
		nextPutAll: anInteger asString;
		nextPutAll: '))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asIntegerValueFrom:on: (in category 'linking') -----
emitLoad: aString asIntegerValueFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: 	' = interpreterProxy stackIntegerValue(';
		nextPutAll: anInteger asString;
		nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asKindOf:from:on: (in category 'linking') -----
emitLoad: aString asKindOf: aClass from: anInteger on: aStream

	self emitLoad: aString asNakedOopFrom: anInteger on: aStream.
	aStream
		crtab;
		nextPutAll: 'interpreterProxy->success(interpreterProxy->isKindOf(';
		nextPutAll: aString;
		nextPutAll: 	', ''';
		nextPutAll:	aClass asString;
		nextPutAll: '''))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asMemberOf:from:on: (in category 'linking') -----
emitLoad: aString asMemberOf: aClass from: anInteger on: aStream

	self emitLoad: aString asNakedOopFrom: anInteger on: aStream.
	aStream
		crtab;
		nextPutAll: 'interpreterProxy->success(interpreterProxy->isMemberOf(';
		nextPutAll: aString;
		nextPutAll: 	', ''';
		nextPutAll:	aClass asString;
		nextPutAll: '''))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asNakedOopFrom:on: (in category 'linking') -----
emitLoad: aString asNakedOopFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: ' = interpreterProxy stackValue(';
		nextPutAll: anInteger asString;
		nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asNonIntegerValueFrom:on: (in category 'linking') -----
emitLoad: aString asNonIntegerValueFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: 	' = interpreterProxy stackObjectValue(';
		nextPutAll: anInteger asString;
		nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>emitLoad:asUnsignedValueFrom:on: (in category 'linking') -----
emitLoad: aString asUnsignedValueFrom: anInteger on: aStream

	aStream
		nextPutAll: aString;
		nextPutAll: 	' = interpreterProxy->positive32BitValueOf(';
		crtab: 2;
		nextPutAll: 	'interpreterProxy->stackValue(';
		nextPutAll: anInteger asString;
		nextPutAll: '))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsBooleanObj:on:indent: (in category 'translating builtins') -----
generateAsBooleanObj: aNode on: aStream indent: anInteger

	aStream nextPutAll: '('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: 
		') ? interpreterProxy->trueObject(): interpreterProxy->falseObject()'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsCBoolean:on:indent: (in category 'translating builtins') -----
generateAsCBoolean: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->booleanValueOf('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsCDouble:on:indent: (in category 'translating builtins') -----
generateAsCDouble: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->floatValueOf('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsCInt:on:indent: (in category 'translating builtins') -----
generateAsCInt: aNode on: aStream indent: anInteger

	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ' >> 1'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsCUnsigned:on:indent: (in category 'translating builtins') -----
generateAsCUnsigned: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->positive32BitValueOf('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsCharPtr:on:indent: (in category 'translating builtins') -----
generateAsCharPtr: aNode on: aStream indent: anInteger

	aStream nextPutAll: '(char *) interpreterProxy->firstIndexableField('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsFloatObj:on:indent: (in category 'translating builtins') -----
generateAsFloatObj: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->floatObjectOf('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsIfVar:on:indent: (in category 'translating builtins') -----
generateAsIfVar: aNode on: aStream indent: anInteger

	| cName fName class index |
	cName := String streamContents: 
		[:scStr | self emitJSExpression: aNode args first on: scStr].
	class := Smalltalk 
		at: (cName asSymbol) 
		ifAbsent: [nil].
	(class isNil not and: [class isBehavior]) ifFalse: 
		[^self error: 'first arg must identify class'].
	fName := aNode args second value.
	index := class allInstVarNames
		indexOf: fName
		ifAbsent: [^self error: 'second arg must be instVar'].
	aStream 
		nextPutAll: 'interpreterProxy->fetchPointerofObject(';
		nextPutAll: (index - 1) asString;
		nextPutAll: ','.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsIfVarAsValue:on:indent: (in category 'translating builtins') -----
generateAsIfVarAsValue: aNode on: aStream indent: anInteger

	| cName fName class index fetchNode |
	cName := String streamContents: 
		[:scStr | self emitJSExpression: aNode args first on: scStr].
	class := Smalltalk 
		at: (cName asSymbol) 
		ifAbsent: [nil].
	(class isNil not and: [class isBehavior]) ifFalse: 
		[^self error: 'first arg must identify class'].
	fName := aNode args second value.
	index := class allInstVarNames
		indexOf: fName
		ifAbsent: [^self error: 'second arg must be instVar'].
	fetchNode := TSendNode new
		setSelector: #fetchPointer:ofObject:
		receiver: (TVariableNode new setName: 'interpreterProxy')
		arguments: (Array
			with: (TConstantNode new setValue: index - 1)
			with: aNode receiver).
	cName := aNode args third nameOrValue.
	class := Smalltalk 
		at: (cName asSymbol) 
		ifAbsent: [nil].
	(class isNil not and: [class isBehavior]) ifFalse: 
		[^self error: 'third arg must identify class'].
	class jscg: self generateCoerceToValueFrom: fetchNode on: aStream
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsIfVarPut:on:indent: (in category 'translating builtins') -----
generateAsIfVarPut: aNode on: aStream indent: anInteger

	| cName fName class index |
	cName := String streamContents: 
		[:scStr | self emitJSExpression: aNode args first on: scStr].
	class := Smalltalk 
		at: (cName asSymbol) 
		ifAbsent: [nil].
	(class isNil not and: [class isBehavior]) ifFalse: 
		[^self error: 'first arg must identify class'].
	fName := aNode args second value.
	index := class allInstVarNames
		indexOf: fName
		ifAbsent: [^self error: 'second arg must be instVar'].
	aStream 
		nextPutAll: 'interpreterProxy->storePointerofObjectwithValue(';
		nextPutAll: (index - 1) asString;
		nextPutAll: ','.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: aNode args third on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsIntPtr:on:indent: (in category 'translating builtins') -----
generateAsIntPtr: aNode on: aStream indent: anInteger

	aStream nextPutAll: '(int *) interpreterProxy->firstIndexableField('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsOop:on:indent: (in category 'translating builtins') -----
generateAsOop: aNode on: aStream indent: anInteger

	| cName class |
	cName := aNode args first nameOrValue.
	class := Smalltalk 
		at: (cName asSymbol) 
		ifAbsent: [nil].
	(class isNil not and: [class isBehavior]) ifFalse: 
		[^self error: 'first arg must identify class'].
	class jscg: self generateCoerceToOopFrom: aNode receiver on: aStream!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsPositiveIntegerObj:on:indent: (in category 'translating builtins') -----
generateAsPositiveIntegerObj: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->positive32BitIntegerFor('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsSmallIntegerObj:on:indent: (in category 'translating builtins') -----
generateAsSmallIntegerObj: aNode on: aStream indent: anInteger
	self emitJSExpression: aNode receiver on: aStream.
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateAsValue:on:indent: (in category 'translating builtins') -----
generateAsValue: aNode on: aStream indent: anInteger

	| cName class |
	cName := aNode args first nameOrValue.
	class := Smalltalk 
		at: (cName asSymbol) 
		ifAbsent: [nil].
	(class isNil not and: [class isBehavior]) ifFalse: 
		[^self error: 'first arg must identify class'].
	class jscg: self generateCoerceToValueFrom: aNode receiver on: aStream!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCPtrAsOop:on:indent: (in category 'translating builtins') -----
generateCPtrAsOop: aNode on: aStream indent: anInteger 

	aStream nextPutAll: '('.
	aStream nextPutAll: 'oopForPointer( '.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ' ) - BASE_HEADER_SIZE)'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateClass:on:indent: (in category 'translating builtins') -----
generateClass: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->fetchClassOf('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToBooleanObjectFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToBooleanObjectFrom: aNode on: aStream

	aStream nextPutAll: '('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: '? interpreterProxy.trueObject() : interpreterProxy.falseObject())'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToBooleanValueFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToBooleanValueFrom: aNode on: aStream
self halt: 'todo'.
	aStream nextPutAll: 'interpreterProxy.booleanValueOf('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToFloatObjectFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToFloatObjectFrom: aNode on: aStream
self halt: 'todo'.
	aStream nextPutAll: 'interpreterProxy.floatObjectOf('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToFloatValueFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToFloatValueFrom: aNode on: aStream
self halt: 'todo'.
	aStream nextPutAll: 'interpreterProxy.floatValueOf('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToObjectFromPtr:on: (in category 'asOop:/asValue:') -----
generateCoerceToObjectFromPtr: aNode on: aStream
	"This code assumes no named instance variables"
self halt: 'todo'.
	aStream nextPutAll: 'oopForPointer('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: ') - BASE_HEADER_SIZE'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToPtr:fromObject:on: (in category 'asOop:/asValue:') -----
generateCoerceToPtr: aString fromObject: aNode on: aStream
	"This code assumes no named instance variables"
self halt: 'todo'.
	aStream 
		nextPutAll: '((';
		nextPutAll: aString;
		nextPutAll: ') interpreterProxy->firstIndexableField('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: '))'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToSmallIntegerObjectFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToSmallIntegerObjectFrom: aNode on: aStream
	self emitJSExpression: aNode on: aStream.
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToSmallIntegerValueFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToSmallIntegerValueFrom: aNode on: aStream
	self emitJSExpression: aNode on: aStream.
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToUnsignedObjectFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToUnsignedObjectFrom: aNode on: aStream
self halt: 'todo'.
	aStream nextPutAll: 'interpreterProxy.positive32BitIntegerFor('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateCoerceToUnsignedValueFrom:on: (in category 'asOop:/asValue:') -----
generateCoerceToUnsignedValueFrom: aNode on: aStream
self halt: 'todo'.
	aStream nextPutAll: 'interpreterProxy.positive32BitValueOf('.
	self emitJSExpression: aNode on: aStream.
	aStream nextPutAll: ')'!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateDebugCode (in category 'debug code') -----
generateDebugCode
	^ debugFlag!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateDebugCode: (in category 'debug code') -----
generateDebugCode: aBool 
	debugFlag := aBool!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateDebugCode:on:indent: (in category 'translating builtins') -----
generateDebugCode: aNode on: aStream indent: level 
	"Generate the C debug code for this message onto the given stream, if  
	compiled in debugMode."
	self generateDebugCode
		ifTrue: 
			[aStream nextPutAll: '// DebugCode...';
			 cr.
			aNode args first
				emitJSCodeOn: aStream
				level: level
				generator: self.
			aStream tab: level.
			aStream nextPutAll: '// ...DebugCode']
		ifFalse: [aStream nextPutAll: '// missing DebugCode']!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateField:on:indent: (in category 'translating builtins') -----
generateField: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->fetchPointerofObject('.
	self emitJSExpression: aNode args first on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateFieldPut:on:indent: (in category 'translating builtins') -----
generateFieldPut: aNode on: aStream indent: anInteger
		
	aStream nextPutAll: 'interpreterProxy->storePointerofObjectwithValue('.
	self emitJSExpression: aNode args first on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: aNode args second on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateFromStack:on:indent: (in category 'translating builtins') -----
generateFromStack: aNode on: aStream indent: anInteger

	| idList |
	aNode args first isConstant ifFalse: [^self error: 'arg must be constant'].
	idList := aNode args first value.
	(1 to: idList size)
		do: [:i | 
			aStream 
				nextPutAll: (idList at: i);
				nextPutAll: ' = interpreterProxy->stackValue(';
				nextPutAll: (idList size - i) asString;
				nextPutAll: ')']
		separatedBy: [aStream nextPut: $;; crtab: anInteger].
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsBytes:on:indent: (in category 'translating builtins') -----
generateIsBytes: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isBytes('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsFloat:on:indent: (in category 'translating builtins') -----
generateIsFloat: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isFloatObject('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsIndexable:on:indent: (in category 'translating builtins') -----
generateIsIndexable: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isIndexable('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsInteger:on:indent: (in category 'translating builtins') -----
generateIsInteger: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isIntegerValue('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsIntegerOop:on:indent: (in category 'translating builtins') -----
generateIsIntegerOop: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isIntegerObject('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsIntegerValue:on:indent: (in category 'translating builtins') -----
generateIsIntegerValue: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isIntegerValue('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsKindOf:on:indent: (in category 'translating builtins') -----
generateIsKindOf: aNode on: aStream indent: anInteger
	| className |
	className := aNode args second value.
	(#('LargePositiveInteger', 'LargeNegativeInteger') includes: className) ifTrue: [
		self emitJSExpression: aNode args first on: aStream.
		^aStream nextPutAll: '.sqClass === interpreterProxy.class', className, '()'].
	(#('Integer') includes: className) ifFalse: [self halt: 'isKindOf: ', className].
	aStream nextPutAll: 'interpreterProxy.isKindOf', className, '('.
	self emitJSExpression: aNode args first on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsMemberOf:on:indent: (in category 'translating builtins') -----
generateIsMemberOf: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isMemberOf('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ','''.
	self emitJSExpression: aNode args first on: aStream.
	aStream nextPutAll: ''')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsPointers:on:indent: (in category 'translating builtins') -----
generateIsPointers: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isPointers('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsWords:on:indent: (in category 'translating builtins') -----
generateIsWords: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isWords('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateIsWordsOrBytes:on:indent: (in category 'translating builtins') -----
generateIsWordsOrBytes: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->isWordsOrBytes('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateNext:on:indent: (in category 'translating builtins') -----
generateNext: msgNode on: aStream indent: level
	"Generate the C code for this message onto the given stream."

	| varNode |
	varNode := msgNode receiver.
	varNode isVariable
		ifFalse: [ self error: 'next can only be applied to variables' ].
	aStream nextPutAll: '*'.
	aStream nextPutAll: varNode name.
	aStream nextPutAll: '++'
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateRemapOopIn:on:indent: (in category 'translating builtins') -----
generateRemapOopIn: aNode on: aStream indent: level
	"Generate the JS code for this message onto the given stream."

	aNode args second emitJSCodeOn: aStream level: level-1 generator: self.
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateStAt:on:indent: (in category 'translating builtins') -----
generateStAt: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->stObjectat('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: aNode args first on: aStream.
	aStream nextPutAll: ')'
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateStAtPut:on:indent: (in category 'translating builtins') -----
generateStAtPut: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy.stObjectatput('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: aNode args first on: aStream.
	aStream nextPutAll: ','.
	self emitJSExpression: aNode args second on: aStream.
	aStream nextPutAll: ')'
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>generateStSize:on:indent: (in category 'translating builtins') -----
generateStSize: aNode on: aStream indent: anInteger

	aStream nextPutAll: 'interpreterProxy->stSizeOf('.
	self emitJSExpression: aNode receiver on: aStream.
	aStream nextPutAll: ')'.!

----- Method: JSSmartSyntaxPluginCodeGenerator>>initialize (in category 'initialize') -----
initialize
	super initialize.
	debugFlag := false.
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>initializeCTranslationDictionary (in category 'translating builtins') -----
initializeCTranslationDictionary 
	"Initialize the dictionary mapping message names to actions for C code generation."

	| pairs |
	super initializeCTranslationDictionary.
	pairs := #(
		#asCInt						#generateAsCInt:on:indent:
		#asCUnsigned				#generateAsCUnsigned:on:indent:
		#asCBoolean					#generateAsCBoolean:on:indent:
		#asCDouble					#generateAsCDouble:on:indent:

		#asSmallIntegerObj			#generateAsSmallIntegerObj:on:indent:
		#asPositiveIntegerObj		#generateAsPositiveIntegerObj:on:indent:
		#asBooleanObj				#generateAsBooleanObj:on:indent:
		#asFloatObj					#generateAsFloatObj:on:indent:

		#asIf:var:					#generateAsIfVar:on:indent:
		#asIf:var:asValue:			#generateAsIfVarAsValue:on:indent:
		#asIf:var:put:				#generateAsIfVarPut:on:indent:
		#field:						#generateField:on:indent:
		#field:put:					#generateFieldPut:on:indent:
		
		#class						#generateClass:on:indent:

		#stSize						#generateStSize:on:indent:
		#stAt:						#generateStAt:on:indent:
		#stAt:put:					#generateStAtPut:on:indent:

		#asCharPtr					#generateAsCharPtr:on:indent:
		#asIntPtr					#generateAsIntPtr:on:indent:
		#cPtrAsOop					#generateCPtrAsOop:on:indent:
		#next						#generateNext:on:indent:

		#asOop:						#generateAsOop:on:indent:
		#asValue:					#generateAsValue:on:indent:

		#isFloat						#generateIsFloat:on:indent:
		#isIndexable					#generateIsIndexable:on:indent:
		#isIntegerOop				#generateIsIntegerOop:on:indent:
		#isIntegerValue				#generateIsIntegerValue:on:indent:
		#FloatOop					#generateIsFloatValue:on:indent:
		#isWords					#generateIsWords:on:indent:
		#isWordsOrBytes				#generateIsWordsOrBytes:on:indent:
		#isPointers					#generateIsPointers:on:indent:
		#isNil						#generateIsNil:on:indent:
		#isMemberOf:				#generateIsMemberOf:on:indent:
		#isKindOf:					#generateIsKindOf:on:indent:

		#fromStack:					#generateFromStack:on:indent:
		#clone						#generateClone:on:indent
		#new						#generateNew:on:indent
		#new:						#generateNewSize:on:indent
		#superclass					#generateSuperclass:on:indent:
		#remapOop:in:				#generateRemapOopIn:on:indent:
		#debugCode:					#generateDebugCode:on:indent:
	).

	1 to: pairs size by: 2 do: [:i |
		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asBooleanValueFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asBooleanValueFrom: anInteger
	"Answer codestring for boolean coercion (with validating side-effect) of object, as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy booleanValueOf:';
		crtab: 2;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	')'])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asCharPtrFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asCharPtrFrom: anInteger
	"Answer codestring for character pointer to first indexable field of object (without validating side-effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''char *'''])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asCharPtrFrom:andThen: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asCharPtrFrom: anInteger andThen: valBlock
	"Answer codestring for character pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^(valBlock value: anInteger), '.',
	 (aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''char *''']))
	 !

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asFloatValueFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asFloatValueFrom: anInteger
	"Answer codestring for double precision coercion (with validating side-effect) of oop, as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy stackFloatValue: ';
		nextPutAll: anInteger asString])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asIntPtrFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asIntPtrFrom: anInteger
	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''int *'''])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asIntPtrFrom:andThen: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asIntPtrFrom: anInteger andThen: valBlock
	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^(valBlock value: anInteger), '.',
	 (aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''int *''']))!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asIntegerValueFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asIntegerValueFrom: anInteger
	"Answer codestring for integer coercion (with validating side-effect) of oop, as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy stackIntegerValue: ';
		nextPutAll: anInteger asString])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asKindOf:from: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asKindOf: aClass from: anInteger

	^String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy success: (interpreterProxy';
		crtab: 2;
		nextPutAll: 'is: (interpreterProxy stackValue: ';
		nextPutAll: anInteger asString;
		nextPutAll: ')';
		crtab: 2;
		nextPutAll: 	'KindOf: ''';
		nextPutAll:	aClass asString;
		nextPutAll: ''').';
		crtab;
		nextPutAll: (self 
						jscgLoad: aBlock 
						expr: aString 
						asRawOopFrom: anInteger)]!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asMemberOf:from: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asMemberOf: aClass from: anInteger

	^String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy success: (interpreterProxy';
		crtab: 2;
		nextPutAll: 'is: (interpreterProxy stackValue: ';
		nextPutAll: anInteger asString;
		nextPutAll: ')';
		crtab: 2;
		nextPutAll: 	'MemberOf: ''';
		nextPutAll:	aClass asString;
		nextPutAll: ''').';
		crtab;
		nextPutAll: (self 
						jscgLoad: aBlock 
						expr: aString 
						asRawOopFrom: anInteger)]!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asNamedPtr:from: (in category 'coercing') -----
jscgLoad: aBlock expr: exprString asNamedPtr: recordString from: anInteger
	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''';
		nextPutAll: recordString;
		nextPutAll: ' *'''])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asNamedPtr:from:andThen: (in category 'coercing') -----
jscgLoad: aBlock expr: exprString asNamedPtr: recordString from: anInteger andThen: valBlock
	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^(valBlock value: anInteger), '.',
	 (aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''';
		nextPutAll: recordString;
		nextPutAll: ' *''']))!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asNonIntegerValueFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asNonIntegerValueFrom: anInteger
	"Answer codestring for oop (with validating side effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy stackObjectValue: ';
		nextPutAll: anInteger asString])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asRawOopFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asRawOopFrom: anInteger
	"Answer a string for a Slang expression that will load an oop (without validation) from stack index anInteger.  Apply aBlock, a BlockContext instance that when passed an expression, will return a string assigning the expression to the desired identifier, to the string before answering.  aString is a Slang expression that refers to the stack value, once it has been loaded."

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy stackValue: ';
		nextPutAll: anInteger asString])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asUnsignedPtrFrom:andThen: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asUnsignedPtrFrom: anInteger andThen: valBlock
	"Answer a codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^(valBlock value: anInteger), '.',
	 (aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''unsigned *''']))!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asUnsignedValueFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asUnsignedValueFrom: anInteger
	"Answer a codestring for positive integer coercion (with validating side-effect) of oop, as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'interpreterProxy positive32BitValueOf:';
		crtab: 2;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	')'])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asWBCharPtrFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asWBCharPtrFrom: anInteger
	"Answer codestring for char pointer to first indexable field of object (with validating side-effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy arrayValueOf:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''char *'''])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asWBFloatPtrFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asWBFloatPtrFrom: anInteger
	"Answer codestring for single-precision float pointer to first indexable field of object (with validating side-effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy arrayValueOf:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''float *'''])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgLoad:expr:asWBIntPtrFrom: (in category 'coercing') -----
jscgLoad: aBlock expr: aString asWBIntPtrFrom: anInteger
	"Answer codestring for integer pointer to first indexable field of object (with validating side-effect), as described in comment to jscgLoad:expr:asRawOopFrom:"

	^aBlock value: (String streamContents: [:aStream | aStream
		nextPutAll: 'self cCoerce: (interpreterProxy arrayValueOf:';
		crtab: 4;
		nextPutAll: '(interpreterProxy stackValue:';
		nextPutAll: anInteger asString;
		nextPutAll:	'))';
		crtab: 3;
		nextPutAll: 'to: ''int *'''])!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgSetBlock: (in category 'coercing') -----
jscgSetBlock: aString

	^[:expr | aString, ' := ', expr]!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgTVarBlock: (in category 'coercing') -----
jscgTVarBlock: anInteger

	^[:expr | '(thisContext tempAt: 1) tempAt: ', anInteger asString, ' put: (', expr, ')']!

----- Method: JSSmartSyntaxPluginCodeGenerator>>jscgValBlock: (in category 'coercing') -----
jscgValBlock: valString
	^[:index | String streamContents:
		[:aStream | aStream
			nextPutAll: 'interpreterProxy success: (interpreterProxy ';
			nextPutAll: valString;
			nextPutAll: ': (interpreterProxy stackValue: ';
			nextPutAll: index asString;
			nextPutAll: '))']]!

----- Method: JSSmartSyntaxPluginCodeGenerator>>translationMethodClass (in category 'initialize') -----
translationMethodClass
	"return the class used to produce C translation methods from MethodNodes"
	^JSSmartSyntaxPluginMethod!

----- Method: JSSmartSyntaxPluginCodeGenerator>>var:as: (in category 'transforming') -----
var: varName as: aClass
	"Record the given C declaration for a global variable"

	variableDeclarations at: varName asString put: (aClass jscgDeclareJSForVar: varName)!

Object subclass: #JSMethod
	instanceVariableNames: 'selector returnType args locals declarations primitive parseTree labels possibleSideEffectsCache complete export static sharedLabel sharedCase comment definingClass globalStructureBuildMethodHasFoo canAsmLabel mustAsmLabel properties cascadeVariableNumber extraVariableNumber'
	classVariableNames: 'CaseStatements'
	poolDictionaries: ''
	category: 'VMMakerJS-Translation to JS'!

!JSMethod commentStamp: 'bf 10/3/2014 04:14' prior: 0!
A JSMethod is a translation method, representing a MethodNode that is to be translated to JavaScript source. It has a parseTree of translation nodes that mirrors the parse tree of the corresponding Smalltalk method.!

----- Method: JSMethod class>>initialize (in category 'class initialization') -----
initialize
	"JSMethod initialize"	
	CaseStatements := IdentitySet new: 10.
	CaseStatements addAll: #(dispatchOn:in: dispatchOn:in:with: dispatchOn:in:with:with:).!

----- Method: JSMethod>>addVarsDeclarationsAndLabelsOf: (in category 'inlining support') -----
addVarsDeclarationsAndLabelsOf: methodToBeInlined
	"Prepare to inline the body of the given method into the receiver by making the args and locals of the argument to the receiver be locals of the receiver. Record any type declarations for these variables. Record labels. Assumes that the variables have already be renamed to avoid name clashes."

	methodToBeInlined args, methodToBeInlined locals do: [ :v |
		(locals includes: v) ifFalse: [ locals addLast: v ].
	].
	methodToBeInlined declarations associationsDo: [ :assoc |
		declarations add: assoc.
	].
	methodToBeInlined labels do: [ :label |
		labels add: label.
	].!

----- Method: JSMethod>>allCalls (in category 'utilities') -----
allCalls
	"Answer a collection of selectors for the messages sent by this method."

	^parseTree allCalls!

----- Method: JSMethod>>argAssignmentsFor:args:in: (in category 'inlining') -----
argAssignmentsFor: meth args: argList in: aCodeGen
	"Return a collection of assignment nodes that assign the given argument expressions to the formal parameter variables of the given method."
	"Optimization: If the actual parameters are either constants or local variables in the target method (the receiver), substitute them directly into the body of meth. Note that global variables cannot be subsituted because the inlined method might depend on the exact ordering of side effects to the globals."

	| stmtList substitutionDict |
	stmtList := OrderedCollection new: 100.
	substitutionDict := Dictionary new: 100.
	meth args with: argList do: [ :argName :exprNode |
		(self isSubstitutableNode: exprNode intoMethod: meth in: aCodeGen) ifTrue: [
			substitutionDict at: argName put: exprNode.
			locals remove: argName.
		] ifFalse: [
			stmtList add: (TAssignmentNode new
				setVariable: (TVariableNode new setName: argName)
				expression: exprNode copyTree).
		].
	].
	meth parseTree: (meth parseTree bindVariablesIn: substitutionDict).
	^stmtList!

----- Method: JSMethod>>argConversionExprFor:stackIndex: (in category 'primitive compilation') -----
argConversionExprFor: varName stackIndex: stackIndex 
	"Return the parse tree for an expression that fetches and converts the 
	primitive argument at the given stack offset."
	| exprList decl stmtList |
	exprList := OrderedCollection new.
	(declarations includesKey: varName) ifTrue:[
		decl := declarations at: varName.
		(decl includes: $*) ifTrue:["array"
			(decl includesSubString: 'char') ifTrue:[ | expr |
				expr := '(interpreterProxy isBytes: (interpreterProxy stackValue: (stackIndex))) ifFalse:[^interpreterProxy primitiveFail].'.
				expr := expr copyReplaceAll: 'interpreterProxy' with: self vmNameString.
				expr := expr copyReplaceAll: 'stackIndex' with: stackIndex printString.
				exprList add: expr.
			].
			exprList add: varName , ' := ', self vmNameString, ' arrayValueOf: (', self vmNameString, ' stackValue: (' , stackIndex printString , '))'.
			exprList add: varName , ' := ' , varName , ' - 1'.
		] ifFalse:["must be a double"
			(decl findString: 'double' startingAt: 1) = 0 ifTrue: [
				self error: 'unsupported type declaration in a primitive method'
			].
			exprList add: varName , ' := ', self vmNameString, ' stackFloatValue: ' , stackIndex printString.
		]
	] ifFalse: ["undeclared variables are taken to be integer"
		exprList add: varName , ' := ', self vmNameString, ' stackIntegerValue: ' , stackIndex printString
	].
	stmtList := OrderedCollection new.
	exprList do: [:e | stmtList addAll: (self statementsFor: e varName: varName)].
	^ stmtList!

----- Method: JSMethod>>args (in category 'accessing') -----
args
	"The arguments of this method."

	^args!

----- Method: JSMethod>>asInlineNode (in category 'transformations') -----
asInlineNode
	^TInlineNode new method: self!

----- Method: JSMethod>>bindClassVariablesIn: (in category 'transformations') -----
bindClassVariablesIn: constantDictionary
	"Class variables are used as constants. This method replaces all references to class variables in the body of this method with the corresponding constant looked up in the class pool dictionary of the source class. The source class class variables should be initialized before this method is called."

	parseTree := parseTree bindVariablesIn: constantDictionary.!

----- Method: JSMethod>>bindVariableUsesIn: (in category 'transformations') -----
bindVariableUsesIn: aDictionary
	parseTree := parseTree bindVariableUsesIn: aDictionary.!

----- Method: JSMethod>>buildCaseStmt: (in category 'transformations') -----
buildCaseStmt: aSendNode
	"Build a case statement node for the given send of dispatchOn:in:."
	"Note: the first argument is the variable to be dispatched on. The second argument is a constant node holding an array of unary selectors, which will be turned into sends to self."

	((aSendNode args size >= 2) and:
	 [aSendNode args second isConstant and:
	 [aSendNode args second value class = Array]]) ifFalse: [
		self error: 'wrong node structure for a case statement'.
	].

	^TCaseStmtNode new
		setExpression: aSendNode args first
		selectors: aSendNode args second value
		arguments: (aSendNode args copyFrom: 3 to: aSendNode args size)!

----- Method: JSMethod>>checkForCompleteness:in: (in category 'inlining') -----
checkForCompleteness: stmtLists in: aCodeGen
	"Set the complete flag if none of the given statement list nodes contains further candidates for inlining."

	complete := true.
	stmtLists do: [ :stmtList |
		stmtList statements do: [ :node |
			(self inlineableSend: node in: aCodeGen) ifTrue: [
				complete := false.  "more inlining to do"
				^self
			].
		].
	].
	parseTree nodesDo: [ :n |
		(self inlineableFunctionCall: n in: aCodeGen) ifTrue: [
			complete := false.  "more inlining to do"
			^self
		].
	].!

----- Method: JSMethod>>checkSuccessExpr (in category 'primitive compilation') -----
checkSuccessExpr
	"Return the parse tree for an expression that aborts the primitive if the successFlag is not true."

	| expr |
	expr := 'successFlag ifFalse: [^ nil ]'.
	^ self statementsFor: expr varName: ''
!

----- Method: JSMethod>>comment: (in category 'accessing') -----
comment: aComment

	comment := aComment !

----- Method: JSMethod>>computePossibleSideEffectsIn: (in category 'inlining support') -----
computePossibleSideEffectsIn: aCodeGen
	"Answer true if this method may have side effects. It has side effects if it assigns to a global variable. It may have side effects if it calls a non-built-in method."

	parseTree nodesDo: [ :node |
		node isSend ifTrue: [
			node isBuiltinOperator ifFalse: [ ^true ].
		].
	].
	^ false!

----- Method: JSMethod>>copy (in category 'utilities') -----
copy
	"Make a deep copy of this JSMethod."

	^ (self class basicNew)
		setSelector: selector
		returnType: returnType
		args: args copy
		locals: locals copy
		declarations: declarations copy
		primitive: primitive
		parseTree: parseTree copyTree
		labels: labels copy
		complete: complete;
		sharedLabel: sharedLabel;
		sharedCase: sharedCase;
		yourself
!

----- Method: JSMethod>>covertToZeroBasedArrayReferences (in category 'primitive compilation') -----
covertToZeroBasedArrayReferences
	"Replace the index expressions in at: and at:put: messages with (<expr> - 1), since C uses zero-based array indexing."
	"Note: Up through release 1.31, generated primitives used the convention that array variables pointed to the first element. That meant that Smalltalk one-based index expressions had to have one subtracted to yield a zero-based index. Later, we decided to adjust the base address by -1 once in the primitive prolog rather on every array access. This resulted in a five percent performance increase for the bitmap compress/decompress primitives. This method is retained as documentation and in case we choose to revert the the previous scheme."

	| oldIndexExpr newIndexExpr |
	parseTree nodesDo: [ :n |
		(n isSend and: [(n selector = #at:) or: [ n selector = #at:put: ]]) ifTrue: [
			oldIndexExpr := n args first.
			oldIndexExpr isConstant ifTrue: [
				"index expression is a constant: decrement the constant now"
				newIndexExpr := TConstantNode new setValue: (n args first value - 1).
			] ifFalse: [
				"index expression is complex: build an expression to decrement result at runtime"
				newIndexExpr := TSendNode new
					setSelector: #-
					receiver: oldIndexExpr
					arguments: (Array with: (TConstantNode new setValue: 1)).
			].
			n args at: 1 put: newIndexExpr.
		].
	].
!

----- Method: JSMethod>>declarationAt: (in category 'accessing') -----
declarationAt: aVariableName
	^declarations at: aVariableName ifAbsent: [#sqInt, ' ', aVariableName]!

----- Method: JSMethod>>declarationAt:put: (in category 'accessing') -----
declarationAt: aVariableName  "<String>" put: aDeclaration "<String>" "^aDeclaration"
	^declarations at: aVariableName put: aDeclaration!

----- Method: JSMethod>>declarations (in category 'accessing') -----
declarations
	"The type declaration dictionary of this method."

	^declarations!

----- Method: JSMethod>>definingClass (in category 'accessing') -----
definingClass
	^definingClass!

----- Method: JSMethod>>definingClass: (in category 'accessing') -----
definingClass: aClass
	definingClass := aClass.!

----- Method: JSMethod>>emitGlobalStructReferenceOn: (in category 'JS code generation') -----
emitGlobalStructReferenceOn: aStream
	"Add a reference to the globals struct if needed"

	(self globalStructureBuildMethodHasFoo > 1)
		ifTrue: [aStream nextPutAll: 'var foo = fum;'; cr].
!

----- Method: JSMethod>>emitInlineOn:level:generator: (in category 'JS code generation') -----
emitInlineOn: aStream level: level generator: aCodeGen
	"Emit C code for this method onto the given stream. All calls to inlined methods should already have been expanded."
	self removeUnusedTemps.
	sharedLabel ifNotNil:[
		aStream crtab: level-1; nextPutAll: sharedLabel; nextPutAll:':'.
		aStream crtab: level.
		aStream nextPutAll: '/* '; nextPutAll: selector; nextPutAll: ' */'.
		aStream crtab: level.
	].
	aStream nextPutAll:'{'; cr.
	locals do: [ :var |
		aStream tab: level+1.
		aStream nextPutAll: (declarations at: var ifAbsent: [ 'sqInt ', var]), ';'; cr.
	].
	parseTree emitJSCodeOn: aStream level: level+1 generator: aCodeGen.
	aStream tab: level; nextPutAll: '}'; cr.!

----- Method: JSMethod>>emitJSCodeOn:generator: (in category 'JS code generation') -----
emitJSCodeOn: aStream generator: aCodeGen
	"Emit JS code for this method onto the given stream. All calls to inlined methods should already have been expanded."
	aCodeGen currentMethod: self.
	aCodeGen pushScope: declarations while: [
		self emitJSCommentOn: aStream.	"place method comment before function"
		self emitJSHeaderOn: aStream generator: aCodeGen.
		parseTree emitJSCodeOn: aStream level: 1 generator: aCodeGen.
		aStream nextPutAll: '}'; cr]!

----- Method: JSMethod>>emitJSCommentOn: (in category 'JS code generation') -----
emitJSCommentOn: aStream
	"Emit the transferred Smalltalk comments as C comments."

	comment ifNotNil: [
		aStream cr;cr.
		1 to: comment size do: [:index | 
			aStream 
				nextPutAll: '/*'; tab;
				nextPutAll: (comment at: index);
				nextPutAll: ' */';
				cr]]!

----- Method: JSMethod>>emitJSFunctionHeader:generator: (in category 'JS code generation') -----
emitJSFunctionHeader: aStream generator: aCodeGen
	"Emit a C function header for this method onto the given stream."

	properties ifNotNil:
		[(properties at: #api: ifAbsent: []) ifNotNil:
			[:pragma|
			aStream nextPutAll: (pragma argumentAt: 1).
			^self]].
	self emitJSFunctionHeader: aStream generator: aCodeGen newlineBeforeName: false!

----- Method: JSMethod>>emitJSFunctionHeader:generator:newlineBeforeName: (in category 'JS code generation') -----
emitJSFunctionHeader: aStream generator: aCodeGen newlineBeforeName: newlineBeforeName "<Boolean>"
	"Emit a JS function header for this method onto the given stream."

	aStream nextPutAll: 'function'.
	newlineBeforeName ifTrue: [aStream cr] ifFalse: [aStream space].
	(returnType last = $)
	and: [returnType includesSubString: (aCodeGen cFunctionNameFor: self selectorForCodeGeneration)]) ifTrue:
		["Hack fix for e.g. <returnTypeC: 'void (*setInterruptCheckChain(void (*aFunction)(void)))()'>"
		 ^self].
	aStream
		nextPutAll: (aCodeGen cFunctionNameFor: self selectorForCodeGeneration);
		nextPut: $(.
	args
		do: [:arg | aStream nextPutAll: (aCodeGen returnPrefixFromVariable: arg)]
		separatedBy: [ aStream nextPutAll: ', ' ].
	aStream nextPut: $)!

----- Method: JSMethod>>emitJSHeaderOn:generator: (in category 'JS code generation') -----
emitJSHeaderOn: aStream generator: aCodeGen
	"Emit a C function header for this method onto the given stream."

	aStream cr. 
	self emitJSFunctionHeader: aStream generator: aCodeGen.
	aStream nextPutAll: ' {'; cr.
	self emitGlobalStructReferenceOn: aStream.
	locals do: [ :var |
		aStream nextPutAll: '	var ', (aCodeGen returnPrefixFromVariable: var), ';'; cr.
	].
	locals isEmpty ifFalse: [ aStream cr ].!

----- Method: JSMethod>>emitProxyFunctionPrototype:generator: (in category 'JS code generation') -----
emitProxyFunctionPrototype: aStream generator: aCodeGen
	"Emit an indirect C function header for this method onto the given stream."

	| arg |
	aStream nextPutAll: returnType; space.
	aStream nextPutAll: '(*', (aCodeGen cFunctionNameFor: self selectorForCodeGeneration), ')('.
	args isEmpty ifTrue: [ aStream nextPutAll: 'void' ].
	1 to: args size do: [ :i |
		arg := args at: i.
		(declarations includesKey: arg) ifTrue: [
			aStream nextPutAll: (declarations at: arg).
		] ifFalse: [
			aStream nextPutAll: 'sqInt ', (args at: i).
		].
		i < args size ifTrue: [ aStream nextPutAll: ', ' ].
	].
	aStream nextPutAll: ')'.!

----- Method: JSMethod>>endsWithReturn (in category 'inlining support') -----
endsWithReturn
	"Answer true if the last statement of this method is a return."

	^ parseTree statements last isReturn!

----- Method: JSMethod>>exitVar:label: (in category 'inlining') -----
exitVar: exitVar label: exitLabel
	"Replace each return statement in this method with an assignment to the exit variable followed by a goto to the given label. Return true if a goto was generated."
	"Optimization: If exitVar is nil, the return value of the inlined method is not being used, so don't add the assignment statement."

	| newStmts labelUsed |
	labelUsed := false.
	parseTree nodesDo: [ :node |
		node isStmtList ifTrue: [
			newStmts := OrderedCollection new: 100.
			node statements do: [ :stmt |
				(stmt isReturn) ifTrue: [
					exitVar = nil ifTrue: [
						stmt expression isLeaf ifFalse: [
							"evaluate return expression even though value isn't used"
							newStmts add: stmt expression.
						].
					] ifFalse: [
						"assign return expression to exit variable"
						newStmts add:
							(TAssignmentNode new
								setVariable: (TVariableNode new setName: exitVar)
								expression: stmt expression).
					].
					(stmt == parseTree statements last) ifFalse: [
						"generate a goto (this return is NOT the last statement in the method)"
						newStmts add: (TGoToNode new setLabel: exitLabel).
						labelUsed := true.
					].
				] ifFalse: [
					newStmts addLast: stmt.
				].
			].
			node setStatements: newStmts asArray.
		].
	].
	^labelUsed!

----- Method: JSMethod>>export (in category 'accessing') -----
export

	^ export
!

----- Method: JSMethod>>extractDirective:valueBlock:default: (in category 'transformations') -----
extractDirective: theSelector valueBlock: aBlock default: defaultResult
	"Find a pragma of the form:

		<theSelector[args]>

	 Answer the result of evaluating aBock with a TSendNode corresponding
	 to the pragma node, or defaultResult if there is no matching pragma."

	| result found newStatements |
	(properties at: theSelector ifAbsent: []) ifNotNil:
		[:pragma|
		^aBlock value: (TSendNode new
							setSelector: pragma keyword
							receiver: (TVariableNode new setName: 'self')
							arguments: (pragma arguments collect: [:const| TConstantNode new setValue: const]))].
	"Pre-pragma backward compatibility:
	 Scan the top-level statements for a labelling directive of the form:

		self theSelector[args]

	 and remove the directive from the method body if found.
	 Answer the result of evaluating aBock with the send node,
	  or defaultResult if there is no labelling directive."	result := defaultResult.
	found := false.
	newStatements := OrderedCollection new: parseTree statements size.
	parseTree statements do:
		[ :stmt |
		(stmt isSend
		 and: [stmt selector = theSelector])
			ifTrue:
				[found := true.
				 result := aBlock value: stmt]
			ifFalse:
				[newStatements add: stmt]].
	^found
		ifTrue:
			[parseTree setStatements: newStatements asArray.
			 result]
		ifFalse: [defaultResult]!

----- Method: JSMethod>>extractExpandCaseDirective (in category 'transformations') -----
extractExpandCaseDirective
	"Scan the top-level statements for an inlining directive of the form:
		self expandCases
	 and remove the directive from the method body. Answer whether
	 there was such a directive."

	^self
		extractDirective: #expandCases
		valueBlock: [:sendNode| true]
		default: false!

----- Method: JSMethod>>extractExportDirective (in category 'transformations') -----
extractExportDirective
	"Scan the top-level statements for an inlining directive of the form:

		self export: <boolean>

	 and remove the directive from the method body. Return the argument of the directive or false if there is no export directive."

	| result newStatements methodDirectiveFound |
	result := false.
	methodDirectiveFound := false.
	newStatements := OrderedCollection new: parseTree statements size.
	parseTree statements do: [ :stmt |
		(stmt isSend and: [stmt selector = #export:]) ifTrue: [
			methodDirectiveFound := true.
			result := stmt args first value = true.
		] ifFalse: [
			newStatements add: stmt.
		].
	].
	parseTree setStatements: newStatements asArray.
	methodDirectiveFound ifTrue: [^ result].
	"no method declaration was used, so check for a pragma declaration"
	^self
		extractDirective: #export:
		valueBlock: [:sendNode| sendNode args first value ~= false]
		default: false
!

----- Method: JSMethod>>extractInlineDirective (in category 'inlining support') -----
extractInlineDirective
	"Scan the top-level statements for an inlining directive of the form:

		self inline: <boolean>

	 and remove the directive from the method body. Return the argument of the directive or #dontCare if there is no inlining directive."

	| result newStatements methodDirectiveFound |
	sharedCase ifNotNil:[^false]. "don't auto-inline shared code; it gets handled specially"
	result := #dontCare.
	methodDirectiveFound := false.
	newStatements := OrderedCollection new: parseTree statements size.
	parseTree statements do: [ :stmt |
		(stmt isSend and: [stmt selector = #inline:]) ifTrue: [
			methodDirectiveFound := true.
			result := stmt args first value = true.
		] ifFalse: [
			newStatements add: stmt.
		].
	].
	parseTree setStatements: newStatements asArray.
	methodDirectiveFound ifTrue: [^ result].
	"no method declaration was used, so check for a pragma declaration"
	sharedCase ifNotNil: [^false]. "don't auto-inline shared code; it gets handled specially"
	^self
		extractDirective: #inline:
		valueBlock: [:sendNode| sendNode args first value = true]
		default: #dontCare!

----- Method: JSMethod>>extractLabelDirective (in category 'transformations') -----
extractLabelDirective
	"Scan the top-level statements for an inlining directive of the form:

		self asmLabel: <boolean>

	 and remove the directive from the method body. Answer the
	 argument of the directive or true if there is no export directive."

	^self
		extractDirective: #asmLabel:
		valueBlock: [:sendNode| sendNode args first value ~= false and: [mustAsmLabel := true. true]]
		default: true!

----- Method: JSMethod>>extractSharedCase (in category 'transformations') -----
extractSharedCase
	"Scan the top-level statements for an shared case directive of the form:

		self sharedCodeNamed: <sharedLabel> inCase: <sharedCase>.

	and remove the directive from the method body."

	| newStatements |
	newStatements := OrderedCollection new: parseTree statements size.
	parseTree statements do: [ :stmt |
		(stmt isSend and: [stmt selector = #sharedCodeNamed:inCase:]) ifTrue: [
			sharedLabel := stmt args first value.
			sharedCase := stmt args last value
		] ifFalse: [
			newStatements add: stmt.
		].
	].
	parseTree setStatements: newStatements asArray.
	sharedCase ifNotNil:[
		args isEmpty ifFalse:[self error: 'Cannot share code sections in methods with arguments'].
	].!

----- Method: JSMethod>>extractStaticDirective (in category 'transformations') -----
extractStaticDirective
	"Scan the top-level statements for an inlining directive of the form:

		self static: <boolean>

	and remove the directive from the method body. Answer the argument of the
	directive. If there is no static directive, answer true if this is an api method,
	otherwise answer nil for undefined. The code generator may determine the
	static declaration when undefined."

	^self
		extractDirective: #static:
		valueBlock: [:sendNode| sendNode args first value ~= false]
		default: (((properties includesKey: #api) or: [properties includesKey: #api:])
					ifTrue: [false] "api methods cannot be declared static"
					ifFalse: [nil]) "undefined, defer to the code generator for default"!

----- Method: JSMethod>>fetchRcvrExpr (in category 'primitive compilation') -----
fetchRcvrExpr
	"Return the parse tree for an expression that fetches the receiver from the stack."

	| expr |
	expr := 'rcvr := ', self vmNameString, ' stackValue: (', args size printString, ')'.
	^ self statementsFor: expr varName: ''
!

----- Method: JSMethod>>fixUpReturns:postlog: (in category 'primitive compilation') -----
fixUpReturns: argCount postlog: postlog
	"Replace each return statement in this method with (a) the given postlog, (b) code to pop the receiver and the given number of arguments, and (c) code to push the integer result and return."

	| newStmts |
	parseTree nodesDo: [:node |
		node isStmtList ifTrue: [
			newStmts := OrderedCollection new: 100.
			node statements do: [:stmt |
				stmt isReturn
					ifTrue: [
						(stmt expression isSend and:
						 ['primitiveFail' = stmt expression selector])
							ifTrue: [  "failure return"
								newStmts addLast: stmt expression.
								newStmts addLast: (TReturnNode new
									setExpression: (TVariableNode new setName: 'null'))]
							ifFalse: [  "normal return"
								newStmts addAll: postlog.
								newStmts addAll: (self popArgsExpr: argCount + 1).
								newStmts addLast: (TSendNode new
									setSelector: #pushInteger:
									receiver: (TVariableNode new setName: self vmNameString)
									arguments: (Array with: stmt expression)).
								newStmts addLast: (TReturnNode new
									setExpression: (TVariableNode new setName: 'null'))]]
					ifFalse: [
						newStmts addLast: stmt]].
			node setStatements: newStmts asArray]].
!

----- Method: JSMethod>>freeVariableReferences (in category 'utilities') -----
freeVariableReferences
	"Answer a collection of variables referenced this method, excluding locals, arguments, and pseudovariables."

	| refs |
	refs := Set new.
	parseTree nodesDo: [ :node |
		node isVariable ifTrue: [ refs add: node name asString ].
	].
	args do: [ :var | refs remove: var asString ifAbsent: [] ].
	locals do: [ :var | refs remove: var asString ifAbsent: [] ].
	#('self' 'nil' 'true' 'false') do: [ :var | refs remove: var ifAbsent: [] ].
	^ refs asSortedCollection!

----- Method: JSMethod>>globalStructureBuildMethodHasFoo (in category 'accessing') -----
globalStructureBuildMethodHasFoo
	^globalStructureBuildMethodHasFoo!

----- Method: JSMethod>>globalStructureBuildMethodHasFoo: (in category 'accessing') -----
globalStructureBuildMethodHasFoo: number
	globalStructureBuildMethodHasFoo := number!

----- Method: JSMethod>>hasDoNotGenerateStatement (in category 'inlining support') -----
hasDoNotGenerateStatement
	"True if method has a #doNotGenerate statement, equivalent to pragma <doNotGenerate>
	or if it has a #subclassResponsibility statement."
	parseTree statements
		detect: [:stmt | stmt isSend
					and: [stmt selector = #doNotGenerate
						or: [stmt selector = #subclassResponsibility]]]
		ifNone: [^ false].
	^ true!

----- Method: JSMethod>>hasNoCCode (in category 'utilities') -----
hasNoCCode
	"Answer true if the receiver does not use inlined C or C declarations, which are not currently renamed properly by the the inliner."

	declarations isEmpty ifFalse: [ ^ false ].

	parseTree nodesDo: [ :node |
		node isSend ifTrue: [
			node selector = #cCode: ifTrue: [ ^ false ].
		].
	].
	^ true!

----- Method: JSMethod>>hasReturn (in category 'testing') -----
hasReturn
	"Answer true if this method contains a return statement."

	parseTree nodesDo: [ :n | n isReturn ifTrue: [ ^ true ]].
	^ false!

----- Method: JSMethod>>inlineCaseStatementBranchesIn:localizingVars: (in category 'inlining') -----
inlineCaseStatementBranchesIn: aCodeGen localizingVars: varsList

	| stmt sel meth newStatements maxTemp usedVars exitLabel v |
	maxTemp := 0.
	parseTree nodesDo: [ :n |
		n isCaseStmt ifTrue: [
			n cases do: [ :stmtNode |
				stmt := stmtNode statements first.
				stmt isSend ifTrue: [
					sel := stmt selector.
					meth := aCodeGen methodNamed: sel.
					"Note, original version of this method tested for #hasNoCCode. Removed
					the test to permit inlining methods that may contain automatically
					generated C code for type conversions. -dtl"
					((meth ~= nil) and:
					 [meth args size = 0]) ifTrue: [
						meth := meth copy.
						meth hasReturn ifTrue: [
							exitLabel := self unusedLabelForInliningInto: self.
							meth exitVar: nil label: exitLabel.
							labels add: exitLabel.
						] ifFalse: [ exitLabel := nil ].

						meth renameLabelsForInliningInto: self.
						meth labels do: [ :label | labels add: label ].
						newStatements := stmtNode statements asOrderedCollection.
						newStatements removeFirst.

						exitLabel ~= nil ifTrue: [
							newStatements addFirst:
								(TLabeledCommentNode new
									setLabel: exitLabel comment: 'end case').
						].

						newStatements addFirst: meth asInlineNode.
						newStatements addFirst:
							(TLabeledCommentNode new setComment: meth selector).
						stmtNode setStatements: newStatements.
					].
				].
			].
		].
	].
	usedVars := (locals, args) asSet.
	1 to: maxTemp do: [ :i |
		v := ('t', i printString).
		(usedVars includes: v) ifTrue: [ self error: 'temp variable name conflicts with an existing local or arg' ].
		locals addLast: v.
	].

	"make local versions of the given globals"
	varsList do: [ :var |
		(usedVars includes: var) ifFalse: [ locals addFirst: var asString ].
	].
!

----- Method: JSMethod>>inlineCodeOrNilForStatement:in: (in category 'inlining') -----
inlineCodeOrNilForStatement: aNode in: aCodeGen
	"If the given statement node can be inlined, answer the statements that replace it. Otherwise, answer nil."

	| stmts |
	aNode isReturn ifTrue: [
		(self inlineableSend: aNode expression in: aCodeGen) ifTrue: [
			stmts := self inlineSend: aNode expression
				directReturn: true exitVar: nil in: aCodeGen.
			^stmts
		].
	].
	aNode isAssignment ifTrue: [
		(self inlineableSend: aNode expression in: aCodeGen) ifTrue: [
			^self inlineSend: aNode expression
				directReturn: false exitVar: aNode variable name in: aCodeGen
		].
	].
	aNode isSend ifTrue: [
		(self inlineableSend: aNode in: aCodeGen) ifTrue: [
			^self inlineSend: aNode
				directReturn: false exitVar: nil in: aCodeGen
		].
	].
	^nil!

----- Method: JSMethod>>inlineFunctionCall:in: (in category 'inlining') -----
inlineFunctionCall: aSendNode in: aCodeGen
	"Answer the body of the called function, substituting the actual parameters for the formal argument variables in the method body."
	"Assume caller has established that:
		1. the method arguments are all substitutable nodes, and
		2. the method to be inlined contains no additional embedded returns."

	| sel meth substitutionDict |
	sel := aSendNode selector.
	meth := (aCodeGen methodNamed: sel) copy.
	meth renameVarsForInliningInto: self in: aCodeGen.
	meth renameLabelsForInliningInto: self.
	self addVarsDeclarationsAndLabelsOf: meth.
	substitutionDict := Dictionary new: 100.
	meth args with: aSendNode args do: [ :argName :exprNode |
		substitutionDict at: argName put: exprNode.
		locals remove: argName.
		declarations removeKey: argName ifAbsent: []].
	meth parseTree bindVariablesIn: substitutionDict.
	^ meth statements first expression!

----- Method: JSMethod>>inlineSend:directReturn:exitVar:in: (in category 'inlining') -----
inlineSend: aSendNode directReturn: directReturn exitVar: exitVar in: aCodeGen
	"Answer a collection of statments to replace the given send. directReturn indicates that the send is the expression of a return statement, so returns can be left in the body of the inlined method. If exitVar is nil, the value returned by the send is not used; thus, returns need not assign to the output variable."

	| sel meth exitLabel labelUsed inlineStmts |
	sel := aSendNode selector.
	meth := (aCodeGen methodNamed: sel) copy.
	meth renameVarsForInliningInto: self in: aCodeGen.
	meth renameLabelsForInliningInto: self.
	self addVarsDeclarationsAndLabelsOf: meth.
	meth hasReturn ifTrue: [
		directReturn ifTrue: [
			"propagate the return type, if necessary"
			returnType = meth returnType ifFalse: [ self halt ].  "caller's return type should be declared by user"
			returnType := meth returnType.
		] ifFalse: [
			exitLabel := self unusedLabelForInliningInto: self.
			labelUsed := meth exitVar: exitVar label: exitLabel.
			labelUsed
				ifTrue: [ labels add: exitLabel ]
				ifFalse: [ exitLabel := nil ].
		].
		"propagate type info if necessary"
		((exitVar ~= nil) and: [meth returnType ~= 'sqInt']) ifTrue: [
			declarations at: exitVar put: meth returnType, ' ', exitVar.
		].
	].
	inlineStmts := OrderedCollection new: 100.
	inlineStmts add: (TLabeledCommentNode new setComment: 'begin ', sel).
	inlineStmts addAll:
		(self argAssignmentsFor: meth args: aSendNode args in: aCodeGen).
	inlineStmts addAll: meth statements.  "method body"
	(directReturn and: [meth endsWithReturn not]) ifTrue: [
		inlineStmts add: (TReturnNode new setExpression: (TVariableNode new setName: 'nil')).
	].
	exitLabel ~= nil ifTrue: [
		inlineStmts add:
			(TLabeledCommentNode new
				setLabel: exitLabel comment: 'end ', meth selector).
	].
	^inlineStmts!

----- Method: JSMethod>>inlineableFunctionCall:in: (in category 'inlining') -----
inlineableFunctionCall: aNode in: aCodeGen
	"Answer true if the given send node is a call to a 'functional' method--a method whose body is a single return statement of some expression and whose actual parameters can all be directly substituted."

	| m |
	aNode isSend ifFalse: [ ^false ].
	m := aCodeGen methodNamed: aNode selector.  "nil if builtin or external function"
	((m ~= nil) and: [m isFunctional and: [aCodeGen mayInline: m selector]]) ifTrue: [
		aNode args do: [ :a | (self isSubstitutableNode: a intoMethod: m in: aCodeGen) ifFalse: [ ^false ]].
		^true
	] ifFalse: [
		^false
	].!

----- Method: JSMethod>>inlineableSend:in: (in category 'inlining') -----
inlineableSend: aNode in: aCodeGen
	"Answer true if the given send node is a call to a method that can be inlined."

	| m |
	aNode isSend ifFalse: [ ^false ].
	m := aCodeGen methodNamed: aNode selector.  "nil if builtin or external function"
	^(m ~= nil) and: [m isComplete and: [aCodeGen mayInline: m selector]]!

----- Method: JSMethod>>instVarGetExprFor:offset: (in category 'primitive compilation') -----
instVarGetExprFor: varName offset: instIndex
	"Return the parse tree for an expression that fetches and converts the value of the instance variable at the given offset."

	| exprList decl stmtList |
	exprList := OrderedCollection new.
	(declarations includesKey: varName) ifTrue: [
		decl := declarations at: varName.
		(decl includes: $*) ifTrue: [  "array"
			exprList add:
				(varName, ' := ', self vmNameString, ' fetchArray: ', instIndex printString, ' ofObject: rcvr').
			exprList add: (varName, ' := ', varName, ' - 1').
		] ifFalse: [  "must be a double"
			((decl findString: 'double' startingAt: 1) = 0)
				ifTrue: [ self error: 'unsupported type declaration in a primitive method' ].
			exprList add:
				(varName, ' := ', self vmNameString, ' fetchFloat: ', instIndex printString, ' ofObject: rcvr').
		].
	] ifFalse: [  "undeclared variables are taken to be integer"
		exprList add:
			(varName, ' := ', self vmNameString, ' fetchInteger: ', instIndex printString, ' ofObject: rcvr').
	].
	stmtList := OrderedCollection new.
	exprList do: [:e | stmtList addAll: (self statementsFor: e varName: varName)].
	^ stmtList
!

----- Method: JSMethod>>instVarPutExprFor:offset: (in category 'primitive compilation') -----
instVarPutExprFor: varName offset: instIndex
	"Return the parse tree for an expression that saves the value of the integer instance variable at the given offset."

	| expr |
	(declarations includesKey: varName) ifTrue: [
		self error: 'a primitive method can only modify integer instance variables'.
	].
	expr := '', self vmNameString, ' storeInteger: ', instIndex printString, ' ofObject: rcvr withValue: ', varName.
	^ self statementsFor: expr varName: varName
!

----- Method: JSMethod>>isAssertion (in category 'testing') -----
isAssertion
	^(selector beginsWith: 'assert') or: [selector beginsWith: 'verify']!

----- Method: JSMethod>>isComplete (in category 'accessing') -----
isComplete
	"A method is 'complete' if it does not contain any more inline-able calls."

	^complete!

----- Method: JSMethod>>isFunctional (in category 'inlining') -----
isFunctional
	"Answer true if the receiver is a functional method. That is, if it consists of a single return statement of an expression that contains no other returns."

	(parseTree statements size = 1 and:
	 [parseTree statements last isReturn]) ifFalse: [ ^false ].
	parseTree statements last expression nodesDo: [ :n | n isReturn ifTrue: [ ^false ]].
	^true!

----- Method: JSMethod>>isStaticIn: (in category 'accessing') -----
isStaticIn: aCodeGen
	"If static has been explicitly set, honor that setting. Otherwise defer
	to the code generator for a default setting."
	^static ifNil: [aCodeGen declareMethodsStatic]!

----- Method: JSMethod>>isSubstitutableNode: (in category 'inlining') -----
isSubstitutableNode: aNode
	"Answer true if the given parameter node is either a constant, a local variable, or a formal parameter of the receiver. Such parameter nodes may be substituted directly into the body of the method during inlining. Note that global variables cannot be subsituted because the inlined method might depend on the exact ordering of side effects to the globals."

	aNode isConstant ifTrue: [ ^true ].
	^aNode isVariable and:
		[(locals includes: aNode name) or:
		[args includes: aNode name]]!

----- Method: JSMethod>>isSubstitutableNode:intoMethod:in: (in category 'inlining') -----
isSubstitutableNode: aNode intoMethod: targetMeth in: aCodeGen
	"Answer true if the given parameter node is either a constant, a local variable, or a formal parameter of the receiver. Such parameter nodes may be substituted directly into the body of the method during inlining. Note that global variables cannot be subsituted into methods with possible side effects (i.e., methods that may assign to global variables) because the inlined method might depend on having the value of the global variable captured when it is passed in as an argument."

	| var |
	aNode isConstant ifTrue: [ ^ true ].

	aNode isVariable ifTrue: [
		var := aNode name.
		((locals includes: var) or: [args includes: var]) ifTrue: [ ^ true ].
		(#(self true false nil) includes: var) ifTrue: [ ^ true ].
		(targetMeth maySubstituteGlobal: var in: aCodeGen) ifTrue: [ ^ true ].
	].

	"scan expression tree; must contain only constants, builtin ops, and inlineable vars"
	aNode nodesDo: [ :node |
		node isSend ifTrue: [
			node isBuiltinOperator ifFalse: [ ^false ].
		].
		node isVariable ifTrue: [
			var := node name.
			((locals includes: var) or:
			 [(args includes: var) or:
			 [(#(self true false nil) includes: var) or:
			 [targetMeth maySubstituteGlobal: var in: aCodeGen]]]) ifFalse: [ ^ false ].
		].
		(node isConstant or: [node isVariable or: [node isSend]]) ifFalse: [ ^false ].
	].

	^ true!

----- Method: JSMethod>>labels (in category 'accessing') -----
labels

	^labels!

----- Method: JSMethod>>locals (in category 'accessing') -----
locals
	"The local variables of this method."

	^locals!

----- Method: JSMethod>>mapReceiversIn: (in category 'transformations') -----
mapReceiversIn: aDictionary
	parseTree mapReceiversIn: aDictionary.!

----- Method: JSMethod>>maySubstituteGlobal:in: (in category 'inlining support') -----
maySubstituteGlobal: globalVar in: aCodeGen
	"Answer true if this method does or may have side effects on the given global variable."

	possibleSideEffectsCache = nil ifTrue: [
		"see if this calls any other method and record the result"
		possibleSideEffectsCache := self computePossibleSideEffectsIn: aCodeGen.
	].
	possibleSideEffectsCache ifTrue: [ ^ false ].

	parseTree nodesDo: [ :node |
		node isAssignment ifTrue: [
			node variable name = globalVar ifTrue: [ ^ false ].
		].
	].

	"if we get here, receiver calls no other method
	 and does not itself assign to the given global variable"
	^ true!

----- Method: JSMethod>>newCascadeTempFor: (in category 'initialization') -----
newCascadeTempFor: aTParseNode
	| varNode |
	cascadeVariableNumber := cascadeVariableNumber
								ifNil: [0]
								ifNotNil: [cascadeVariableNumber + 1].
	varNode := TVariableNode new setName: 'cascade', cascadeVariableNumber printString.
	aTParseNode isLeaf ifFalse:
		[declarations
			at: varNode name
			put: [:cg| self determineTypeFor: aTParseNode in: cg]].
	^varNode!

----- Method: JSMethod>>nodeCount (in category 'utilities') -----
nodeCount
	"Answer the number of nodes in this method's parseTree (a rough measure of its size)."

	| cnt |
	cnt := 0.
	parseTree nodesDo: [ :n | cnt := cnt + 1 ].
	^cnt!

----- Method: JSMethod>>parseTree (in category 'accessing') -----
parseTree
	"The parse tree of this method."

	^parseTree!

----- Method: JSMethod>>parseTree: (in category 'accessing') -----
parseTree: aNode
	"Set the parse tree of this method."

	parseTree := aNode.!

----- Method: JSMethod>>popArgsExpr: (in category 'primitive compilation') -----
popArgsExpr: argCount
	"Return the parse tree for an expression that pops the given number of arguments from the stack."

	| expr |
	expr := '', self vmNameString, ' pop: ', argCount printString.
	^ self statementsFor: expr varName: ''
!

----- Method: JSMethod>>prepareMethodIn: (in category 'transformations') -----
prepareMethodIn: aCodeGen
	"Record sends of builtin operators and replace sends of the special selector dispatchOn:in: with case statement nodes."
	"Note: Only replaces top-level sends of dispatchOn:in:. Case statements must be top-level statements; they cannot appear in expressions."

	| stmts stmt |
	parseTree nodesDo: [ :node |
		node isSend ifTrue: [
			"record sends of builtin operators"
			(aCodeGen builtin: node selector) ifTrue: [ node isBuiltinOperator: true ].
		].
		node isStmtList ifTrue: [
			"replace dispatchOn:in: with case statement node"
			stmts := node statements.
			1 to: stmts size do: [ :i |
				stmt := stmts at: i.
				(stmt isSend and: [CaseStatements includes: stmt selector]) ifTrue: [
					stmts at: i put: (self buildCaseStmt: stmt).
				].
			].
		].
	].!

----- Method: JSMethod>>preparePrimitiveName (in category 'primitive compilation') -----
preparePrimitiveName
	"Prepare the selector for this method in translation"
	| aClass |
	aClass := definingClass.
	primitive = 117 
		ifTrue:[selector := ((aClass includesSelector: selector)
					ifTrue: [aClass compiledMethodAt: selector]
					ifFalse: [aClass class compiledMethodAt: selector]) literals first at: 2.
				export := true]
		ifFalse:[selector := 'prim', aClass name, selector].

!

----- Method: JSMethod>>preparePrimitivePrologue (in category 'primitive compilation') -----
preparePrimitivePrologue
	"Add a prolog and postlog to a primitive method. The prolog copies any instance variables referenced by this primitive method into local variables. The postlog copies values of assigned-to variables back into the instance. The names of the new locals are added to the local variables list.

The declarations dictionary defines the types of any non-integer variables (locals, arguments, or instance variables). In particular, it may specify the types:

	int *		-- an array of 32-bit values (e.g., a BitMap)
	short *		-- an array of 16-bit values (e.g., a SoundBuffer)
	char *		-- an array of unsigned bytes (e.g., a String)
	double		-- a double precision floating point number (e.g., 3.14159)

Undeclared variables are taken to be integers and will be converted from Smalltalk to C ints."

"Current restrictions:
	o method must not contain message sends
	o method must not allocate objects
	o method must not manipulate raw oops
	o method cannot access class variables
	o method can only return an integer"

	| prolog postlog instVarsUsed varsAssignedTo instVarList primArgCount varName endsWithReturn aClass |
selector == #setInterpreter: ifTrue:[self halt].
	aClass := definingClass.
	prolog := OrderedCollection new.
	postlog := OrderedCollection new.
	instVarsUsed := self freeVariableReferences asSet.
	varsAssignedTo := self variablesAssignedTo asSet.
	instVarList := aClass allInstVarNames.
	primArgCount := args size.

	"add receiver fetch and arg conversions to prolog"
	prolog addAll: self fetchRcvrExpr.
	1 to: args size do: [:argIndex |
		varName := args at: argIndex.
		prolog addAll:
			(self argConversionExprFor: varName stackIndex: args size - argIndex)].

	"add success check to postlog"
	postlog addAll: self checkSuccessExpr.

	"add instance variable fetches to prolog and instance variable stores to postlog"
	1 to: instVarList size do: [:varIndex |
		varName := instVarList at: varIndex.
		(instVarsUsed includes: varName) ifTrue: [
			locals add: varName.
			prolog addAll: (self instVarGetExprFor: varName offset: varIndex - 1).
			(varsAssignedTo includes: varName) ifTrue: [
				postlog addAll: (self instVarPutExprFor: varName offset: varIndex - 1)]]].
	prolog addAll: self checkSuccessExpr.

	locals addAllFirst: args.
	locals addFirst: 'rcvr'.
	args := args class new.
	locals asSet size = locals size
		ifFalse: [self error: 'local name conflicts with instance variable name'].
	endsWithReturn := self endsWithReturn.
	self fixUpReturns: primArgCount postlog: postlog.

	endsWithReturn
		ifTrue: [parseTree setStatements: prolog, parseTree statements]
		ifFalse: [
			postlog addAll: (self popArgsExpr: primArgCount).
			parseTree setStatements: prolog, parseTree statements, postlog].
!

----- Method: JSMethod>>primitive (in category 'accessing') -----
primitive
	"The primitive number of this method; zero if not a primitive."

	^ primitive
!

----- Method: JSMethod>>printOn: (in category 'printing') -----
printOn: aStream

	super printOn: aStream.
	aStream nextPutAll: ' (', selector, ')'.!

----- Method: JSMethod>>printTempsAndVar:on: (in category 'private') -----
printTempsAndVar: varName on: aStream 
	"add the required temps and the varname to the stream"
	aStream nextPutAll: '| rcvr stackPointer successFlag ' , varName , ' |';
	 cr!

----- Method: JSMethod>>recordDeclarations (in category 'transformations') -----
recordDeclarations
	"Record C type declarations of the forms

		self returnTypeC: 'float'.
		self var: #foo declareC: 'float foo'
		self var: #foo type:'float'.

	 and remove the declarations from the method body."

	| newStatements |
	properties pragmas notEmpty ifTrue:
		[properties pragmas do:
			[:pragma|
			pragma keyword = #var:declareC: ifTrue:
				[self declarationAt: pragma arguments first asString put: pragma arguments last].
			pragma keyword = #var:type: ifTrue:
				[| varName varType |
				varName := pragma arguments first asString.
				varType := pragma arguments last.
				varType last = $* ifFalse: [varType := varType, ' '].
				self declarationAt: varName put: varType, varName].
			pragma keyword = #returnTypeC: ifTrue:
				[returnType := pragma arguments last].
			pragma keyword = #doNotGenerate: ifTrue:
				[locals remove: pragma arguments last]]].
	newStatements := OrderedCollection new: parseTree statements size.
	parseTree statements do: [ :stmt |
		| isDeclaration |
		isDeclaration := false.
		stmt isSend ifTrue: [
			stmt selector = #var:declareC: ifTrue: [
				isDeclaration := true.
				self declarationAt: stmt args first value asString put: stmt args last value.
			].
			stmt selector = #var:type: ifTrue: [
				| varName varType |
				isDeclaration := true.
				varName := stmt args first value asString.
				varType := stmt args last value.
				varType last = $* ifFalse: [varType := varType, ' '].
				self declarationAt: varName put: varType, varName.
			].
			stmt selector = #returnTypeC: ifTrue: [
				isDeclaration := true.
				returnType := stmt args last value.
			].
		].
		isDeclaration ifFalse: [
			newStatements add: stmt.
		].
	].
	parseTree setStatements: newStatements asArray.!

----- Method: JSMethod>>referencesGlobalStructIncrementBy: (in category 'accessing') -----
referencesGlobalStructIncrementBy: value
	globalStructureBuildMethodHasFoo := globalStructureBuildMethodHasFoo + value.!

----- Method: JSMethod>>referencesGlobalStructMakeZero (in category 'accessing') -----
referencesGlobalStructMakeZero
	globalStructureBuildMethodHasFoo := 0!

----- Method: JSMethod>>removeAssertions (in category 'transformations') -----
removeAssertions
	parseTree removeAssertions!

----- Method: JSMethod>>removeFinalSelfReturn (in category 'transformations') -----
removeFinalSelfReturn
	"The Smalltalk parser automatically adds the statement '^self' to the end of methods without explicit returns. This method removes such statements, since the generated code has no notion of 'self' anyway."

	| stmtList lastStmt |
	stmtList := parseTree statements asOrderedCollection.
	lastStmt := stmtList last.

	((lastStmt isReturn) and:
	 [(lastStmt expression isVariable) and:
	 ['self' = lastStmt expression name]]) ifTrue: [
		stmtList removeLast.
		parseTree setStatements: stmtList.
	].!

----- Method: JSMethod>>removeUnusedTemps (in category 'utilities') -----
removeUnusedTemps
	"Remove all of the unused temps in this method. Answer a bag (why the hell a bag???) with the references."
	"After inlining some variable references are now obsolete, we could fix them there but the 
	code seems a bit complicated, the other choice to to rebuild the locals before extruding. This is done here"
	| refs |
	refs := Bag new.
	"find all the variable names referenced in this method"
	parseTree nodesDo: [ :node |
		node isVariable ifTrue: [ refs add: node name asString ].
		node isStmtList ifTrue: [refs addAll: node args]].
	"add all the non-arg declarations (might be variables usedonly in cCode sections)"
	refs addAll:((self declarations keys) reject: [:e | self args includes: e]).
	"reset the locals to be only those still referred to"
	locals := locals select: [:e | refs includes: e].
	^refs
!

----- Method: JSMethod>>renameLabelsForInliningInto: (in category 'inlining support') -----
renameLabelsForInliningInto: destMethod
	"Rename any labels that would clash with those of the destination method."

	| destLabels usedLabels labelMap newLabelName |
	destLabels := destMethod labels asSet.
	usedLabels := destLabels copy.  "usedLabels keeps track of labels in use"
	usedLabels addAll: labels.
	labelMap := Dictionary new: 100.
	self labels do: [ :l |
		(destLabels includes: l) ifTrue: [
			newLabelName := self unusedNamePrefixedBy: 'l' avoiding: usedLabels.
			labelMap at: l put: newLabelName.
		].
	].
	self renameLabelsUsing: labelMap.!

----- Method: JSMethod>>renameLabelsUsing: (in category 'inlining support') -----
renameLabelsUsing: aDictionary
	"Rename all labels according to the old->new mappings of the given dictionary."

	labels := labels collect: [ :label |
		(aDictionary includesKey: label) ifTrue: [ aDictionary at: label ] ifFalse: [ label ].
	].

	parseTree nodesDo: [ :node |
		(node isGoTo and: [aDictionary includesKey: node label]) ifTrue: [
			node setLabel: (aDictionary at: node label).
		].
		(node isLabel and: [aDictionary includesKey: node label]) ifTrue: [
			node setLabel: (aDictionary at: node label).
		].
	].!

----- Method: JSMethod>>renameSelector:as: (in category 'transformations') -----
renameSelector: selectorName as: newSelectorName
	"Rename selectors such that generated code will use the newSelectorName. This
	is intended to allow methods that may have default implementations in the support
	code to be renamed for code generation, such that the renamed versions will
	be referenced rather than the default platform implementations. For example,
	if #pointerForOop: is implemented in Smalltalk, it may be renamed such that
	the generated pointerForOop() function will be renamed to avoid conflict with
	the standard definitions provided in sqMemoryAccess.h."

	selector = selectorName
		ifTrue: [selector := newSelectorName].
	parseTree nodesDo: [:node |
			node
				renameSelector: selectorName
				as: newSelectorName ]
!

----- Method: JSMethod>>renameVariablesUsing: (in category 'inlining support') -----
renameVariablesUsing: aDictionary
	"Rename all variables according to old->new mappings of the given dictionary."

	| newDecls newKey newValue |
	"map args and locals"
	args := args collect: [ :arg |
		(aDictionary includesKey: arg) ifTrue: [ aDictionary at: arg ] ifFalse: [ arg ].
	].
	locals := locals collect: [ :v |
		(aDictionary includesKey: v) ifTrue: [ aDictionary at: v ] ifFalse: [ v ].
	].
	"prevent runaway recursion, e.g. inlining a method with super send"
	locals size > 1000 ifTrue: [self error: 'recursive inlining in ', selector asString, ', too many locals'].

	"map declarations"
	newDecls := declarations species new.
	declarations associationsDo: [ :assoc |
		(aDictionary includesKey: assoc key)
			ifTrue: [ newKey := aDictionary at: assoc key.
					newValue := assoc value replaceLastOccurrence: assoc key with: newKey.
					newDecls at: newKey put: newValue]
			ifFalse: [ newDecls add: assoc ].
	].
	declarations := newDecls.

	"map variable names in parse tree"
	parseTree nodesDo: [ :node |
		(node isVariable and:
		 [aDictionary includesKey: node name]) ifTrue: [
			node setName: (aDictionary at: node name).
		].
		(node isStmtList and: [node args size > 0]) ifTrue: [
			node setArguments:
				(node args collect: [ :arg |
					(aDictionary includesKey: arg)
						ifTrue: [ aDictionary at: arg ]
						ifFalse: [ arg ].
				]).
		].
	].!

----- Method: JSMethod>>renameVarsForCaseStmt (in category 'inlining support') -----
renameVarsForCaseStmt
	"Rename the arguments and locals of this method with names like t1, t2, t3, etc. Return the number of variable names assigned. This is done to allow registers to be shared among the cases."

	| i varMap |
	i := 1.
	varMap := Dictionary new: 100.
	args, locals do: [ :v |
		varMap at: v put: ('t', i printString) asSymbol.
		i := i + 1.
	].
	self renameVariablesUsing: varMap.
	^ i - 1!

----- Method: JSMethod>>renameVarsForInliningInto:in: (in category 'inlining support') -----
renameVarsForInliningInto: destMethod in: aCodeGen
	"Rename any variables that would clash with those of the destination method."

	| destVars usedVars varMap newVarName |
	destVars := aCodeGen globalsAsSet copy.
	destVars addAll: destMethod locals.
	destVars addAll: destMethod args.
	usedVars := destVars copy.  "keeps track of names in use"
	usedVars addAll: args; addAll: locals.
	varMap := Dictionary new: 100.
	args, locals do: [ :v |
		(destVars includes: v) ifTrue: [
			newVarName := self unusedNamePrefixedBy: v avoiding: usedVars.
			varMap at: v put: newVarName.
		].
	].
	self renameVariablesUsing: varMap.!

----- Method: JSMethod>>replaceNodesIn: (in category 'transformations') -----
replaceNodesIn: map
	parseTree := parseTree replaceNodesIn: map.!

----- Method: JSMethod>>replaceSizeMessages (in category 'primitive compilation') -----
replaceSizeMessages
	"Replace sends of the message 'size' with calls to sizeOfSTArrayFromCPrimitive."

	| argExpr |
	parseTree nodesDo: [:n |
		(n isSend and: [n selector = #size]) ifTrue: [
			argExpr := TSendNode new
				setSelector: #+
				receiver: n receiver
				arguments: (Array with: (TConstantNode new setValue: 1)).
			n
				setSelector: #sizeOfSTArrayFromCPrimitive:
				receiver: (TVariableNode new setName: self vmNameString)
				arguments: (Array with: argExpr)]].
!

----- Method: JSMethod>>returnType (in category 'accessing') -----
returnType
	"The type of the values returned by this method. This string will be used in the C declaration of this function."

	^returnType!

----- Method: JSMethod>>returnType: (in category 'accessing') -----
returnType: aString
	"Set the type of the values returned by this method. This string will be used in the C declaration of this function."

	returnType := aString!

----- Method: JSMethod>>selector (in category 'accessing') -----
selector
	"The Smalltalk selector of this method."

	^selector!

----- Method: JSMethod>>selector: (in category 'accessing') -----
selector: newSelector

	selector := newSelector.!

----- Method: JSMethod>>selectorForCodeGeneration (in category 'accessing') -----
selectorForCodeGeneration
	"Subclasses may allow a directive to override the selector specification."

	^ selector!

----- Method: JSMethod>>setSelector:definingClass:args:locals:block:primitive:properties:comment: (in category 'initialization') -----
setSelector: sel definingClass: class args: argList locals: localList block: aBlockNode primitive: aNumber properties: methodProperties comment: aComment
	"Initialize this method using the given information."

	selector := sel.
	definingClass := class.
	returnType := #sqInt. 	 "assume return type is long for now"
	args := argList asOrderedCollection collect: [:arg | arg key].
	locals := (localList asSortedCollection: [:a :b| a key < b key]) collect: [:arg | arg key].
	declarations := Dictionary new.
	"self addTypeForSelf." "<- Cog feature to be added later"
	primitive := aNumber.
	properties := methodProperties.
	comment := aComment.
	parseTree := aBlockNode asTranslatorNodeIn: self.
	labels := OrderedCollection new.
	complete := false.  "set to true when all possible inlining has been done"
	export := self extractExportDirective.
	static := self extractStaticDirective.
	canAsmLabel := self extractLabelDirective.
	self extractSharedCase.
	self removeFinalSelfReturn.	"must preceed recordDeclarations because this may set returnType"
	self recordDeclarations.
	globalStructureBuildMethodHasFoo := 0!

----- Method: JSMethod>>setSelector:returnType:args:locals:declarations:primitive:parseTree:labels:complete: (in category 'initialization') -----
setSelector: sel returnType: retType args: argList locals: localList declarations: decls primitive: primNumber parseTree: aNode labels: labelList complete: completeFlag
	"Initialize this method using the given information. Used for copying."

	selector := sel.
	returnType := retType.
	args := argList.
	locals := localList.
	declarations := decls.
	primitive := primNumber.
	parseTree := aNode.
	labels := labelList.
	complete := completeFlag.!

----- Method: JSMethod>>sharedCase (in category 'accessing') -----
sharedCase
	^sharedCase!

----- Method: JSMethod>>sharedCase: (in category 'accessing') -----
sharedCase: aNumber
	sharedCase := aNumber.!

----- Method: JSMethod>>sharedLabel (in category 'accessing') -----
sharedLabel
	^sharedLabel!

----- Method: JSMethod>>sharedLabel: (in category 'accessing') -----
sharedLabel: aString
	sharedLabel := aString!

----- Method: JSMethod>>statements (in category 'accessing') -----
statements

	parseTree isStmtList
		ifFalse: [ self error: 'expected method parse tree to be a TStmtListNode' ].
	((parseTree args = nil) or: [parseTree args isEmpty])
		ifFalse: [ self error: 'expected method parse tree to have no args' ].

	^parseTree statements!

----- Method: JSMethod>>statementsFor:varName: (in category 'primitive compilation') -----
statementsFor: sourceText varName: varName
	"Return the parse tree for the given expression. The result is the statements list of the method parsed from the given source text."
	"Details: Various variables are declared as locals to avoid Undeclared warnings from the parser."

	| s |
	s := WriteStream on: ''.
	s nextPutAll: 'temp'; cr; cr; tab.
	self printTempsAndVar: varName on: s.
	s nextPutAll: sourceText.
	^ ((Compiler new parse: s contents in: Object notifying: nil)
			asTranslationMethodOfClass: self class) statements
!

----- Method: JSMethod>>statementsListsForInlining (in category 'inlining') -----
statementsListsForInlining
	"Answer a collection of statement list nodes that are candidates for inlining. Currently, we cannot inline into the argument blocks of and: and or: messages."

	| stmtLists |
	stmtLists := OrderedCollection new: 10.
	parseTree nodesDo: [ :node | 
		node isStmtList ifTrue: [ stmtLists add: node ].
	].
	parseTree nodesDo: [ :node | 
		node isSend ifTrue: [
			((node selector = #and:) or: [node selector = #or:]) ifTrue: [
				"Note: the PP 2.3 compiler produces two arg nodes for these selectors"
				stmtLists remove: node args first ifAbsent: [].
				stmtLists remove: node args last ifAbsent: [].
			].
			((node selector = #ifTrue:) or: [node selector = #ifFalse:]) ifTrue: [
				stmtLists remove: node receiver ifAbsent: [].
			].
			((node selector = #ifTrue:ifFalse:) or: [node selector = #ifFalse:ifTrue:]) ifTrue: [
				stmtLists remove: node receiver ifAbsent: [].
			].
			((node selector = #whileFalse:) or: [node selector = #whileTrue:]) ifTrue: [
				"Allow inlining if it is a [...] whileTrue/whileFalse.
				This is identified by having more than one statement in the 
				receiver block in which case the C code wouldn't work anyways"
				node receiver statements size = 1
					ifTrue:[stmtLists remove: node receiver ifAbsent: []].
			].
			(node selector = #to:do:) ifTrue: [
				stmtLists remove: node receiver ifAbsent: [].
				stmtLists remove: node args first ifAbsent: [].
			].
			(node selector = #to:by:do:) ifTrue: [
				stmtLists remove: node receiver ifAbsent: [].
				stmtLists remove: node args first ifAbsent: [].
				stmtLists remove: node args second ifAbsent: [].
			].
		].
		node isCaseStmt ifTrue: [
			"don't inline cases"
			node cases do: [: case | stmtLists remove: case ifAbsent: [] ].
		].
	].
	^stmtLists!

----- Method: JSMethod>>static: (in category 'accessing') -----
static: aBoolean
	static := aBoolean!

----- Method: JSMethod>>tryToInlineMethodsIn: (in category 'inlining') -----
tryToInlineMethodsIn: aCodeGen
	"Expand any (complete) inline methods called by this method. Set the complete bit when all inlining has been done. Return true if something was inlined."

	| stmtLists didSomething newStatements inlinedStmts sendsToInline |
	didSomething := false.

	sendsToInline := Dictionary new: 100.
	parseTree nodesDo: [ :n |
		(self inlineableFunctionCall: n in: aCodeGen) ifTrue: [
			sendsToInline at: n put: (self inlineFunctionCall: n in: aCodeGen).
		].
	].
	sendsToInline isEmpty ifFalse: [
		didSomething := true.
		parseTree := parseTree replaceNodesIn: sendsToInline.
	].

	didSomething ifTrue: [
		possibleSideEffectsCache := nil.
		^didSomething
	].

	stmtLists := self statementsListsForInlining.
	stmtLists do: [ :stmtList | 
		newStatements := OrderedCollection new: 100.
		stmtList statements do: [ :stmt |
			inlinedStmts := self inlineCodeOrNilForStatement: stmt in: aCodeGen.
			(inlinedStmts = nil) ifTrue: [
				newStatements addLast: stmt.
			] ifFalse: [
				didSomething := true.
				newStatements addAllLast: inlinedStmts.
			].
		].
		stmtList setStatements: newStatements asArray.
	].

	didSomething ifTrue: [
		possibleSideEffectsCache := nil.
		^didSomething
	].

	complete ifFalse: [
		self checkForCompleteness: stmtLists in: aCodeGen.
		complete ifTrue: [ didSomething := true ].  "marking a method complete is progress"
	].
	^didSomething!

----- Method: JSMethod>>unusedLabelForInliningInto: (in category 'inlining') -----
unusedLabelForInliningInto: targetMethod

	| usedLabels |
	usedLabels := labels asSet.
	usedLabels addAll: targetMethod labels.
	^self unusedNamePrefixedBy: 'l' avoiding: usedLabels!

----- Method: JSMethod>>unusedNamePrefixedBy:avoiding: (in category 'inlining support') -----
unusedNamePrefixedBy: aString avoiding: usedNames
	"Choose a unique variable or label name with the given string as a prefix, avoiding the names in the given collection. The selected name is added to usedNames."

	| n newVarName |
	n := 1.
	newVarName := aString, n printString.
	[usedNames includes: newVarName] whileTrue: [
		n := n + 1.
		newVarName := aString, n printString.
	].
	usedNames add: newVarName.
	^ newVarName!

----- Method: JSMethod>>variablesAssignedTo (in category 'utilities') -----
variablesAssignedTo
	"Answer a collection of variables assigned to by this method."

	| refs |
	refs := Set new.
	parseTree nodesDo: [ :node |
		node isAssignment ifTrue: [ refs add: node variable name ].
	].
	^ refs!

----- Method: JSMethod>>vmNameString (in category 'primitive compilation') -----
vmNameString
	"return the string to use as the vm name in code generated for this method"
	^'self'!

JSMethod subclass: #JSSmartSyntaxPluginMethod
	instanceVariableNames: 'isPrimitive suppressingFailureGuards selectorOverride fullArgs parmSpecs rcvrSpec'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMakerJS-SmartSyntaxPlugins'!

!JSSmartSyntaxPluginMethod commentStamp: 'bf 10/3/2014 04:18' prior: 0!
Variation of JSMethod node of the Smalltalk JS Code Generator, used in conjunction with SmartSyntaxCodeGenerator and SmartSyntaxInterpreterPlugin to generate named primitives with type coercion specifications.!

----- Method: JSSmartSyntaxPluginMethod class>>fromContext:primitive:parameters:receiver: (in category 'as yet unclassified') -----
fromContext: aContext primitive: aString parameters: aClassList receiver: aClass

	^super new 
		fromContext: aContext 
		primitive: aString 
		parameters: aClassList 
		receiver: aClass
!

----- Method: JSSmartSyntaxPluginMethod>>args: (in category 'accessing') -----
args: anInteger

	^args := anInteger!

----- Method: JSSmartSyntaxPluginMethod>>assign:expression: (in category 'private') -----
assign: variable expression: expression

	^TAssignmentNode new
		setVariable: variable
		expression: expression!

----- Method: JSSmartSyntaxPluginMethod>>checkSuccessExpr (in category 'private') -----
checkSuccessExpr
	"Return the parse tree for an expression that aborts the primitive if primFailCode is set."

	| expr |
	expr := 'interpreterProxy failed ifTrue: [^nil]'.
	^ self statementsFor: expr varName: ''
!

----- Method: JSSmartSyntaxPluginMethod>>emitJSHeaderOn:generator: (in category 'generating JS code') -----
emitJSHeaderOn: aStream generator: aCodeGen
	"Emit a C function header for this method onto the given stream."

	aStream cr. 
	self emitJSFunctionHeader: aStream generator: aCodeGen.
	aStream nextPutAll: ' {'; cr.
	locals do: [ :var |
		aStream nextPutAll: '	var ', (aCodeGen returnPrefixFromVariable: var), ';'; cr.
	].
	locals isEmpty ifFalse: [ aStream cr ].!

----- Method: JSSmartSyntaxPluginMethod>>extractPrimitiveDirectives (in category 'specifying primitives') -----
extractPrimitiveDirectives
	"Set selectorOverride, and save args in fullArgs.  Scan top-level statements for a directive of the form:

		self	
			primitive: 	<string>
or
		self
			primitive:	<string>
			parameters: <list of class names>
or
		self
			primitive:	<string>
			parameters: <list of class names>
			receiver: <class name>

or an assignment of that expression to a local, and manipulate the state and parse tree accordingly."

	parseTree setStatements: (Array streamContents:
		[:sStream |
			parseTree statements do:
				[:stmt |
				 (self primitiveDirectiveWasHandled: stmt on: sStream)
					ifFalse: [sStream nextPut: stmt]]]).
	isPrimitive 
		ifTrue:
			[export := true.
			 parseTree 
				setStatements: self namedPrimitiveProlog, 
								parseTree statements.
			 self fixUpReturns.
			 self replaceSizeMessages.
			 ^true]
		ifFalse: [self removeFinalSelfReturn].
	^false!

----- Method: JSSmartSyntaxPluginMethod>>extractSuppressFailureGuardDirective (in category 'transforming') -----
extractSuppressFailureGuardDirective
	"Scan the top-level statements for a pragma directive of the form:

		self suppressFailureGuards: <boolean>

	 and remove the directive from the method body. Answer the argument of the directive or false if there is no #supressFailureGuards: directive."

	| result newStatements |
	result := false.
	newStatements := OrderedCollection new: parseTree statements size.
	parseTree statements do: [ :stmt |
		(stmt isSend and: [stmt selector = #suppressFailureGuards:]) ifTrue: [
			result := stmt args first name = 'true'.
		] ifFalse: [
			newStatements add: stmt.
		].
	].
	parseTree setStatements: newStatements asArray.
	^ result!

----- Method: JSSmartSyntaxPluginMethod>>fixUpReturnOneStmt:on: (in category 'transforming') -----
fixUpReturnOneStmt: stmt on: sStream

	stmt isReturn ifFalse: [^sStream nextPut: stmt].
	(stmt expression isSend and: ['primitiveFail' = stmt expression selector]) ifTrue: 
		["failure return"
		 sStream nextPut: stmt expression.
		 sStream nextPut: self nullReturnExpr.
		 ^nil].
	(stmt expression isVariable and: ['nil' = stmt expression name]) ifTrue: 
		["^ nil -- this is never right unless automatically generated"
		 sStream nextPut: stmt.
		 ^nil].
	(stmt expression isVariable and: ['self' = stmt expression name]) ifTrue: 
		["^ self"
		 self generateFailureGuardOn: sStream.
		 fullArgs isEmpty ifFalse:[ sStream nextPut: (self popExpr: fullArgs size)].
		 sStream nextPut: self nullReturnExpr.
		 ^nil].
	(stmt expression isVariable | stmt expression isConstant | suppressingFailureGuards) ifTrue:
		["^ variable or ^ constant or ^ expr without guardchecking"
		 self generateFailureGuardOn: sStream.
		 sStream nextPut: (self pop: fullArgs size + 1 thenReturnExpr: stmt expression).
		 sStream nextPut: self nullReturnExpr.
		 ^nil].
	"^ expr with guardchecking"
	sStream nextPut: (self assign: (self oopVariable: '_return_value') expression: stmt expression).
	self generateFailureGuardOn: sStream.
	sStream nextPut: (self pop: fullArgs size + 1 thenReturnExpr: (self oopVariable: '_return_value')).
	sStream nextPut: self nullReturnExpr
!

----- Method: JSSmartSyntaxPluginMethod>>fixUpReturns (in category 'transforming') -----
fixUpReturns
	"Replace each return statement in this method with (a) the given postlog, (b) code to pop the receiver and the given number of arguments, and (c) code to push the integer result and return."

	parseTree nodesDo: [:node |
		node isStmtList ifTrue: [
			node setStatements: (Array streamContents:
				[:sStream |
				 node statements do: 
					[:stmt | self fixUpReturnOneStmt: stmt on: sStream]])]]!

----- Method: JSSmartSyntaxPluginMethod>>fromContext:primitive:parameters:receiver: (in category 'initializing') -----
fromContext: aContext primitive: aString parameters: aClassList receiver: aClass

	fullArgs := args := aContext tempNames
				copyFrom: 1
				to: aContext method numArgs.
	self 
		primitive: aString
		parameters: aClassList
		receiver: aClass!

----- Method: JSSmartSyntaxPluginMethod>>generateFailureGuardOn: (in category 'private') -----
generateFailureGuardOn: sStream
	suppressingFailureGuards ifTrue: [^nil].
	sStream nextPutAll: self checkSuccessExpr
!

----- Method: JSSmartSyntaxPluginMethod>>handlePrimitiveDirective:on: (in category 'specifying primitives') -----
handlePrimitiveDirective: aStmt on: sStream

	isPrimitive := true.
	fullArgs := args.
	locals addAll: args.
	args := OrderedCollection new.
	fullArgs with: parmSpecs do:
		[:argName :spec |
			declarations
				at: argName
				put: (spec jscgDeclareJSForVar: argName)].
	aStmt isAssignment ifTrue:
		[declarations
			at: aStmt variable name
			put: (rcvrSpec jscgDeclareJSForVar: aStmt variable name).
		 sStream nextPutAll: (self
			statementsFor:
				(rcvrSpec
					jscg:	JSSmartSyntaxPluginCodeGenerator new
					prolog:  [:expr | aStmt variable name, ' := ', expr]
					expr: 	aStmt variable name
					index: 	(fullArgs size))
			varName: '')].

	"only add the failure guard if there are args or it is an assignment"
	(fullArgs isEmpty not or:[aStmt isAssignment]) ifTrue:[self generateFailureGuardOn: sStream].
	^true.
!

----- Method: JSSmartSyntaxPluginMethod>>isPrimitiveDirectiveSend: (in category 'specifying primitives') -----
isPrimitiveDirectiveSend: stmt
	
	stmt isSend ifTrue:
		[stmt selector = #primitive: ifTrue:
			[^self primitive: 	stmt args first value
				   parameters:	(Array new: args size withAll: #Oop)
				   receiver:		#Oop].
		 stmt selector = #primitive:parameters: ifTrue:
			[^self primitive: 	stmt args first value
				   parameters: 	stmt args second value
				   receiver:		#Oop].
		 stmt selector = #primitive:parameters:receiver: ifTrue:
			[^self primitive:		stmt args first value
				   parameters:	stmt args second value
				   receiver:		stmt args third value].
		^false].
	^false.
!

----- Method: JSSmartSyntaxPluginMethod>>namedPrimitiveProlog (in category 'specifying primitives') -----
namedPrimitiveProlog

	| cg |
	cg := SmartSyntaxPluginCodeGenerator new.
	^Array streamContents: [:sStream |
		1 to: fullArgs size do:
			[:i |
			 sStream nextPutAll: 
				(self 
					statementsFor: 
						((parmSpecs at: i) 
							jscg: 	cg
							prolog:  [:expr | (fullArgs at: i), ' := ', expr]
							expr: (fullArgs at: i)
							index: (fullArgs size - i))
					varName: '')]]!

----- Method: JSSmartSyntaxPluginMethod>>nullReturnExpr (in category 'private') -----
nullReturnExpr

	^ TReturnNode new
		setExpression: (TVariableNode new setName: 'null')!

----- Method: JSSmartSyntaxPluginMethod>>oldReplaceSizeMessages (in category 'private') -----
oldReplaceSizeMessages
	"Replace sends of the message 'size' with calls to sizeOfSTArrayFromCPrimitive."

	| argExpr |
	parseTree nodesDo: [:n |
		(n isSend and: [n selector = #size]) ifTrue: [
			argExpr := TSendNode new
				setSelector: #+
				receiver: n receiver
				arguments: (Array with: (TConstantNode new setValue: 1)).
			n
				setSelector: #sizeOfSTArrayFromCPrimitive:
				receiver: (TVariableNode new setName: 'interpreterProxy')
				arguments: (Array with: argExpr)]].
!

----- Method: JSSmartSyntaxPluginMethod>>oopVariable: (in category 'private') -----
oopVariable: aString

	(locals includes: aString) ifFalse:
		[locals add: aString.
		 declarations
			at: aString 
			put: 'sqInt ', aString].
	^TVariableNode new setName: aString!

----- Method: JSSmartSyntaxPluginMethod>>parmSpecs (in category 'accessing') -----
parmSpecs

	^parmSpecs!

----- Method: JSSmartSyntaxPluginMethod>>pop:thenReturnExpr: (in category 'private') -----
pop: anInteger thenReturnExpr: anExpression

	^TSendNode new
		setSelector: #pop:thenPush:
		receiver: (TVariableNode new setName: 'interpreterProxy')
		arguments: (Array 
			with: (TConstantNode new 
				setValue: anInteger)
			with: anExpression)!

----- Method: JSSmartSyntaxPluginMethod>>popExpr: (in category 'private') -----
popExpr: anInteger

	^ TSendNode new
			 setSelector: #pop:
			 receiver: (TVariableNode new setName: 'interpreterProxy')
			 arguments: (Array 
				with: (TConstantNode new 
					setValue: anInteger))!

----- Method: JSSmartSyntaxPluginMethod>>primitive:parameters:receiver: (in category 'specifying primitives') -----
primitive: aString parameters: anArray receiver: aClassSymbol

	self selectorOverride: aString asSymbol.
	anArray size == args size ifFalse: 
		[^self error: self selectorOverride, ': incorrect number of parameter specifications'].
	parmSpecs := anArray collect:
		[:each | Smalltalk at: each ifAbsent:
			[^self error: self selectorOverride, ': parameter spec must be a Behavior']].
	parmSpecs do: [:each | each isBehavior ifFalse:
		[^self error: self selectorOverride, ': parameter spec must be a Behavior']].
	rcvrSpec := Smalltalk at: aClassSymbol asSymbol ifAbsent:
		[^self error: self selectorOverride, ': receiver spec must be a Behavior'].
	rcvrSpec isBehavior ifFalse:
		[^self error: self selectorOverride, ': receiver spec must be a Behavior'].
	^true!

----- Method: JSSmartSyntaxPluginMethod>>primitiveDirectiveWasHandled:on: (in category 'specifying primitives') -----
primitiveDirectiveWasHandled: stmt on: sStream

	(self isPrimitiveDirectiveSend: stmt) ifTrue:
		[^self handlePrimitiveDirective: stmt on: sStream].
	(stmt isAssignment and: 
		[self isPrimitiveDirectiveSend: stmt expression]) ifTrue:
			[^self handlePrimitiveDirective: stmt on: sStream].
	^false.
!

----- Method: JSSmartSyntaxPluginMethod>>printTempsAndVar:on: (in category 'private') -----
printTempsAndVar: varName on: aStream 
	"add the required temps and the varname to the stream"
	aStream nextPutAll: '| '.
	(#('rcvr' 'stackPointer' 'successFlag' 'interpreterProxy' ) reject: [:each | locals includes: each])
		do: [:each | aStream nextPutAll: each;
			 space].
	(locals reject: [:each | each first = $_])
		do: [:each | aStream nextPutAll: each;
			 space].
"don't add varName twice. Probably a deeper reason for this, but WTH. TPR"
	(locals includes: varName) ifFalse:[aStream nextPutAll: varName].
	aStream nextPutAll: '|';
	 cr!

----- Method: JSSmartSyntaxPluginMethod>>rcvrSpec (in category 'accessing') -----
rcvrSpec

	^rcvrSpec!

----- Method: JSSmartSyntaxPluginMethod>>recordDeclarations (in category 'transforming') -----
recordDeclarations
	"Record C type declarations of the forms

		self returnTypeC: 'float'.
		self var: #foo declareC: 'float foo'
		self var: #foo as: Class
		self var: #foo type: 'float'.

	 and remove the declarations from the method body."

	| newStatements |
	properties pragmas notEmpty ifTrue:
		[properties pragmas do:
			[:pragma|
			pragma keyword = #var:declareC: ifTrue:
				[self declarationAt: pragma arguments first asString put: pragma arguments last].
			pragma keyword = #var:type: ifTrue:
				[| varName varType |
				varName := pragma arguments first asString.
				varType := pragma arguments last.
				varType last = $* ifFalse: [varType := varType, ' '].
				self declarationAt: varName put: varType, varName].
			 pragma keyword = #var:as: ifTrue:
				[| theClass |
				 theClass := Smalltalk at: pragma arguments last name asSymbol ifAbsent: [nil].
				 (theClass isKindOf: Behavior) ifFalse:
					[^self error: 'declarator must be a Behavior'].
				 self declarationAt: pragma arguments first value asString 
					put: (theClass jscgDeclareJSForVar: pragma arguments first asString)].
			pragma keyword = #returnTypeC: ifTrue:
				[returnType := pragma arguments last].
			pragma keyword = #doNotGenerate: ifTrue:
				[locals removeKey: pragma arguments last]]].
	newStatements := OrderedCollection new: parseTree statements size.
	parseTree statements do: 
		[:stmt | | isDeclaration |
		 isDeclaration := false.
		 stmt isSend ifTrue: 
			[stmt selector = #var:declareC: ifTrue:
				[isDeclaration := true.
				self declarationAt: stmt args first value asString put: stmt args last value].
			stmt selector = #var:type: ifTrue: [
				| varName varType |
				isDeclaration := true.
				varName := stmt args first value asString.
				varType := stmt args last value.
				varType last = $* ifFalse: [varType := varType, ' '].
				self declarationAt: varName put: varType, varName.
			].
			 stmt selector = #var:as: ifTrue:
				[| theClass |
				 isDeclaration := true.
				 theClass := Smalltalk  at: stmt args last name asSymbol ifAbsent: [nil].
				 (theClass isKindOf: Behavior) ifFalse:
					[^self error: 'declarator must be a Behavior'].
				 self declarationAt: stmt args first value asString 
					put: (theClass jscgDeclareJSForVar: stmt args first value asString)].
			 stmt selector = #returnTypeC: ifTrue: 
				[isDeclaration := true.
				 returnType := stmt args last value]].
		 isDeclaration ifFalse: [newStatements add: stmt]].
	parseTree setStatements: newStatements asArray!

----- Method: JSSmartSyntaxPluginMethod>>removeFinalSelfReturn (in category 'transforming') -----
removeFinalSelfReturn
	"The Smalltalk parser automatically adds the statement '^self' to the end of methods without explicit returns. This method removes such statements, since the generated code has no notion of 'self' anyway."

	| stmtList lastStmt |
	stmtList := parseTree statements asOrderedCollection.
	lastStmt := stmtList last.

	((lastStmt isReturn) and:
	 [(lastStmt expression isVariable) and:
	 ['self' = lastStmt expression name]]) ifTrue: [
		stmtList removeLast.
		parseTree setStatements: stmtList.
	].!

----- Method: JSSmartSyntaxPluginMethod>>replaceArraySizeMessages (in category 'transforming') -----
replaceArraySizeMessages
	"Replace sends of the message 'size' with calls to sizeOfSTArrayFromCPrimitive. Specialised version for generating primitives outside a plugin"

	super replaceSizeMessages
!

----- Method: JSSmartSyntaxPluginMethod>>replaceSizeMessages (in category 'transforming') -----
replaceSizeMessages
	"Replace sends of the message 'size' with calls to sizeOfSTArrayFromCPrimitive."

	parseTree nodesDo: [:n |
		(n isSend and: [n selector = #size]) ifTrue: [
			n
				setSelector: #sizeOfSTArrayFromCPrimitive:
				receiver: (TVariableNode new setName: 'interpreterProxy')
				arguments: (Array with: n receiver)]].
!

----- Method: JSSmartSyntaxPluginMethod>>selectorForCodeGeneration (in category 'accessing') -----
selectorForCodeGeneration
	"A primitive directive my override the selector specification."

	^ self selectorOverride ifNil: [self selector]!

----- Method: JSSmartSyntaxPluginMethod>>selectorOverride (in category 'accessing') -----
selectorOverride
	"A primitive directive allows the selector to be overridden in order to specify
	a preferred name for the generated primitive."

	^ selectorOverride!

----- Method: JSSmartSyntaxPluginMethod>>selectorOverride: (in category 'accessing') -----
selectorOverride: preferredSelectorName
	"A primitive directive allows the selector to be overridden in order to specify
	a preferred name for the generated primitive."

	selectorOverride := preferredSelectorName!

----- Method: JSSmartSyntaxPluginMethod>>setSelector:definingClass:args:locals:block:primitive:properties:comment: (in category 'initializing') -----
setSelector: sel definingClass: class args: argList locals: localList block: aBlockNode primitive: aNumber properties: methodProperties comment: aComment
	"Initialize this method using the given information."

	selector := sel.
	definingClass := class.
	returnType := #sqInt. 	 "assume return type is sqInt for now"
	args := argList asOrderedCollection collect: [:arg | arg key].
	locals := localList asOrderedCollection collect: [:arg | arg key].
	declarations := Dictionary new.
	primitive := aNumber.
	properties := methodProperties.
	comment := aComment.
	parseTree := aBlockNode asTranslatorNodeIn: self.
	labels := OrderedCollection new.
	complete := false.  "set to true when all possible inlining has been done"
	export := self extractExportDirective.
	static := self extractStaticDirective.
	canAsmLabel := self extractLabelDirective.
	self extractSharedCase.
	isPrimitive := false.  "set to true only if you find a primtive direction."
	suppressingFailureGuards := self extractSuppressFailureGuardDirective.
	self recordDeclarations.
	self extractPrimitiveDirectives.
!

----- Method: JSSmartSyntaxPluginMethod>>simulatePrologInContext: (in category 'specifying primitives') -----
simulatePrologInContext: aContext

	|cg instructions |
	cg := SmartSyntaxPluginCodeGenerator new.
	parmSpecs keysAndValuesDo: 
		[:index :each |
		 instructions := ((parmSpecs at: index)
			jscg: cg 
			prolog: (cg jscgTVarBlock: index) 
			expr: '<foo>' 
			index: args size - index).
		 Compiler new 
			evaluate: instructions
			in: aContext 
			to: aContext receiver
			notifying: nil
			ifFail: nil].
	instructions := (rcvrSpec
		jscg: cg 
		prolog: [:expr | '^', expr]
		expr: '<foo>' 
		index: args size).
	 ^Compiler new 
		evaluate: instructions
		in: aContext 
		to: aContext receiver
		notifying: nil
		ifFail: nil!

----- Method: JSSmartSyntaxPluginMethod>>vmNameString (in category 'primitive compilation') -----
vmNameString
	"return the string to use as the vm name in code generated for this method"
	^'interpreterProxy'!

----- Method: Object class>>jscg:generateCoerceToOopFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToOopFrom: aNode on: aStream
	"N.B.  The is used both for generation and simulation so answer the result (for interpretation)"
	^cg emitJSExpression: aNode on: aStream!

----- Method: Object class>>jscg:generateCoerceToValueFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToValueFrom: aNode on: aStream
	"N.B.  The could be used both for generation and simulation so answer the result (for interpretation)"
	^cg emitJSExpression: aNode on: aStream!

----- Method: Object class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg jscgLoad: aBlock expr: aString asKindOf: self from: anInteger!

----- Method: Object class>>jscgCanConvertFrom: (in category '*vmmakerjs') -----
jscgCanConvertFrom: anObject

	^anObject isKindOf: self!

----- Method: Object class>>jscgDeclareJSForVar: (in category '*vmmakerjs') -----
jscgDeclareJSForVar: aSymbolOrString

	^'var ', aSymbolOrString!

----- Method: Array class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg 
		jscgLoad: aBlock 
		expr: aString 
		asIntPtrFrom: anInteger
		andThen: (cg jscgValBlock: 'isIndexable')!

----- Method: TVariableNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen

	name = 'nil'
		ifTrue: [ aStream nextPutAll: (aCodeGen cLiteralFor: nil) ]
		ifFalse: [ aStream nextPutAll: (aCodeGen returnPrefixFromVariable: name) ].!

----- Method: SmartSyntaxPluginCodeGenerator class>>new (in category '*vmmakerjs') -----
new
	JSCodeGenerator isActive ifTrue: [^JSSmartSyntaxPluginCodeGenerator new].
	^super new!

----- Method: Unsigned class>>jscg:generateCoerceToOopFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToOopFrom: aNode on: aStream
	"N.B.  The is used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToUnsignedObjectFrom: aNode on: aStream!

----- Method: Unsigned class>>jscg:generateCoerceToValueFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToValueFrom: aNode on: aStream
	"N.B.  The could be used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToUnsignedValueFrom: aNode on: aStream!

----- Method: Unsigned class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg jscgLoad: aBlock expr: aString asUnsignedValueFrom: anInteger!

----- Method: Unsigned class>>jscgCanConvertFrom: (in category '*vmmakerjs') -----
jscgCanConvertFrom: anObject

	anObject isInteger ifFalse: 
		[self error: 'Not an Integer object'. ^false].
	anObject >= 0 ifFalse: 
		[self error: 'Object is negative integer'. ^false].
	anObject < (2 raisedToInteger: 32) ifFalse: 
		[self error: 'Object is too large'. ^false].
	^true!

----- Method: TConstantNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	"Emit a C literal."

	aStream nextPutAll: (aCodeGen cLiteralFor: value).!

----- Method: TInlineNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	method emitInlineOn: aStream level: level generator: aCodeGen.
!

----- Method: WordArray class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg 
		jscgLoad: aBlock 
		expr: aString 
		asUnsignedPtrFrom: anInteger
		andThen: (cg jscgValBlock: 'isWords')!

----- Method: TAssignmentNode>>emitJSCodeAsArgumentOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen
	aStream nextPut: $(.
	self emitJSCodeOn: aStream level: level generator: aCodeGen.
	aStream nextPut: $)!

----- Method: TAssignmentNode>>emitJSCodeAsExpressionOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsExpressionOn: aStream level: level generator: aCodeGen
	aStream nextPut: $(.
	self emitJSCodeOn: aStream level: level generator: aCodeGen.
	aStream nextPut: $)!

----- Method: TAssignmentNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	expression isSwitch ifTrue:
		[^expression emitJSCodeOn: aStream addToEndOfCases: self level: level generator: aCodeGen].
	variable emitJSCodeOn: aStream level: level generator: aCodeGen.
	self isVariableUpdatingAssignment
		ifTrue:
			[aStream
				space;
				nextPutAll: expression selector;	"+ or -"
				nextPut: $=;
				space.
			expression args first emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen]
		ifFalse:
			[aStream space; nextPut: $=; space.
			 expression emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen]!

----- Method: TSendNode>>emitJSCodeAsArgumentOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen
	"Emit the receiver in a form that can be passed as an argument."

	"If the selector is a built-in construct, translate it and return"
	(aCodeGen emitBuiltinConstructAsArgumentFor: self asExpression on: aStream level: level) ifFalse:
		["If it is a pointer dereference generate it"
		(self emitJSCodeAsPointerDereferenceOn: aStream level: level generator: aCodeGen) ifFalse:
			["Otherwise generate the vanilla C function call."
			 self emitJSCodeAsFunctionCallOn: aStream level: level generator: aCodeGen]]!

----- Method: TSendNode>>emitJSCodeAsExpressionOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsExpressionOn: aStream level: level generator: aCodeGen
	^self emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen!

----- Method: TSendNode>>emitJSCodeAsFunctionCallOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsFunctionCallOn: aStream level: level generator: aCodeGen

	"Translate this message send into a C function call"
	"Special case for pluggable modules. Replace messages to interpreterProxy
	 by interpreterProxy->message(..) if the message is not builtin"
	(aCodeGen isGeneratingPluginCode
	 and: [receiver isVariable
	 and: ['interpreterProxy' = receiver name
	 and: [self isBuiltinOperator not]]]) ifTrue:
		[aStream nextPutAll:'interpreterProxy.'].
	"Translate this message send into a C function call."
	aStream nextPutAll: (aCodeGen cFunctionNameFor: selector); nextPut: $(.
	"Only include the receiver as the first argument in certain cases.
	 The receiver is always included if it is an expression.
	 If it is a variable:
		 If the vmClass says it is an implicit variable, don't include it.
		 If the variable is 'self' and the method being called is not in
		 the method set (i.e. it is some external code), don't include it."
	(self shouldIncludeReceiverAsFirstArgument: aCodeGen) ifTrue:
		[receiver emitJSCodeOn: aStream level: level generator: aCodeGen.
		arguments isEmpty ifFalse:
			[aStream nextPutAll: ', ']].
	arguments do:
		[ :arg| arg emitJSCodeAsArgumentOn: aStream level: level generator: aCodeGen]
		separatedBy: [aStream nextPut: $,; space].
	aStream nextPut: $)!

----- Method: TSendNode>>emitJSCodeAsPointerDereferenceOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeAsPointerDereferenceOn: aStream level: level generator: aCodeGen
	"If appropriate, translate this message send as a pointer dereference"

	(self isStructSend: aCodeGen) ifFalse:
		[^false].

	aStream nextPut: $(.
	receiver  emitJSCodeAsExpressionOn: aStream level: 0 generator: aCodeGen.
	aStream nextPut: $-; nextPut: $>.
	aStream nextPutAll: (aCodeGen cFunctionNameFor: selector).
	arguments isEmpty ifFalse:
		[self assert: arguments size = 1.
		 aStream nextPutAll: ' = '.
		 arguments first emitJSCodeAsExpressionOn: aStream level: level generator: aCodeGen].
	aStream nextPut: $).
	^true!

----- Method: TSendNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	"Emit the receiver as a statement."

	"If the selector is a built-in construct, translate it and return"
	(aCodeGen emitBuiltinConstructFor: self on: aStream level: level) ifFalse:
		["If it is a pointer dereference generate it"
		(self emitJSCodeAsPointerDereferenceOn: aStream level: level generator: aCodeGen) ifFalse:
			["Otherwise generate the vanilla C function call."
			 self emitJSCodeAsFunctionCallOn: aStream level: level generator: aCodeGen]]!

----- Method: Boolean class>>jscg:generateCoerceToOopFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToOopFrom: aNode on: aStream
	"N.B.  The is used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToBooleanObjectFrom: aNode on: aStream!

----- Method: Boolean class>>jscg:generateCoerceToValueFrom:on: (in category '*vmmakerjs') -----
jscg: cg generateCoerceToValueFrom: aNode on: aStream
	"N.B.  The could be used both for generation and simulation so answer the result (for interpretation)"
	^cg generateCoerceToBooleanValueFrom: aNode on: aStream!

----- Method: Boolean class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg jscgLoad: aBlock expr: aString asBooleanValueFrom: anInteger!

----- Method: ByteArray class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg 
		jscgLoad: aBlock 
		expr: aString 
		asCharPtrFrom: anInteger
		andThen: (cg jscgValBlock: 'isBytes')!

----- Method: IntegerArray class>>jscg:prolog:expr:index: (in category '*vmmakerjs') -----
jscg: cg prolog: aBlock expr: aString index: anInteger

	^cg 
		jscgLoad: aBlock 
		expr: aString 
		asIntPtrFrom: anInteger
		andThen: (cg jscgValBlock: 'isWords')!

----- Method: InterpreterPlugin class>>moduleExtension (in category '*vmmakerjs-override') -----
moduleExtension
	Smalltalk at: #JSCodeGenerator ifPresent: [:js | js isActive ifTrue: [^'.js']].
	^ self isCPP ifTrue: ['.cpp'] ifFalse: ['.c']!

----- Method: TNotImplementedNode>>emitJSCodeOn:level:generator: (in category '*vmmakerjs') -----
emitJSCodeOn: aStream level: level generator: aCodeGen
	"Emit a comment only"

	aStream cr; nextPutAll: '/*** ';
		nextPutAll: self printString;
		nextPutAll: ' cannot translate: '; cr;
		nextPutAll: parseNode printString;
		cr; nextPutAll: ' ***/'; cr
!



More information about the Vm-dev mailing list