[Vm-dev] VM Maker: VMMaker.oscog-eem.580.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jan 9 23:38:50 UTC 2014


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.580.mcz

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

Name: VMMaker.oscog-eem.580
Author: eem
Time: 9 January 2014, 3:35:28.199 pm
UUID: 751b08d4-d92e-440a-b3f6-cb2c76f52514
Ancestors: VMMaker.oscog-eem.579

Output accessor depth for external primitives in the form of
per-primitive signed chars named primitiveFooAccessorDepth
that hold the depth for primitiveFoo.

Check when outputting the primitive declarations that the real ones
in StackInterpreter, ObjectMemory et al match those in
InterpreterProxy.

Fix the signatures of floatObjectOf:, positive64BitIntegerFor: &
signed64BitIntegerFor:.  Pragmatize HostWindowPlugin>>
shutdownModule.

Nuke Object>>export:, Object>>inline:, & Object>>static:.  These
cause confusion and delay (cuz they mask the fact that TMethod
may not implement them as expected).

=============== Diff against VMMaker.oscog-eem.579 ===============

Item was changed:
  ----- Method: CCodeGenerator>>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 |
  	selector == #initialize ifTrue:
  		[^nil].
  	method := aClass compiledMethodAt: selector.
  	(method pragmaAt: #doNotGenerate) ifNotNil:
  		[^nil].
  	method isSubclassResponsibility ifTrue:
  		[^nil].
  	(self shouldIncludeMethodFor: aClass selector: selector) ifFalse:
  		[^nil].
  	tmethod := self addMethod: (self compileToTMethodSelector: selector in: aClass).
  	"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.
+ 		(inlineList includes: selector) ifTrue:
+ 			[inlineList := inlineList copyWithout: selector]].
- 		tmethod inline: false].
  	(method propertyValueAt: #cmacro:) ifNotNil:
  		[:macro|
  		self addMacro: macro for: selector.
+ 		(inlineList includes: selector) ifTrue:
+ 			[inlineList := inlineList copyWithout: selector]].
- 		tmethod inline: false].
  	^tmethod!

Item was changed:
  ----- Method: HostWindowPlugin>>shutdownModule (in category 'initialize-release') -----
  shutdownModule
  "do any window related VM closing down work your platform requires."
+ 	<export: true>
- 	self export: true.
  	^self cCode: 'ioCloseAllWindows()' inSmalltalk:[true]!

Item was changed:
  ----- Method: InterpreterProxy>>floatObjectOf: (in category 'converting') -----
  floatObjectOf: aFloat
+ 	<returnTypeC: #sqInt> "...because answering the float argument causes the type inferencer to say this answers a float."
  	<var: #aFloat type: 'double '>
  	aFloat class == Float ifFalse:[self error:'Not a float object'].
  	^aFloat!

Item was changed:
  ----- Method: InterpreterProxy>>positive64BitIntegerFor: (in category 'converting') -----
  positive64BitIntegerFor: integerValue
+ 	<returnTypeC: #sqInt> "...because answering the 64-bit argument causes the type inferencer to say this answers 64-bits."
  	<var: 'integerValue' type: #sqLong>
  	integerValue isInteger ifFalse:[self error:'Not an Integer object'].
  	^integerValue > 0
  		ifTrue:[integerValue]
  		ifFalse:[ (1 bitShift: 64) + integerValue]!

Item was changed:
  ----- Method: InterpreterProxy>>signed64BitIntegerFor: (in category 'converting') -----
  signed64BitIntegerFor: integerValue
+ 	<returnTypeC: #sqInt> "...because answering the 64-bit argument causes the type inferencer to say this answers 64-bits."
  	<var: 'integerValue' type: #sqLong>
  	integerValue isInteger ifFalse:[self error:'Not an Integer object'].
  	^integerValue!

Item was removed:
- ----- Method: Object>>export: (in category '*VMMaker-translation support') -----
- export: aBoolean
- 	"For translation only; noop when running in Smalltalk."!

Item was removed:
- ----- Method: Object>>inline: (in category '*VMMaker-translation support') -----
- inline: inlineFlag
- 	"For translation only; noop when running in Smalltalk."!

Item was removed:
- ----- Method: Object>>static: (in category '*VMMaker-translation support') -----
- static: aBoolean
- 	"For translation only; noop when running in Smalltalk."!

Item was changed:
  ----- Method: SpurMemoryManager>>ioLoadFunction:From: (in category 'simulation only') -----
+ ioLoadFunction: functionName From: moduleName
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring.
+ 	 provide accurate types for the VMPluginCodeGenerator."
- ioLoadFunction: functionString From: pluginString
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
  	<doNotGenerate>
+ 	<returnTypeC: #'void *'>
+ 	<var: #functionName type: #'char *'>
+ 	<var: #moduleName type: #'char *'>
+ 	^coInterpreter ioLoadFunction: functionName From: moduleName!
- 	^coInterpreter ioLoadFunction: functionString From: pluginString!

Item was added:
+ ----- Method: TMethod>>export: (in category 'accessing') -----
+ export: aBoolean
+ 	export := aBoolean!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>emitAccessorDepthsOn: (in category 'C code generator') -----
+ emitAccessorDepthsOn: aStream 
+ 	"Output accessor depth bytes for all primitives in the plugin.
+ 	 This is for external primitives in Spur."
+ 	(self sortStrings: self exportedPrimitiveNames) do:
+ 		[:primName|
+ 		 (self accessorDepthForSelector: primName asSymbol) ifNotNil:
+ 			[:depth|
+ 			 "store the accessor depth in a byte variable; save a little space
+ 			  by omitting depths < 0; support code supplies the default."
+ 			 self assert: depth < 128.
+ 			 depth >= 0 ifTrue:
+ 				[aStream
+ 					nextPutAll: 'signed char ';
+ 					nextPutAll: primName;
+ 					nextPutAll: 'AccessorDepth = ';
+ 					nextPutAll: (self cLiteralFor: depth);
+ 					nextPut: $;;
+ 					cr]]]!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>emitExportsOn: (in category 'C code generator') -----
  emitExportsOn: aStream
  	"Store all the exported primitives in the form used by the internal named prim system."
  	aStream cr; cr; nextPutAll:'#ifdef SQUEAK_BUILTIN_PLUGIN'.
  	self emitExportsNamed: pluginName pluginName: pluginName on: aStream.
+ 	aStream cr; nextPutAll: '#else /* ifdef SQ_BUILTIN_PLUGIN */'; cr; cr.
+ 	self emitAccessorDepthsOn: aStream.
  	aStream cr; nextPutAll: '#endif /* ifdef SQ_BUILTIN_PLUGIN */'; cr!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>preDeclareInterpreterProxyOn: (in category 'C code generator') -----
  preDeclareInterpreterProxyOn: aStream
  	"Put the necessary #defines needed before interpreterProxy.  Basically
  	 internal plugins use the VM's interpreterProxy variable and external plugins
  	 use their own.  Override to keep local copies of all functions in external
  	 prims, and link directly in internal plugins."
  	"| pcc |
  	pcc := self new.
  	(InterpreterProxy selectors reject: [:s| #(initialize private) includes: (InterpreterProxy whichCategoryIncludesSelector: s)]) do:
  		[:s| pcc noteUsedPluginFunction: s].
  	pcc preDeclareInterpreterProxyOn: Transcript.
  	Transcript flush"
+ 	| pluginFuncs interpreterClass objectMemoryClass |
+ 	(pluginFuncs := self pluginFunctionsToClone) isEmpty ifTrue:
- 	| pluginsToClone |
- 	(pluginsToClone := self pluginFunctionsToClone) isEmpty ifTrue:
  		[^super preDeclareInterpreterProxyOn: aStream].
  	aStream cr; nextPutAll: '#if !!defined(SQUEAK_BUILTIN_PLUGIN)'; cr.
+ 	interpreterClass := self referenceInterpreterClass.
+ 	objectMemoryClass := self referenceObjectMemoryClass.
+ 	pluginFuncs := pluginFuncs collect:
+ 						[:selector| | reference actual |
+ 						reference := self compileToTMethodSelector: selector
+ 										in: ((interpreterClass whichClassIncludesSelector: selector) ifNil:
+ 											[(objectMemoryClass whichClassIncludesSelector: selector) ifNil:
+ 												[InterpreterProxy]]).
+ 						actual := self compileToTMethodSelector: selector in: InterpreterProxy.
+ 						(reference returnType ~= actual returnType
+ 						 or: [(1 to: reference args size) anySatisfy:
+ 								[:i| (reference typeFor: (reference args at: i) in: self)
+ 								  ~= (actual typeFor: (actual args at: i) in: self)]]) ifTrue:
+ 							[self logger
+ 								nextPutAll: 'warning, signature of InterpreterProxy>>';
+ 								nextPutAll: selector;
+ 								nextPutAll: ' does not match reference implementation.';
+ 								cr].
+ 						actual].
+ 	pluginFuncs do:
+ 		[:tMethod| | functionName |
+ 		functionName := self cFunctionNameFor: tMethod selector.
- 	pluginsToClone do:
- 		[:selector| | functionName |
- 		functionName := self cFunctionNameFor: selector.
  		aStream nextPutAll:
  			((String streamContents:
+ 					[:s|
+ 					tMethod
+ 						static: true;
+ 						emitCFunctionPrototype: s generator: self])
- 				[:s|
- 				(self compileToTMethodSelector: selector in: InterpreterProxy)
- 					emitCFunctionPrototype: s generator: self])
  				copyReplaceAll: functionName
+ 				with: '(*', functionName, ')'
+ 				tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]]).
- 				with: '(*', functionName, ')').
  		aStream nextPut: $;; cr].
  	aStream nextPutAll: '#else /* !!defined(SQUEAK_BUILTIN_PLUGIN) */'.
+ 	pluginFuncs do:
+ 		[:tMethod|
+ 		self withOptionalVerbiageFor: tMethod selector
- 	pluginsToClone do:
- 		[:selector| | m |
- 		m := self compileToTMethodSelector: selector in: InterpreterProxy.
- 		self withOptionalVerbiageFor: selector
  			on: aStream
  			do: [aStream cr; nextPutAll: 'extern '.
+ 				tMethod static: false; export: false; emitCFunctionPrototype: aStream generator: self.
- 				m static: false; emitCFunctionPrototype: aStream generator: self.
  				aStream nextPut: $;]
  			ifOptionalDo:
  				[aStream cr; nextPutAll: '# define '.
  				 (TSendNode new
+ 					setSelector: tMethod selector
- 					setSelector: selector
  						receiver: (TVariableNode new setName: 'interpreterProxy')
+ 							arguments: (tMethod args collect: [:a| TVariableNode new setName: a]))
- 							arguments: (m args collect: [:a| TVariableNode new setName: a]))
  					emitCCodeAsArgumentOn: aStream
  						level: 0
  							generator: self.
  				 aStream nextPutAll: ' 0']].
  	aStream cr; nextPutAll: 'extern'.
  	aStream cr; nextPutAll: '#endif'; cr!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>referenceInterpreterClass (in category 'C code generator') -----
+ referenceInterpreterClass
+ 	"Define the class from which to take methods to define the interpreter proxy imports."
+ 	^(Smalltalk classNamed: #StackInterpreter) ifNil:
+ 		[(Smalltalk classNamed: #Interpreter) ifNil:
+ 			[InterpreterProxy]]!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>referenceObjectMemoryClass (in category 'C code generator') -----
+ referenceObjectMemoryClass
+ 	"Define the class from which to take methods to define the interpreter proxy imports."
+ 	^(Smalltalk classNamed: #SpurMemoryManager) ifNil:
+ 		[(Smalltalk classNamed: #NewObjectMemory) ifNil:
+ 			[ObjectMemory]]!



More information about the Vm-dev mailing list