[Vm-dev] VM Maker: VMMaker.oscog-EstebanLorenzano.1675.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Feb 2 11:54:39 UTC 2016


Esteban Lorenzano uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-EstebanLorenzano.1675.mcz

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

Name: VMMaker.oscog-EstebanLorenzano.1675
Author: EstebanLorenzano
Time: 2 February 2016, 12:51:45.901817 pm
UUID: 1ffd58e1-613f-4809-97aa-126f6b63ac17
Ancestors: VMMaker.oscog-eem.1674

fix optional output for declarations. 
Rational for this change:  with the introduction of IMMUTABILITY flag IA21ABI plugin needs to be generated with an optional flag. When compiled as external, this plugin creates this structure: 

#if IMMUTABILITY
	isOopImmutable = interpreterProxy->isOopImmutable;
#else
	#if !defined(isOopImmutable)
		isOopImmutable = 0;
	#endif
#endif

which at least for CLANG is bad, because it tries to excute a function who points to NULL.
This change fixes that behaviour, while preserving correct generation when plugin is internal.

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

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)'.
  	pluginsToClone do:
  		[:s| | cs |
  		cs := self cFunctionNameFor: s.
  		self withOptionalVerbiageFor: s
  			on: aStream
+ 			do: [aStream crtab: anInteger; nextPutAll: cs; nextPutAll: ' = interpreterProxy->'; nextPutAll: cs; nextPut: $;]].
- 			do: [aStream crtab: anInteger; nextPutAll: cs; nextPutAll: ' = interpreterProxy->'; nextPutAll: cs; nextPut: $;]
- 			ifOptionalDo: [aStream
- 							cr; nextPutAll: '# if !!defined('; nextPutAll: cs; nextPut: $);
- 							crtab: anInteger; nextPutAll: cs; nextPutAll: ' = 0;';
- 							cr; nextPutAll: '# endif']].
  	aStream cr; nextPutAll: '#endif /* !!defined(SQUEAK_BUILTIN_PLUGIN) */'.!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>preDeclareExternFunction:on: (in category 'C code generator') -----
+ preDeclareExternFunction: tMethod on: aStream
+ 	self withOptionalVerbiageFor: tMethod selector
+ 		on: aStream
+ 		do: [aStream cr.
+ 			tMethod static: false; export: false; emitCFunctionPrototype: aStream generator: self.
+ 			aStream nextPut: $;]
+ 		ifOptionalDo:
+ 			[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']	!

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

Item was added:
+ ----- Method: VMPluginCodeGenerator>>preDeclareStaticFunction:on: (in category 'C code generator') -----
+ preDeclareStaticFunction: tMethod on: aStream
+ 	| functionName |
+ 	functionName := self cFunctionNameFor: tMethod selector.
+ 	self withOptionalVerbiageFor: tMethod selector
+ 		on: aStream
+ 		do: 
+ 			[aStream cr; nextPutAll:
+ 				((String streamContents: 
+ 					[:s|
+ 						tMethod
+ 							static: true;
+ 							emitCFunctionPrototype: s generator: self])
+ 					copyReplaceAll: functionName
+ 					with: '(*', functionName, ')'
+ 					tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]]).
+ 			aStream nextPut: $;]
+ 		ifOptionalDo: [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'].	
+ !

Item was added:
+ ----- Method: VMPluginCodeGenerator>>withOptionalVerbiageFor:on:do: (in category 'C translation') -----
+ withOptionalVerbiageFor: selector on: aStream do: mainBlock
+ 	^ self 
+ 		withOptionalVerbiageFor: selector 
+ 		on: aStream 
+ 		do: mainBlock 
+ 		ifOptionalDo: nil		!

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.
  			 mainBlock value.
+ 			 optionalBlock ifNotNil: 
+ 				[aStream cr; nextPutAll: '#else'.
+ 			 	 optionalBlock value].
- 			 aStream cr; nextPutAll: '#else'.
- 			 optionalBlock value.
  			 aStream cr; nextPutAll: '#endif']!



More information about the Vm-dev mailing list