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

commits at source.squeak.org commits at source.squeak.org
Sun Sep 5 14:18:16 UTC 2021


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

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

Name: VMMaker.oscog-eem.3052
Author: eem
Time: 5 September 2021, 7:18:04.242112 am
UUID: d3f4107c-e267-4a0d-a8f5-a212ea858ee6
Ancestors: VMMaker.oscog-eem.3051

Slang:
Don't generate receiverTagBitsForMethod: in non-Cog VMs.
Neither SPURVM nor SpurMemoryManager are official option: names; SpurObjectMemory is.

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

Item was changed:
  ----- Method: CCodeGenerator>>optionIsFalse:in: (in category 'utilities') -----
  optionIsFalse: key in: aClass
  	"Answer whether a notOption: is false in the context of aClass. The key either a
  	 Cogit class name or a class variable name or a variable name in VMBasicConstants."
  
+ 	"If the option is the name of a subclass of Cogit, include it if it doesn't inherit from the Cogit class."
- 	"If the option is the name of a subclass of Cogit, include it if it dfoesn't inherit from the Cogit class."
  	(Smalltalk classNamed: key) ifNotNil:
  		[:optionClass|
+ 		 vmClass hasCogit
+ 			ifTrue:
+ 				[aClass cogitClass
+ 					ifNotNil:
+ 						[:cogitClass|
+ 						 (optionClass includesBehavior: Cogit) ifTrue:
+ 							[^(cogitClass includesBehavior: optionClass) not]]]
+ 			ifFalse:
+ 				[(optionClass includesBehavior: Cogit) ifTrue:
+ 					[^true]].
- 		 aClass cogitClass ifNotNil:
- 			[:cogitClass|
- 			 (optionClass includesBehavior: Cogit) ifTrue:
- 				[^(cogitClass includesBehavior: optionClass) not]].
  		 aClass objectMemoryClass ifNotNil:
  			[:objectMemoryClass|
  			 ((optionClass includesBehavior: ObjectMemory)
  			   or: [optionClass includesBehavior: SpurMemoryManager]) ifTrue:
  				[^(objectMemoryClass includesBehavior: optionClass) not]]].
  	"Lookup options in options, class variables of the defining class, VMBasicConstants, the interpreterClass and the objectMemoryClass"
  	{aClass initializationOptions.
  	  aClass.
  	  VMBasicConstants.
  	  aClass interpreterClass.
  	  aClass objectMemoryClass} do:
  		[:scopeOrNil|
  		 scopeOrNil ifNotNil:
  			[:scope|
  			 (scope bindingOf: key) ifNotNil:
  				[:binding|
  				binding value ~~ true ifTrue: [^true]]]].
  	^false!

Item was changed:
  ----- Method: CCodeGenerator>>optionIsTrue:in: (in category 'utilities') -----
  optionIsTrue: key in: aClass
  	"Answer whether an option: is true in the context of aClass. The key either a
  	 Cogit class name or a class variable name or a variable name in VMBasicConstants."
  
  	"If the option is the name of a subclass of Cogit, include it if it inherits from the Cogit class."
  	(Smalltalk classNamed: key) ifNotNil:
  		[:optionClass|
+ 		 vmClass hasCogit
+ 			ifTrue:
+ 				[aClass cogitClass
+ 					ifNotNil:
+ 						[:cogitClass|
+ 						 (optionClass includesBehavior: Cogit) ifTrue:
+ 							[^cogitClass includesBehavior: optionClass]]]
+ 			ifFalse:
+ 				[(optionClass includesBehavior: Cogit) ifTrue:
+ 					[^false]].
- 		 aClass cogitClass ifNotNil:
- 			[:cogitClass|
- 			 (optionClass includesBehavior: Cogit) ifTrue:
- 				[^cogitClass includesBehavior: optionClass]].
  		 aClass objectMemoryClass ifNotNil:
  			[:objectMemoryClass|
  			 ((optionClass includesBehavior: ObjectMemory)
  			   or: [optionClass includesBehavior: SpurMemoryManager]) ifTrue:
  				[^objectMemoryClass includesBehavior: optionClass]]].
  	"Lookup options in options, class variables of the defining class, VMBasicConstants, the interpreterClass and the objectMemoryClass"
  	{aClass initializationOptions.
  	  aClass.
  	  VMBasicConstants.
  	  aClass interpreterClass.
  	  aClass objectMemoryClass} do:
  		[:scopeOrNil|
  		 scopeOrNil ifNotNil:
  			[:scope|
  			 (scope bindingOf: key) ifNotNil:
  				[:binding|
  				binding value ~~ false ifTrue: [^true]]]].
  	^false!

Item was changed:
  ----- Method: CoInterpreter>>accessorDepthForExternalPrimitiveMethod: (in category 'plugin primitive support') -----
  accessorDepthForExternalPrimitiveMethod: methodObj
+ 	<option: #SpurObjectMemory>
- 	<option: #SpurMemoryManager>
  	| flags lit |
  	self assert: (self isLinkedExternalPrimitive: methodObj).
  	lit := self literal: 0 ofMethod: methodObj.
  	 flags := objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit.
   	 ^(objectMemory integerValueOf: flags) >>> SpurPrimitiveAccessorDepthShift!

Item was changed:
  ----- Method: FloatArrayPlugin>>primitiveFromFloat64Array (in category 'access primitives') -----
  primitiveFromFloat64Array
  	"Primitive. Set each element of the receiver, a FloatArray with that of the argument, a Float64Array and return the receiver.
  	Note that this conversion might loose bits, or generate overflow.
  	Fail if both have different size"
+ 	<option: #SpurObjectMemory>
  	<export: true flags: #(FastCPrimitiveFlag FastCPrimitiveAlignForFloatsFlag)>
  	| rcvr arg rcvrPtr argPtr length |
- 	<option: #SPURVM>
  	<var: #rcvrPtr type: #'float *'>
  	<var: #argPtr type: #'double *'>
  	arg := interpreterProxy stackValue: 0.
  	rcvr := interpreterProxy stackValue: 1.
  	((interpreterProxy isLong64s: arg)
  	 and: [(interpreterProxy isWords: rcvr)
  	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
  		[^interpreterProxy primitiveFail].
  	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'float *'.
  	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
  	0 to: length-1 do:[:i|
  		rcvrPtr at: i put: (self cCoerce: (argPtr at: i) to: #float)].
  	^interpreterProxy methodReturnReceiver!

Item was changed:
  ----- Method: SpurMemoryManager>>receiverTagBitsForMethod: (in category 'cog jit support') -----
  receiverTagBitsForMethod: aMethodObj
  	"Answer the tag bits for the receiver based on the method's methodClass, if any.
  	 These bits are extended with a bit that says that the method may have a Context receiver, i.e.
  	 mclass is Context or its superclasses.  The absence of this bit is used to avoid expensive store checks, etc."
  	<api>
+ 	<option: #Cogit>
  	| methodClassOrNil classContextOrSuperclass |
  	methodClassOrNil := coInterpreter methodClassOf: aMethodObj.
  	methodClassOrNil = nilObj ifTrue: "If we don't know the methodClass be pessimal"
  		[^self maybeContextMClassTagBits].
  	NewspeakVM "Mixins don't necessarily have a format inst var; filter out non-integer format."
  		ifTrue:
  			[| instSpec |
  			((self isIntegerObject: (instSpec := self fetchPointer: InstanceSpecificationIndex ofObject: methodClassOrNil))
  			 and: [(self instSpecOfClassFormat: (self integerValueOf: instSpec)) = self forwardedFormat]) ifTrue:
  				[^self receiverTagBitsForImmediateMethodClass: methodClassOrNil]]
  		ifFalse:
  			[(self instSpecOfClass: methodClassOrNil) = self forwardedFormat ifTrue:
  				[^self receiverTagBitsForImmediateMethodClass: methodClassOrNil]].
  	"Now check if mclass is one of Context's superclasses..."
  	classContextOrSuperclass := self knownClassAtIndex: ClassMethodContextCompactIndex.
  	[classContextOrSuperclass = methodClassOrNil ifTrue:
  		[^self maybeContextMClassTagBits].
  	 classContextOrSuperclass := self fetchPointer: SuperclassIndex ofObject: classContextOrSuperclass.
  	 classContextOrSuperclass ~= nilObj]
  		whileTrue.
  	^0!



More information about the Vm-dev mailing list