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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 24 17:17:57 UTC 2016


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

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

Name: VMMaker.oscog-eem.1699
Author: eem
Time: 24 February 2016, 9:16:10.818176 am
UUID: 186ebd51-28ef-4e7f-8411-96b61577b777
Ancestors: VMMaker.oscog-eem.1698

Allow a plugin to override moduleName in generating its export table, via moduleExportsName.

To this end eliminate the pluginName variable from VMPluginCodeGenerator and use pluginClass moduleName instead.

Also use a shared variable to hold the moduleExportsName in the gnerated source.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitExportsNamed:pluginName:on: (in category 'C code generator') -----
  emitExportsNamed: exportsNamePrefix pluginName: pluginName on: aStream
  	"Store all the exported primitives in the form used by the internal named prim system."
  	| nilVMClass excludeDepth |
  	(nilVMClass := vmClass isNil) ifTrue: "We need a vmClass temporarily to compute accessor depths."
  		[vmClass := StackInterpreter].
  	"Don't include the depth in the vm's named primitives if the vm is non-Spur."
  	excludeDepth := exportsNamePrefix = 'vm'
  					  and: [pluginName isEmpty
  					  and: [vmClass objectMemoryClass hasSpurMemoryManagerAPI not]].
+ 	aStream cr; cr; nextPutAll: 'static char _m[] = "'; nextPutAll: pluginName; nextPutAll: '";'.
+ 	aStream cr; nextPutAll: 'void* '; nextPutAll: exportsNamePrefix; nextPutAll: '_exports[][3] = {'; cr.
- 	aStream cr; cr; nextPutAll: 'void* '; nextPutAll: exportsNamePrefix; nextPutAll: '_exports[][3] = {'; cr.
  	((methods select: [:m| m export]) asSortedCollection: [:a :b| a selector caseSensitiveLessOrEqual: b selector]) do:
  		[:method| | compileTimeOptionPragmas primName |
  		(compileTimeOptionPragmas := method compileTimeOptionPragmas) notEmpty ifTrue:
  			[method outputConditionalDefineFor: compileTimeOptionPragmas on: aStream].
  		 primName := self cFunctionNameFor: method selector.
+ 		 aStream tab; nextPutAll: '{(void*)_m, "'; nextPutAll: primName.
- 		 aStream tab; nextPutAll: '{"'; nextPutAll: pluginName; nextPutAll: '", "'; nextPutAll: primName.
  		 excludeDepth ifFalse:
  			[(self accessorDepthForSelector: primName asSymbol) ifNotNil:
  				[:depth| "store the accessor depth in a hidden byte immediately after the primName"
  				self assert: depth < 128.
  				aStream
  					nextPutAll: '\000\';
  					nextPutAll: ((depth bitAnd: 255) printStringBase: 8 nDigits: 3)]].
  		 aStream nextPutAll: '", (void*)'; nextPutAll: primName; nextPutAll: '},'; cr.
  		 method terminateConditionalDefineFor: compileTimeOptionPragmas on: aStream].
  	aStream tab; nextPutAll: '{NULL, NULL, NULL}'; cr; nextPutAll: '};'; cr.
  	nilVMClass ifTrue:
  		[vmClass := nil]!

Item was added:
+ ----- Method: InterpreterPlugin class>>moduleExportsName (in category 'translation') -----
+ moduleExportsName
+ 	"Answer the name to include in receiver's internal plugin exports.
+ 	 This is the value of the module: argument in named primitives.
+ 	 By default answer the moduleName."
+ 
+ 	^self moduleName!

Item was changed:
  ----- Method: SimulatorEventTransformer>>degenerateMouseEvent:for: (in category 'event transformation') -----
  degenerateMouseEvent: aMorphicEvent for: aClient
  	"Convert the mouse event into low-level events for the VM simulator (aClient).  Filter-out mouse moves,
  	 and generate a fake mouse move before each button press.
  	 See HandMorph>>generateMouseEvent"
  	| translated |
  	translated := aMorphicEvent position - aClient displayView bounds origin.
  	modifiers := aMorphicEvent buttons >> 3. "Sad, but modifiers come in on mouse move events..."
  
  	aMorphicEvent type == #mouseMove
+ 		ifTrue: "filter-out mouse moves unless buttons are pressed, so simulation doesn't get window leave events when we leave its window"
- 		ifTrue: "filter-out mouse moves unless buttons are pressed, so simulation doersn't get window leave events when we leave its window"
  			[buttons = 0 ifTrue: [^nil]]
  		ifFalse:"If the buttons are going down, make sure to add a mouse move event to the current position before the buttons are pressed."
  			[((buttons bitAnd: 7) = 0 and: [(aMorphicEvent buttons bitAnd: 7) ~= 0]) ifTrue:
  				[aClient queueForwardedEvent:
  							{	1.
  								aMorphicEvent timeStamp.
  								translated x.
  								translated y.
  								0.
  								buttons >> 3.     "Thanks dtl"
  								0.
  								self windowIndex }].
  				 buttons := aMorphicEvent buttons].
  	aClient queueForwardedEvent:
  			{	1.
  				aMorphicEvent timeStamp.
  				translated x.
  				translated y.
  				buttons bitAnd: 7.  "thanks Ron T."
  				buttons >> 3.     "Thanks dtl"
  				0.
  				self windowIndex }!

Item was added:
+ ----- Method: ThreadedFFIPlugin class>>moduleExportsName (in category 'translation') -----
+ moduleExportsName
+ 	"To make the inclusion of the platform-specific plugin to work it can't use
+ 	 its moduleName in the exports but must use the proper moduleName."
+ 
+ 	^ThreadedFFIPlugin moduleName!

Item was changed:
  CCodeGenerator subclass: #VMPluginCodeGenerator
+ 	instanceVariableNames: 'pluginClass pluginFunctionsUsed inProgressSelectors inliningDone'
- 	instanceVariableNames: 'pluginClass pluginName pluginFunctionsUsed inProgressSelectors inliningDone'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Translation to C'!
  
  !VMPluginCodeGenerator commentStamp: '<historical>' prior: 0!
  I generate code that can be loaded dynamically from external libraries (e.g., DSOs on Unix or DLLs on Windows)!

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: pluginClass moduleName
+ 		pluginName: pluginClass moduleExportsName
+ 		on: aStream.
- 	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>>pluginClass: (in category 'public') -----
  pluginClass: aPluginClass
  	"Set the plugin class and name when generating plugins.
  	 And for run-time use, answer the name string."
  	| packageId |
  	pluginClass := aPluginClass.
- 	pluginName := pluginClass moduleName.
  	packageId := self shortMonticelloDescriptionForClass: pluginClass.
  	(packageId beginsWith: pluginClass name) ifTrue:
  		[packageId := packageId allButFirst: pluginClass name size].
+ 	(packageId beginsWith: pluginClass moduleName) ifTrue:
+ 		[packageId := packageId allButFirst: pluginClass moduleName size].
- 	(packageId beginsWith: pluginName) ifTrue:
- 		[packageId := packageId allButFirst: pluginName size].
  	^self declareModuleName: pluginClass moduleNameAndVersion, packageId!

Item was removed:
- ----- Method: VMPluginCodeGenerator>>pluginName: (in category 'public') -----
- pluginName: aString
- "TPR - moved from CCodeGenerator"
- 	"Set the plugin name when generating plugins."
- 	pluginName := aString.!



More information about the Vm-dev mailing list