[Vm-dev] VM Maker: VMMaker.oscog-tpr.1544.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Dec 3 19:44:48 UTC 2015


tim Rowledge uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-tpr.1544.mcz

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

Name: VMMaker.oscog-tpr.1544
Author: tpr
Time: 3 December 2015, 11:43:44.105 am
UUID: 22ab52d9-be46-4ff2-b6d8-c0fe0b7a3032
Ancestors: VMMaker.oscog-eem.1543

A few changes to make building the Balloon3D plugin work ok for both cog and trunk vmmaker.
Since the pluginClassesUptO: & buildCodegeneratorUpTo: were simply ignoringthe argument, stop bothering to send it. Left a stub version in case other plugin code uses it, with a depracation warning.
Builds a vm that compiles and runs on Pi

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

Item was changed:
  ----- Method: InterpreterPlugin class>>allCodeOlderThan: (in category 'translation') -----
  allCodeOlderThan: modificationTime
+ 	^((self pluginClassesUpToRoot) allSatisfy:
- 	^((self pluginClassesUpTo: self) allSatisfy:
  			[:aPluginClass| aPluginClass timeStamp < modificationTime])
  	  and: [self translatedPrimitives allSatisfy:
  			[:pair| | c m stamp |
  			c := Smalltalk classNamed: pair first.
  			m := c compiledMethodAt: pair last ifAbsent: [c class >> pair last].
  			stamp := (m timeStamp subStrings: {Character space}) last: 2.
  			stamp := TimeStamp date: (Date fromString: stamp first) time: (Time fromString: stamp last).
  			stamp asSeconds < modificationTime]]!

Item was added:
+ ----- Method: InterpreterPlugin class>>buildCodeGenerator (in category 'translation') -----
+ buildCodeGenerator
+ 	"Build a CCodeGenerator for the plugin"
+ 	| cg pluginClasses |
+ 	cg := self codeGeneratorClass new initialize.
+ 	cg pluginClass: self.
+ 	(pluginClasses := self pluginClassesUpToRoot) do:
+ 		[:aClass| cg addClass: aClass].
+ 	(cg structClassesForTranslationClasses: pluginClasses) do:
+ 		[:structClasss| cg addStructClass: structClasss].
+ 	cg addMethodsForTranslatedPrimitives: self translatedPrimitives.
+ 	^cg!

Item was changed:
  ----- Method: InterpreterPlugin class>>buildCodeGeneratorUpTo: (in category 'translation') -----
  buildCodeGeneratorUpTo: aPluginClass
+ 	"Build a CCodeGenerator for the plugin - Deprecated and here only in case old plugin code tries to use it"
+ 	self deprecated.
+ 	^self buildCodeGenerator!
- 	"Build a CCodeGenerator for the plugin"
- 	| cg pluginClasses |
- 	cg := self codeGeneratorClass new initialize.
- 	cg pluginClass: self.
- 	(pluginClasses := self pluginClassesUpTo: aPluginClass) do:
- 		[:aClass| cg addClass: aClass].
- 	(cg structClassesForTranslationClasses: pluginClasses) do:
- 		[:structClasss| cg addStructClass: structClasss].
- 	cg addMethodsForTranslatedPrimitives: self translatedPrimitives.
- 	^cg!

Item was added:
+ ----- Method: InterpreterPlugin class>>moduleFileName (in category 'translation') -----
+ moduleFileName
+ 	"Answer the receiver's module name that is used for the plugin's C code."
+ 
+ 	^ self moduleName, self moduleExtension!

Item was removed:
- ----- Method: InterpreterPlugin class>>pluginClassesUpTo: (in category 'translation') -----
- pluginClassesUpTo: aPluginClass
- 	"Answer the classes to include for translation of aPluginClass, superclasses first, aPluginClass last."
- 	| theClass classes |
- 
- 	classes := OrderedCollection new.
- 	theClass := self.
- 	[theClass == Object
- 	 or: [theClass == VMClass]] whileFalse:
- 		[classes addLast: theClass.
- 		theClass := theClass superclass].
- 	^classes reverse!

Item was added:
+ ----- Method: InterpreterPlugin class>>pluginClassesUpToRoot (in category 'translation') -----
+ pluginClassesUpToRoot
+ 	"Answer the classes to include for translation of aPluginClass, superclasses first, and the root (VMClass in general, possibly Object)  last."
+ 	| theClass classes |
+ 
+ 	classes := OrderedCollection new.
+ 	theClass := self.
+ 	[theClass == Object
+ 	 or: [theClass == VMClass]] whileFalse:
+ 		[classes addLast: theClass.
+ 		theClass := theClass superclass].
+ 	^classes reverse!

Item was changed:
  ----- Method: InterpreterPlugin class>>translateInDirectory:doInlining: (in category 'translation') -----
  translateInDirectory: directory doInlining: inlineFlag
  "This is the default method for writing out sources for a plugin. Several classes need special handling, so look at all implementors of this message"
  	| cg fname |
  	 fname := self moduleName, '.c'.
  
  	"don't translate if the file is newer than my timeStamp"
  	(directory entryAt: fname ifAbsent: nil) ifNotNil:
  		[:fstat| | mTime |
  		mTime := fstat modificationTime.
  		mTime isInteger ifFalse: [mTime := mTime asSeconds].
  		 (self allCodeOlderThan: mTime) ifTrue:
  			[^nil]].
  
  	self initialize.
+ 	cg := self buildCodeGenerator.
- 	cg := self buildCodeGeneratorUpTo: self.
  	cg inferTypesForImplicitlyTypedVariablesAndMethods.
  	self pruneUnusedInterpreterPluginMethodsIn: cg.
  	cg storeCodeOnFile:  (directory fullNameFor: fname) doInlining: inlineFlag.
  	^cg exportedPrimitiveNames asArray!

Item was changed:
  ----- Method: StackInterpreter>>tryLoadNewPlugin:pluginEntries: (in category 'primitive support') -----
  tryLoadNewPlugin: pluginString pluginEntries: pluginEntries
  	"Load the plugin and if on Spur, populate pluginEntries with the prmitives in the plugin."
  	<doNotGenerate>
  	| plugin realPluginClass plugins simulatorClasses |
  	self transcript cr; show: 'Looking for module ', pluginString.
  	"Defeat loading of the FloatArrayPlugin & Matrix2x3Plugin since complications with 32-bit
  	 float support prevent simulation.  If you feel up to tackling this start by implementing
  		cCoerce: value to: cType
  			^cType = 'float'
  				ifTrue: [value asIEEE32BitWord]
  				ifFalse: [value]
  	 in FloatArrayPlugin & Matrix2x3Plugin and then address the issues in the BalloonEnginePlugin.
  	 See http://forum.world.st/Simulating-the-BalloonEnginePlugin-FloatArrayPlugin-amp-Matrix2x3Plugin-primitives-td4734673.html"
  	(#('FloatArrayPlugin' 'Matrix2x3Plugin') includes: pluginString) ifTrue:
  		[self transcript show: ' ... defeated'. ^nil].
  	pluginString isEmpty
  		ifTrue:
  			[plugin := self]
  		ifFalse:
  			[plugins := InterpreterPlugin allSubclasses select: [:psc| psc moduleName asString = pluginString asString].
  			simulatorClasses := (plugins
  									select: [:psc| psc simulatorClass notNil]
  									thenCollect: [:psc| psc simulatorClass]) asSet.
  			simulatorClasses isEmpty ifTrue: [self transcript show: ' ... not found'. ^nil].
  			simulatorClasses size > 1 ifTrue: [^self error: 'This won''t work...'].
  			(plugins copyWithoutAll: simulatorClasses) notEmpty ifTrue:
  				[plugins := plugins copyWithoutAll: simulatorClasses].
  			plugins size > 1 ifTrue:
  				[self transcript show: '...multiple plugin classes; choosing ', plugins last name].
  			realPluginClass := plugins last. "hopefully lowest in the hierarchy..."
  			plugin := simulatorClasses anyOne newFor: realPluginClass.
  			plugin setInterpreter: objectMemory. "Ignore return value from setInterpreter"
  			(plugin respondsTo: #initialiseModule) ifTrue:
  				[plugin initialiseModule ifFalse:
  					[self transcript show: ' ... initialiser failed'. ^nil]]]. "module initialiser failed"
  	self transcript show: ' ... loaded'.
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[| realPlugin cg |
  		 self transcript show: '...computing accessor depths'.
  		 plugin class isPluginClass
  			ifTrue:
  				[realPlugin := (plugin isSmartSyntaxPluginSimulator
  									ifTrue: [realPluginClass]
  									ifFalse: [plugin class])
  								 withAllSuperclasses detect: [:class| class shouldBeTranslated].
+ 				 cg := realPlugin buildCodeGenerator]
- 				 cg := realPlugin buildCodeGeneratorUpTo: realPlugin]
  			ifFalse:
  				[cg := self codeGeneratorToComputeAccessorDepth.
  				 primitiveTable withIndexDo:
  					[:prim :index| | depth |
  					 prim isSymbol ifTrue:
  						[depth := cg accessorDepthForSelector: prim.
  						 self assert: (depth isInteger or: [depth isNil and: [(plugin class whichClassIncludesSelector: prim) isNil]]).
  						 primitiveAccessorDepthTable at: index - 1 put: depth]]].
  		 cg exportedPrimitiveNames do:
  			[:primName| | fnSymbol |
  			 fnSymbol := primName asSymbol.
  			 pluginEntries addLast: {plugin.
  									fnSymbol.
  									[plugin perform: fnSymbol. self].
  									cg accessorDepthForSelector: fnSymbol}].
  		 self transcript show: '...done'].
  	^pluginString asString -> plugin!

Item was changed:
  ----- Method: SurfacePlugin class>>translateInDirectory:doInlining: (in category 'translation') -----
  translateInDirectory: directory doInlining: inlineFlag
  "handle a special case external file rather than normal generated code."
  	| cg |
  	self initialize.
  
+ 	cg := self buildCodeGenerator.
- 	cg := self buildCodeGeneratorUpTo: self.
  
  	"We rely on the fake entry points implemented on the instance side to allow the export list to be accurate. Please update them if you change the code"
  	^cg exportedPrimitiveNames asArray!



More information about the Vm-dev mailing list