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

commits at source.squeak.org commits at source.squeak.org
Tue Dec 21 21:19:44 UTC 2021


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

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

Name: VMMaker.oscog-eem.3121
Author: eem
Time: 21 December 2021, 1:19:29.560355 pm
UUID: 7f60f66f-6fd0-4b7c-9769-8bac01f93f95
Ancestors: VMMaker.oscog-eem.3120

Fix initialization of the primitive table for in-image compilation and 64-bit Spur.

Add an assert to stop banging one's head against the wall simulating a MULTIPLEBYTECODESETS image with a single bytecode set simulator.

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

Item was added:
+ ----- Method: CArrayAccessor>>withIndexDo: (in category 'enumerating') -----
+ withIndexDo: aBinaryBlock
+ 	self assert: offset = 0.
+ 	object withIndexDo: aBinaryBlock!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacadeFor64BitSpurObjectRepresentation>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'accessing') -----
- functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr
- 	| candidates literal method |
- 	primIndex = PrimNumberExternalCall ifTrue:
- 		[method := self objectForOop: methodOop.
- 		 self assert: method primitive = PrimNumberExternalCall.
- 		 literal := method literalAt: 1.
- 		 candidates := self sn
- 							allImplementorsOf: literal second
- 							localTo: (literal first basicSize = 0
- 										ifTrue: [InterpreterPrimitives]
- 										ifFalse: [InterpreterPlugin allSubclasses
- 													detect: [:pluginClass| pluginClass moduleName = literal first]]).
- 		 self assert: candidates size = 1.
- 		 flagsPtr
- 			at: 0
- 			put: (coInterpreter
- 					primitivePropertyFlagsFor: candidates first compiledMethod
- 					primitiveIndex: primIndex).
- 		 ^self oopForObject: literal second].
- 	^super functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>accessorDepthForPrimitiveMethod: (in category 'accessing') -----
+ accessorDepthForPrimitiveMethod: methodOop
+ 	
+ 	| primIndex |
+ 	primIndex := self primitiveIndexOf: methodOop.
+ 	^primIndex = PrimNumberExternalCall
+ 		ifTrue: [self accessorDepthForExternalPrimitiveMethod: methodOop]
+ 		ifFalse:
+ 			[coInterpreter initializePluginEntries.
+ 			 coInterpreter accessorDepthForPrimitiveIndex: primIndex]!

Item was added:
+ ----- Method: ObjectMemory class>>validateInitializationOptions (in category 'initialization') -----
+ validateInitializationOptions
+ 	"hook for Spur"!

Item was added:
+ ----- Method: Spur32BitMemoryManager class>>validateInitializationOptions (in category 'initialization') -----
+ validateInitializationOptions
+ 	InitializationOptions at: #Spur32BitMemoryManager put: true.
+ 	(InitializationOptions at: #Spur64BitMemoryManager ifAbsent: false) ifTrue:
+ 		[InitializationOptions at: #Spur64BitMemoryManager put: false]!

Item was added:
+ ----- Method: Spur64BitMemoryManager class>>validateInitializationOptions (in category 'initialization') -----
+ validateInitializationOptions
+ 	InitializationOptions at: #Spur64BitMemoryManager put: true.
+ 	(InitializationOptions at: #Spur32BitMemoryManager ifAbsent: false) ifTrue:
+ 		[InitializationOptions at: #Spur32BitMemoryManager put: false]!

Item was changed:
  ----- Method: StackInterpreter class>>primitiveTable (in category 'constants') -----
  primitiveTable
+ 	PrimitiveTable ifNil: [self initializePrimitiveTable].
+ 	^PrimitiveTable!
- 	| cg |
- 	cg := CCodeGenerator new.
- 	cg vmClass: self.
- 	^PrimitiveTable collect:
- 		[:thing|
- 		(thing isInteger "quick prims, 0 for fast primitve fail"
- 		 or: [thing == #primitiveFail])
- 			ifTrue: [thing]
- 			ifFalse:
- 				[(self primitivesClass whichClassIncludesSelector: thing)
- 					ifNil: [#primitiveFail]
- 					ifNotNil:
- 						[:class|
- 						 (cg shouldIncludeMethodFor: class selector: thing)
- 							ifTrue: [thing]
- 							ifFalse: [#primitiveFail]]]]!

Item was changed:
  ----- Method: StackInterpreter>>setMethod: (in category 'internal interpreter access') -----
  setMethod: aMethodObj
  	"Set the method and determine the bytecode set based on the method header's sign.
  	 If MULTIPLEBYTECODESETS then a negative header selects the alternate bytecode set.
  	 Conditionalizing the code on MULTIPLEBYTECODESETS allows the header sign bit to be
  	 used for other experiments."
  	<inline: true>
  	method := aMethodObj.
  	self assert: (objectMemory isOopCompiledMethod: method).
  	self cppIf: MULTIPLEBYTECODESETS
  		ifTrue: [bytecodeSetSelector := (self methodUsesAlternateBytecodeSet: method)
  											ifTrue: [256]
+ 											ifFalse: [0]]
+ 		ifFalse: [self deny: (self methodUsesAlternateBytecodeSet: method)]!
- 											ifFalse: [0]]!

Item was changed:
  ----- Method: StackInterpreter>>setMethod:methodHeader: (in category 'internal interpreter access') -----
  setMethod: aMethodObj methodHeader: methodHeader
  	"Set the method and determine the bytecode set based on the method header's sign.
  	 If MULTIPLEBYTECODESETS then a negative header selects the alternate bytecode set.
  	 Conditionalizing the code on MULTIPLEBYTECODESETS allows the header sign bit to be
  	 used for other experiments."
  	<inline: true>
  	method := aMethodObj.
  	self assert: (objectMemory isOopCompiledMethod: method).
  	self assert: (objectMemory methodHeaderOf: method) = methodHeader.
  	self cppIf: MULTIPLEBYTECODESETS
  		ifTrue: [bytecodeSetSelector := (objectMemory headerIndicatesAlternateBytecodeSet: methodHeader)
  											ifTrue: [256]
+ 											ifFalse: [0]]
+ 		ifFalse: [self deny: (objectMemory headerIndicatesAlternateBytecodeSet: methodHeader)]!
- 											ifFalse: [0]]!

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.
  	 Subclass implementations need to include a super initializeMiscConstants"
  
  	| omc |
  	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
  	SPURVM := STACKVM := COGVM := COGMTVM := false.
  
  	InitializationOptions ifNil: [InitializationOptions := Dictionary new].
  	omc := InitializationOptions at: #ObjectMemory ifAbsent: nil.
  	(omc isNil and: [self defaultObjectMemoryClass notNil]) ifTrue:
  		[omc := InitializationOptions at: #ObjectMemory put: self defaultObjectMemoryClass name].
+ 	omc := omc ifNotNil: [Smalltalk at: omc].
  	InitializationOptions
  		at: #SqueakV3ObjectMemory	"the good ole default"
  			ifAbsentPut: (omc
  					ifNil: [true]
+ 					ifNotNil: [omc includesBehavior: ObjectMemory]);
- 					ifNotNil: [(Smalltalk at: omc) includesBehavior: ObjectMemory]);
  		at: #SpurObjectMemory		"the new contender"
  			ifAbsentPut: (omc
  					ifNil: [false]
+ 					ifNotNil: [omc includesBehavior: SpurMemoryManager]).
+ 	omc validateInitializationOptions. "hack around edge cases"
- 					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].
  	TempVectReadBarrier := InitializationOptions at: #TempVectReadBarrier ifAbsentPut: [false].
  	LowcodeVM := InitializationOptions at: #LowcodeVM ifAbsentPut: [false].
  	MULTIPLEBYTECODESETS := InitializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false].
  	"Simulation only; on by default..."
  	CloneOnGC := InitializationOptions at: #CloneOnGC ifAbsentPut: [true].
  	CloneOnScavenge := InitializationOptions at: #CloneOnScavenge ifAbsentPut: [true].
  
  	"These must be set only if specified, not defaulted, because they are set on the command line or in include files."
  	InitializationOptions
  		at: #VMBIGENDIAN	ifPresent: [:value| VMBIGENDIAN := value];
  		at: #ObjectMemory	ifPresent: [:value| SPURVM := value beginsWith: 'Spur'];
  		at: #STACKVM		ifPresent: [:value| STACKVM := value];
  		at: #COGVM		ifPresent: [:value| COGVM := InitializationOptions at: #COGVM];
  		at: #COGMTVM		ifPresent: [:value| COGMTVM := InitializationOptions at: #COGMTVM].
  
  	"consistency checks"
  	SPURVM
  		ifTrue:
  			[(TempVectReadBarrier not
  			  and: [{SpurMemoryManager compactorClass}, (SpurMemoryManager compactorClass ancilliaryClasses) anySatisfy:
  						[:c| c == SpurSelectiveCompactor]]) ifTrue:
  				[self error: 'Selective compactor requires read barrier']]
  		ifFalse:
  			[TempVectReadBarrier ifTrue: [self error: 'read barrier works with spur VM only...'].
  			 SistaVM ifTrue: [self error: 'Sista VM works with spur VM only...']].
  
  	"And not these; they're compile-time"
  	IMMUTABILITY := InitializationOptions at: #IMMUTABILITY ifAbsent: [SPURVM] "Default as enabled for Spur VMs"!

Item was changed:
  ----- Method: VMClass class>>optionClassNames (in category 'initialization') -----
  optionClassNames
+ 	"Answer the names of all classes that appear in option: pragmas.
+ 	 These have to be set to false before selectively being enabled for
- 	"Answer the names of all classes that appear in opption : pragmas.
- 	 These have to be set to false befpre seelectively being enabled for
  	 the option: pragma to be correctly processed in shouldIncludeMethodForSelector:"
  	| optionClassNames block |
  	optionClassNames := Set new.
  	block :=
  		[:c|
  		c methodsDo:
  			[:m|
  			 (m pragmaAt: #option:) ifNotNil:
  				[:p|
  				 (p arguments first isSymbol
  				  and: [(Smalltalk classNamed: p arguments first) notNil]) ifTrue:
  					[optionClassNames add: p arguments first]]]].
  	InterpreterPrimitives withAllSubclasses do: block.
  	CogObjectRepresentation withAllSubclasses do: block.
  	^optionClassNames!



More information about the Vm-dev mailing list