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

commits at source.squeak.org commits at source.squeak.org
Fri Apr 22 00:05:01 UTC 2016


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

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

Name: VMMaker.oscog-eem.1832
Author: eem
Time: 21 April 2016, 5:03:03.826813 pm
UUID: 3e4d6e88-f60d-4a01-930d-7c5895b8a86a
Ancestors: VMMaker.oscog-eem.1831

Do that rename.  I wanna generate sources :-)

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

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 |
  	self notePluginFunctionsUsedByMacros.
+ 	self preDeclareMacrosForFastClassCheckingOn: aStream.
- 	self preDeclareMacrosForFastClassChekingOn: aStream.
  	(pluginFuncs := 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|
  		 tMethod recordDeclarationsIn: self.
  		 tMethod returnType ifNil:
  			[tMethod inferReturnTypeIn: self]].
  	pluginFuncs do:
  		[:tMethod| | functionName |
  		functionName := self cFunctionNameFor: tMethod selector.
  		aStream nextPutAll:
  			((String streamContents:
  					[:s|
  					tMethod
  						static: true;
  						emitCFunctionPrototype: s generator: self])
  				copyReplaceAll: functionName
  				with: '(*', functionName, ')'
  				tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]])].
  	aStream nextPutAll: '#else /* !!defined(SQUEAK_BUILTIN_PLUGIN) */'; cr.
  	pluginFuncs do:
  		[:tMethod|
  		self withOptionalVerbiageFor: tMethod selector
  			on: aStream
  			do: [tMethod static: false; export: false; emitCFunctionPrototype: aStream generator: self]
  			ifOptionalDo:
  				[aStream nextPutAll: '# define '.
  				 (TSendNode new
  					setSelector: tMethod selector
  						receiver: (TVariableNode new setName: 'interpreterProxy')
  							arguments: (tMethod args collect: [:a| TVariableNode new setName: a]))
  					emitCCodeAsArgumentOn: aStream
  						level: 0
  							generator: self.
  				 aStream nextPutAll: ' 0'; cr]].
  	aStream nextPutAll: 'extern'; cr; nextPutAll: '#endif'; cr.!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>preDeclareMacrosForFastClassCheckingOn: (in category 'C code generator') -----
+ preDeclareMacrosForFastClassCheckingOn: aStream
+ 	"These macros can be used to check for various case of Integer type.
+ 	Since they can be defined based on existing API, this is a good trade off:
+ 	- avoid extending the interpreterProxy API like mad
+ 	- provide fast type checking"
+ 	
+ 	"Fast-up generated code by using a macro for this well known function unconditionnally"
+ 	#(	'#define isIntegerObject(oop) (oop & 1)' cr
+ 		'#if SPURVM && defined(SQUEAK_BUILTIN_PLUGIN)'
+ 
+ 		"Compact class index are hardcoded because there is no guarantee that the pool values at generation time are that of SPUR..
+ 		 Make sure they are in sync with SpurMemoryManager class>>initializeCompactClassIndices"
+ 		'extern sqInt classIndexOf(sqInt);'
+ 		'# define LargeNegativeIntegerClassIndex 32'
+ 		'# define LargePositiveIntegerClassIndex 33'
+ 		'# define isKindOfInteger(oop) (isImmediate(oop) ? isIntegerObject(oop) : (unsigned)(classIndexOf(oop) - LargeNegativeIntegerClassIndex) <= 1)'
+ 		'# define isLargeIntegerObject(oop) (!!isImmediate(oop) && (unsigned)(classIndexOf(oop) - LargeNegativeIntegerClassIndex) <= 1)'
+ 		'# define isLargeNegativeIntegerObject(oop) (!!isImmediate(oop) && classIndexOf(oop) == LargeNegativeIntegerClassIndex)'
+ 		'# define isLargePositiveIntegerObject(oop) (!!isImmediate(oop) && classIndexOf(oop) == LargePositiveIntegerClassIndex)'
+ 
+ 		'#else /* defined(SQUEAK_BUILTIN_PLUGIN) && defined(SPURVM) */'
+ 
+ 		'# define isLargeNegativeIntegerObject(oop) (fetchClassOf(oop) == classLargeNegativeInteger())'
+ 		'# define isLargePositiveIntegerObject(oop) (fetchClassOf(oop) == classLargePositiveInteger())'
+ 		'# define isLargeIntegerObject(oop) (isLargeNegativeIntegerObject(oop) || isLargePositiveIntegerObject(oop))'
+ 		'# define isKindOfInteger(oop) (isIntegerObject(oop) || isLargeNegativeIntegerObject(oop) || isLargePositiveIntegerObject(oop))'
+ 
+ 		'#endif /* defined(SQUEAK_BUILTIN_PLUGIN) && defined(SPURVM) */' cr) do:
+ 		[:element|
+ 		aStream cr.
+ 		element ~~ #cr ifTrue: [aStream cr; nextPutAll: element]]!

Item was removed:
- ----- Method: VMPluginCodeGenerator>>preDeclareMacrosForFastClassChekingOn: (in category 'C code generator') -----
- preDeclareMacrosForFastClassChekingOn: aStream
- 	"These macros can be used to check for various case of Integer type.
- 	Since they can be defined based on existing API, this is a good trade off:
- 	- avoid extending the interpreterProxy API like mad
- 	- provide fast type checking"
- 	
- 	"Fast-up generated code by using a macro for this well known function unconditionnally"
- 	aStream cr; nextPutAll: '#define isIntegerObject(oop) (oop & 1)'; cr. 
- 	
- 	aStream cr; nextPutAll: '#if SPURVM && defined(SQUEAK_BUILTIN_PLUGIN)'.
- 	
- 	"Compact class index are hardcoded because there is no guaranty that the pool values at generation time are that of SPUR..
- 	 Make sure they are in sync with SpurMemoryManager class>>initializeCompactClassIndices"
- 	aStream cr; nextPutAll: '# define LargeNegativeIntegerClassIndex 32'.
- 	aStream cr; nextPutAll: '# define LargePositiveIntegerClassIndex 33'.
- 	aStream cr; nextPutAll: 'extern sqInt classIndexOf(sqInt);'.
- 	aStream cr; nextPutAll: '# define isKindOfInteger(oop) (isImmediate(oop) ? isIntegerObject(oop) : (unsigned)(classIndexOf(oop) - LargeNegativeIntegerClassIndex) <= 1)'.
- 	aStream cr; nextPutAll: '# define isLargeIntegerObject(oop) (!!isImmediate(oop) && (unsigned)(classIndexOf(oop) - LargeNegativeIntegerClassIndex) <= 1)'.
- 	aStream cr; nextPutAll: '# define isLargeNegativeIntegerObject(oop) (!!isImmediate(oop) && classIndexOf(oop) == LargeNegativeIntegerClassIndex)'.
- 	aStream cr; nextPutAll: '# define isLargePositiveIntegerObject(oop) (!!isImmediate(oop) && classIndexOf(oop) == LargePositiveIntegerClassIndex)'.
- 	
- 	aStream cr; nextPutAll: '#else /* defined(SQUEAK_BUILTIN_PLUGIN) && defined(SPURVM) */'.
- 	
- 	aStream cr; nextPutAll: '# define isLargeNegativeIntegerObject(oop) (fetchClassOf(oop) == classLargeNegativeInteger())'.
- 	aStream cr; nextPutAll: '# define isLargePositiveIntegerObject(oop) (fetchClassOf(oop) == classLargePositiveInteger())'.
- 	aStream cr; nextPutAll: '# define isLargeIntegerObject(oop) (isLargeNegativeIntegerObject(oop) || isLargePositiveIntegerObject(oop))'.
- 	aStream cr; nextPutAll: '# define isKindOfInteger(oop) (isIntegerObject(oop) || isLargeNegativeIntegerObject(oop) || isLargePositiveIntegerObject(oop))'.
- 
- 	aStream cr; nextPutAll: '#endif /* defined(SQUEAK_BUILTIN_PLUGIN) && defined(SPURVM) */'; cr
- 	!



More information about the Vm-dev mailing list