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

commits at source.squeak.org commits at source.squeak.org
Sat Feb 13 02:06:56 UTC 2016


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

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

Name: VMMaker.oscog-eem.1677
Author: eem
Time: 13 February 2016, 6:04:44.780067 pm
UUID: 7056bb77-6aa0-4cb6-aa6c-cd921c231d37
Ancestors: VMMaker.oscog-eem.1676

Slang:
Don't waste effort changing from symbols to strings when constructing TDefineNodes.
Change the interpreter proxy function dereference code to use carriage-return-last necessitated by the new optional declaration of functions prototype generation introduced in VMMaker.oscog-eem.1675.

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

Item was changed:
  ----- Method: CCodeGenerator>>addConstantForBinding: (in category 'public') -----
  addConstantForBinding: variableBinding
  	"Add the pool variable to the code base as a constant."
  	| node val |
  	val := variableBinding value.
  	node := (useSymbolicConstants and: [self isCLiteral: val])
  				ifTrue:[TDefineNode new
+ 							setName: variableBinding key
- 							setName: variableBinding key asString
  							value: variableBinding value]
  				ifFalse:[TConstantNode new setValue: variableBinding value].
+ 	constants at: variableBinding key put: node!
- 	constants at: variableBinding key asString put: node!

Item was changed:
  ----- Method: CCodeGenerator>>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:
+ 			[:binding |
+ 			self addConstantForBinding: binding]]!
- 		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]].!

Item was changed:
  ----- Method: CCodeGenerator>>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) ifTrue:
- 		(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) ifTrue:
- 			(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:
  		[(self instVarNamesForClass: aClass) 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 | | tmeth meth |
  		((self shouldIncludeMethodFor: aClass selector: sel)
  		and: [(tmeth := methods at: sel ifAbsent: nil) notNil
  		and: [(aClass isStructClass and: [(aClass isAccessor: sel)
  				and: [(methods at: sel) isStructAccessor]]) not
  		and: [(meth := aClass >> sel) isSubclassResponsibility not
  		and: [(aClass includesBehavior: tmeth definingClass) not]]]]) ifTrue:
  			[((aClass >>sel) pragmaAt: #option:)
  				ifNil: [self error: 'Method ', sel, ' was defined in a previously added class.']
  				ifNotNil:
  					[logger
  						ensureCr;
  						show: 'warning, method ', aClass name, '>>', sel storeString,
  								' overrides ', tmeth definingClass, '>>', sel storeString;
  						cr]]]!

Item was changed:
  ----- Method: CCodeGenerator>>const:declareC: (in category 'public') -----
  const: constName declareC: declarationString
  	"Record the given C declaration for a constant."
  
  	constants
+ 		at: constName
- 		at: constName asString
  		put: (TDefineNode new
+ 				setName: constName
- 				setName: constName asString
  				value: declarationString)!

Item was changed:
  ----- Method: TDefineNode>>name (in category 'accessing') -----
  name
+ 	^name!
- 	^name asString!

Item was changed:
  ----- Method: VMBasicConstants class>>defineAtCompileTime: (in category 'C translation') -----
+ defineAtCompileTime: anObject
+ 	^anObject isSymbol
+ 	 and: [self namesDefinedAtCompileTime includes: anObject]!
- defineAtCompileTime: aSymbol
- 	self assert: aSymbol isSymbol.
- 	^self namesDefinedAtCompileTime includes: aSymbol!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>generateInterpreterProxyFunctionDeference:on:indent: (in category 'C translation') -----
  generateInterpreterProxyFunctionDeference: aNode on: aStream indent: anInteger
  	| pluginsToClone |
  	(pluginsToClone := self pluginFunctionsToClone) isEmpty ifTrue:
  		[^self].
+ 	aStream cr; nextPutAll: '#if !!defined(SQUEAK_BUILTIN_PLUGIN)'; cr.
- 	aStream cr; nextPutAll: '#if !!defined(SQUEAK_BUILTIN_PLUGIN)'.
  	pluginsToClone do:
  		[:s| | cs |
  		cs := self cFunctionNameFor: s.
  		self withOptionalVerbiageFor: s
  			on: aStream
+ 			do: [aStream tab: anInteger; nextPutAll: cs; nextPutAll: ' = interpreterProxy->'; nextPutAll: cs; nextPut: $;; cr]
- 			do: [aStream crtab: anInteger; nextPutAll: cs; nextPutAll: ' = interpreterProxy->'; nextPutAll: cs; nextPut: $;]
  			ifOptionalDo: [aStream
+ 							nextPutAll: '# if !!defined('; nextPutAll: cs; nextPut: $);
- 							cr; nextPutAll: '# if !!defined('; nextPutAll: cs; nextPut: $);
  							crtab: anInteger; nextPutAll: cs; nextPutAll: ' = 0;';
+ 							cr; nextPutAll: '# endif'; cr]].
+ 	aStream nextPutAll: '#endif /* !!defined(SQUEAK_BUILTIN_PLUGIN) */'.!
- 							cr; nextPutAll: '# endif']].
- 	aStream cr; nextPutAll: '#endif /* !!defined(SQUEAK_BUILTIN_PLUGIN) */'.!

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:
  		[^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.
- 	aStream nextPutAll: '#else /* !!defined(SQUEAK_BUILTIN_PLUGIN) */'.
  	pluginFuncs do:
  		[:tMethod|
  		self withOptionalVerbiageFor: tMethod selector
  			on: aStream
+ 			do: [tMethod static: false; export: false; emitCFunctionPrototype: aStream generator: self]
- 			do: [aStream cr.
- 				tMethod static: false; export: false; emitCFunctionPrototype: aStream generator: self.
- 				aStream nextPut: $;]
  			ifOptionalDo:
+ 				[aStream nextPutAll: '# define '.
- 				[aStream cr; 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!
- 				 aStream nextPutAll: ' 0']].
- 	aStream cr; nextPutAll: 'extern'.
- 	aStream cr; nextPutAll: '#endif'; cr!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>withOptionalVerbiageFor:on:do:ifOptionalDo: (in category 'C translation') -----
  withOptionalVerbiageFor: selector on: aStream do: mainBlock ifOptionalDo: optionalBlock
  	(InterpreterProxy >> selector pragmaAt: #option:)
  		ifNil:
  			[mainBlock value]
  		ifNotNil:
  			[:pragma|
- 			 aStream cr.
  			 self emitIfdefForPluginFunctionOption: pragma arguments first on: aStream.
+ 			 aStream cr.
  			 mainBlock value.
+ 			 aStream nextPutAll: '#else'; cr.
- 			 aStream cr; nextPutAll: '#else'.
  			 optionalBlock value.
+ 			 aStream nextPutAll: '#endif'; cr]!
- 			 aStream cr; nextPutAll: '#endif']!



More information about the Vm-dev mailing list