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

commits at source.squeak.org commits at source.squeak.org
Tue Oct 14 22:54:27 UTC 2014


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

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

Name: VMMakerJS-bf.12
Author: bf
Time: 14 October 2014, 3:49:18.236 pm
UUID: a24182f0-6780-4782-a772-87ccf9030a78
Ancestors: VMMakerJS-bf.11

Fix inst vars in non-inlined prim methods (specifically, ADPCMCodecPlugin).

=============== Diff against VMMakerJS-bf.11 ===============

Item was changed:
  ----- Method: JSCodeGenerator class>>beActiveDuring: (in category 'preferences') -----
  beActiveDuring: aBlock
  	| wasActive |
  	wasActive := self isActive.
+ 	self isActive: true.
  	aBlock ensure: [self isActive: wasActive].!

Item was changed:
  ----- Method: JSCodeGenerator>>addMethodsForPrimitives: (in category 'public') -----
  addMethodsForPrimitives: classAndSelectorList 
+ 	| sel aClass source verbose meth primInstVars sharedInstVars assignedInstVars |
- 	| 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: false"
- 	self doInlining: false.
  
+ 	primInstVars := Set new.			"inst vars used in primitives"
+ 	sharedInstVars := Set new.			"inst vars used in non-primitives"
+ 	assignedInstVars :=  Set new.		"inst vars modified in non-primitives"
  	methods do:[:m|
+ 		m primitive > 0 ifTrue: [
+ 			primInstVars addAll: m freeVariableReferences.
+ 		] ifFalse: [
+ 			sharedInstVars addAll: m freeVariableReferences.
+ 			assignedInstVars addAll: m variablesAssignedTo.
+ 		].
+ 	].
+ 	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 preparePrimitivePrologueShared: sharedInstVars assigned: assignedInstVars ].
- 		m primitive > 0 ifTrue: [m preparePrimitivePrologue].
  		"check for one-based array access"	
  		m oneBasedArrays ifNotNil: [self oneBasedArrays: true].
+ 	].
+ 	"Add declarations for inst vars used in both prims and non-prims as global"
+ 	((primInstVars intersection: sharedInstVars) difference: variables) do: [:var |
+ 		methods do:[:m|
+ 			m declarations at: var ifPresent: [:decl |
+ 				variableDeclarations at: var
+ 					ifPresent: [:existing |
+ 						decl = existing ifFalse: [self error: 'decls do not match']]
+ 					ifAbsent: [variableDeclarations at: var put: decl]]].
+ 		variables add: var].
+ 	"Add non-shared inst vars as local"
+ 	methods do:[:m|
+ 		m locals addAll: (m freeVariableReferences difference: sharedInstVars)].
+ 	!
- 	].!

Item was changed:
  ----- 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' 'null') do: [ :var | refs remove: var ifAbsent: [] ].
- 	#('self' 'nil' 'true' 'false') do: [ :var | refs remove: var ifAbsent: [] ].
  	^ refs asSortedCollection!

Item was removed:
- ----- 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].
- !

Item was added:
+ ----- Method: JSMethod>>preparePrimitivePrologueShared:assigned: (in category 'primitive compilation') -----
+ preparePrimitivePrologueShared: sharedInstVars assigned: assignedInstVars
+ 	"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 union: sharedInstVars.
+ 	varsAssignedTo := self variablesAssignedTo asSet union: assignedInstVars.
+ 	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. -- since we do not inline, we cannot declare these local since they migth be used by inlined methods"
+ 			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].
+ !



More information about the Vm-dev mailing list