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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 20 03:12:26 UTC 2016


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

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

Name: VMMaker.oscog-eem.1657
Author: eem
Time: 20 January 2016, 7:10:43.229682 pm
UUID: 1f8ad679-f107-4ef7-94ef-76171db3aa25
Ancestors: VMMaker.oscog-eem.1656

Slang: Make IMMUTABILITY something that is defined on the C compiler command line.

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

Item was changed:
+ ----- Method: InterpreterProxy>>isOopImmutable: (in category 'object access') -----
+ isOopImmutable: oop
+ 	<option: #IMMUTABILITY>
+ 	^StackInterpreter objectMemoryClass isOopImmutable: oop!
- ----- Method: InterpreterProxy>>isOopImmutable: (in category 'testing') -----
- isOopImmutable: anOop
- 	<api>
- 	^self notYetImplementedError!

Item was changed:
  ----- Method: VMClass class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  	"Falsify the `what type of VM is this?' flags that are defined in the various interp.h files,
  	 or in the case of VMBIGENDIAN the various sqConfig.h files.
  	 Subclass implementations need to include a super initializeMiscConstants"
  
  	| omc |
+ 	"VMBIGENDIAN & IMMUTABILITY are intended to be defined on the C compiler command line/in an include file, etc.
+ 	 Don't inline them."
  	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
+ 	IMMUTABILITY class.
+ 
  	self isInterpreterClass ifTrue:
  		[STACKVM := COGVM := COGMTVM := false].
  
  	initializationOptions ifNil: [self initializationOptions: Dictionary new].
  	omc := initializationOptions at: #ObjectMemory ifAbsent: nil.
  	(omc isNil and: [self defaultObjectMemoryClass notNil]) ifTrue:
  		[omc := initializationOptions at: #ObjectMemory put: self defaultObjectMemoryClass name].
  	initializationOptions
  		at: #SqueakV3ObjectMemory	"the good ole default"
  			ifAbsentPut: (omc
  					ifNil: [true]
  					ifNotNil: [(Smalltalk at: omc) includesBehavior: ObjectMemory]);
  		at: #SpurObjectMemory		"the new contender"
  			ifAbsentPut: (omc
  					ifNil: [false]
  					ifNotNil: [(Smalltalk at: omc) includesBehavior: SpurMemoryManager]).
  
  	"Use ifAbsentPut: so that they will get copied back to the
  	 VMMaker's options and dead code will likely be eliminated."
  	PharoVM := initializationOptions at: #PharoVM ifAbsentPut: [false].
  	NewspeakVM := initializationOptions at: #NewspeakVM ifAbsentPut: [false].
  	SistaVM := initializationOptions at: #SistaVM ifAbsentPut: [false].
  	MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false].
- 	"N.B.  Not yet implemented."
- 	IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsentPut: [false].
  
  	"These for scripts etc... Usually they should get set by an Interpreter class's initializeMiscConstantsWith:"
  	(initializationOptions includesKey: #STACKVM) ifTrue:
  		[STACKVM := initializationOptions at: #STACKVM].
  	(initializationOptions includesKey: #COGVM) ifTrue:
  		[COGVM := initializationOptions at: #COGVM].
  	(initializationOptions includesKey: #COGMTVM) ifTrue:
  		[COGMTVM := initializationOptions at: #COGMTVM]!

Item was removed:
- ----- Method: VMMaker class>>generateSqueakSpurStackVMWithImmutability (in category 'configurations') -----
- generateSqueakSpurStackVMWithImmutability
- 	"No primitives since we can use those from the Cog VM"
- 	^VMMaker
- 		generate: StackInterpreter
- 		with: #(ObjectMemory Spur32BitMemoryManager
- 				FailImbalancedPrimitives false
- 				IMMUTABILITY true)
- 		to: (FileDirectory default directoryNamed: self sourceTree, '/spurstacksrc') fullName
- 		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
- 		including: #()!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForCogit:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForCogit: cogitClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  	"Answer the code generator for translating the cogit."
  
  	| cg cogitClasses |
  	cg := self createCogitCodeGenerator.
  
  	cg vmClass: cogitClass.
  	initializeClasses ifTrue:
  		[{ cogitClass. self interpreterClass. self interpreterClass objectMemoryClass } do:
  			[:cgc|
  			(cgc respondsTo: #initializeWithOptions:)
  				ifTrue: [cgc initializeWithOptions: optionsDictionary]
  				ifFalse: [cgc initialize]]].
  
  	cogitClasses := OrderedCollection withAll: (cogitClass withAllSuperclasses copyUpThrough: VMClass) reverse.
  	cogitClasses addAllLast: ((cogitClass ancilliaryClasses: optionsDictionary) reject: [:class| class isStructClass]).
  	cogitClasses do: [:cgc| cg addClass: cgc].
  	cg addStructClasses: (cg structClassesForTranslationClasses: cogitClasses).
  
  	getAPIMethods ifTrue:
  		[cg includeAPIFrom: (self
  								buildCodeGeneratorForInterpreter: self interpreterClass
  								includeAPIMethods: false
  								initializeClasses: false)].
  
+ 	cg
+ 		removeConstant: #VMBIGENDIAN; "this should be defined in platforms/??/vm/sqConfig.h"
+ 		const: #IMMUTABILITY "this can be defined on the C compiler command line."
+ 			declareC: ('#if !!defined(IMMUTABILITY)\/* Allow IMMUTABILITY to be overridden on the compiler command line */\# define IMMUTABILITY ', (cg cLiteralFor: false),'\#endif') withCRs.
- 	cg removeConstant: #VMBIGENDIAN. "this should be defined in platforms/??/vm/sqConfig.h"
  
  	^cg!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForInterpreter:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForInterpreter: interpreterClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  	"Answer the code generator for translating the interpreter."
  
  	| cg interpreterClasses |
  	initializeClasses ifTrue:
  		[interpreterClass initializeWithOptions: optionsDictionary.
  		 interpreterClass hasCogit ifTrue:
  			[interpreterClass cogitClass initializeWithOptions: optionsDictionary]].
  
  	(cg := self createCodeGenerator) vmClass: interpreterClass.
  
  	"Construct interpreterClasses as all classes from interpreterClass &
  	 objectMemoryClass up to VMClass in superclass to subclass order."
  	interpreterClasses := OrderedCollection new.
  	{interpreterClass. interpreterClass objectMemoryClass} do:
  		[:vmClass| | theClass |
  		 theClass := vmClass.
  		 [theClass ~~ VMClass] whileTrue:
  			[interpreterClasses addFirst: theClass.
  			 theClass := theClass superclass]].
  	interpreterClasses
  		addFirst: VMClass;
  		addAllLast: (cg nonStructClassesForTranslationClasses: interpreterClasses).
  
  	initializeClasses ifTrue:
  		[interpreterClasses do:
  			[:ic|
  			(ic respondsTo: #initializeWithOptions:)
  				ifTrue: [ic initializeWithOptions: optionsDictionary]
  				ifFalse: [ic initialize]].
  		 (cg structClassesForTranslationClasses: interpreterClasses) do:
  			[:structClass| structClass initialize]].
  
  	cg addStructClasses: (cg structClassesForTranslationClasses: interpreterClasses).
  
  	interpreterClasses do: [:ic| cg addClass: ic].
  
  	getAPIMethods ifTrue:
  		[interpreterClass cogitClass ifNotNil:
  			[:cogitClass|
  			 cg includeAPIFrom: (self
  									buildCodeGeneratorForCogit: cogitClass
  									includeAPIMethods: false
  									initializeClasses: false)]].
  
+ 	cg removeConstant: #VMBIGENDIAN; "this should be defined in platforms/??/vm/sqConfig.h"
+ 		const: #IMMUTABILITY "this can be defined on the C compiler command line."
+ 			declareC: ('#if !!defined(IMMUTABILITY)\/* Allow IMMUTABILITY to be overridden on the compiler command line */\# define IMMUTABILITY ', (cg cLiteralFor: false),'\#endif') withCRs.
- 	cg removeConstant: #VMBIGENDIAN. "this should be defined in platforms/??/vm/sqConfig.h"
  
  	^cg!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>emitIfdefForPluginFunctionOption:on: (in category 'C translation') -----
+ emitIfdefForPluginFunctionOption: anArrayOrSymbol on: aStream
+ 	"See e.g. senders of atLeastVMProxyMajor:minor: or <option: #IMMUTABLITY>
+ 	 in InterpreterProxy"
+ 	aStream nextPutAll: '#if '; nextPutAll: (anArrayOrSymbol isSymbol
+ 											ifTrue: [anArrayOrSymbol]
+ 											ifFalse: [self perform: anArrayOrSymbol first
+ 														withArguments: anArrayOrSymbol allButFirst])!
- emitIfdefForPluginFunctionOption: anArray on: aStream 
- 	aStream nextPutAll: '#if '; nextPutAll: (self perform: anArray first withArguments: anArray allButFirst)!

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



More information about the Vm-dev mailing list