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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 23 00:53:27 UTC 2017


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

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

Name: VMMaker.oscog-eem.2264
Author: eem
Time: 22 August 2017, 5:52:20.489903 pm
UUID: 9708118d-160d-4940-8282-8801b300c3bf
Ancestors: VMMaker.oscog-eem.2263

Spur:
The OmterpreterProxy/sqVirtualMachine.h API (e.g. in the ThreadedFFIPlugin) expects instantiateClass:indexableSize: to work with 0 indexable size for fixed classes.  So remove the cppIf:... from the Spur implementation.

ObjectMemory:
Eliminate the header2 variable in a few routines.  It is always the same as classPointer.

General:
If ioScreenSize answers a zero screen extent (as is the case for headless images) then on snapshot write the sawvedWindowSize rather thna the zero extent.  This should fix the experience people have with Pharo of saving headless images that then come up with a zero sized window when started headful.

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

Item was changed:
  ----- Method: ObjectMemory>>instantiateClass:indexableSize: (in category 'interpreter access') -----
  instantiateClass: classPointer indexableSize: size
  	"NOTE: This method supports the backward-compatible split instSize field of the 
  	class format word. The sizeHiBits will go away and other shifts change by 2 
  	when the split fields get merged in an (incompatible) image change."
  	<api>
+ 	| hash header1 cClass byteSize format binc header3 hdrSize sizeHiBits bm1 classFormat |
- 	| hash header1 header2 cClass byteSize format binc header3 hdrSize sizeHiBits bm1 classFormat |
  	<inline: false>
  	self assert: size >= 0. "'cannot have a negative indexable field count"
  	hash := self newObjectHash.
  	classFormat := self formatOfClass: classPointer.
  	"Low 2 bits are 0"
  	header1 := (classFormat bitAnd: 16r1FF00) bitOr: (hash bitAnd: HashMaskUnshifted) << HashBitsOffset.
- 	header2 := classPointer.
  	sizeHiBits := (classFormat bitAnd: 16r60000) >> 9.
  	cClass := header1 bitAnd: CompactClassMask. "compact class field from format word"
  	byteSize := (classFormat bitAnd: SizeMask + Size4Bit) + sizeHiBits.
  		"size in bytes -- low 2 bits are 0"
  	"Note this byteSize comes from the format word of the class which is pre-shifted
  		to 4 bytes per field.  Need another shift for 8 bytes per word..."
  	byteSize := byteSize << (self shiftForWord-2).
  	format := self formatOfHeader: classFormat.
  	self flag: #sizeLowBits.
  	format < self firstByteFormat
  		ifTrue:
  			[format = self firstLongFormat
  				ifTrue: "long32 bitmaps"
  					[bm1 := self wordSize-1.
  					byteSize := byteSize + (size * 4) + bm1 bitAnd: LongSizeMask. "round up"
  					binc := bm1 - ((size * 4) + bm1 bitAnd: bm1). "odd bytes"
  					"extra low bit (4) for 64-bit VM goes in 4-bit (betw hdr bits and sizeBits)"
  					header1 := header1 bitOr: (binc bitAnd: 4)]
  				ifFalse: "Arrays and 64-bit bitmaps"
  					[byteSize := byteSize + (size * self wordSize)]]
  		ifFalse:
  			["Strings and Methods"
  			bm1 := self wordSize-1.
  			byteSize := byteSize + size + bm1 bitAnd: LongSizeMask. "round up"
  			binc := bm1 - (size + bm1 bitAnd: bm1). "odd bytes"
  			"low bits of byte size go in format field"
  			header1 := header1 bitOr: (binc bitAnd: 3) << self instFormatFieldLSB.
  			"extra low bit (4) for 64-bit VM goes in 4-bit (betw hdr bits and sizeBits)"
  			header1 := header1 bitOr: (binc bitAnd: 4)].
  	byteSize > 255 "requires size header word/full header"
  		ifTrue: [header3 := byteSize. hdrSize := 3]
  		ifFalse: [header1 := header1 bitOr: byteSize. hdrSize := cClass = 0 ifTrue: [2] ifFalse: [1]].
+ 	^self allocate: byteSize headerSize: hdrSize h1: header1 h2: classPointer h3: header3 doFill: true format: format!
- 	^self allocate: byteSize headerSize: hdrSize h1: header1 h2: header2 h3: header3 doFill: true format: format!

Item was changed:
  ----- Method: ObjectMemory>>instantiateContext:sizeInBytes: (in category 'interpreter access') -----
  instantiateContext: classPointer sizeInBytes: sizeInBytes 
  	"This version of instantiateClass assumes that the total object 
  	size is under 256 bytes, the limit for objects with only one or 
  	two header words. Note that the size is specified in bytes 
  	and should include four bytes for the base header word."
+ 	| hash header1 hdrSize |
- 	| hash header1 header2 hdrSize |
  	hash := self newObjectHash.
  	header1 := (hash bitAnd: HashMaskUnshifted) << HashBitsOffset bitOr: (self formatOfClass: classPointer).
- 	header2 := classPointer.
  	(header1 bitAnd: CompactClassMask) > 0 "are contexts compact?"
  		ifTrue: [hdrSize := 1]
  		ifFalse: [hdrSize := 2].
  	sizeInBytes <= SizeMask
  		ifTrue: ["OR size into header1.  Must not do this if size > SizeMask"
  				header1 := header1 + (sizeInBytes - (header1 bitAnd: SizeMask))]
  		ifFalse: [hdrSize := 3.
  				"Zero the size field of header1 if large"
  				header1 := header1 - (header1 bitAnd: SizeMask)].
+ 	^self allocate: sizeInBytes headerSize: hdrSize h1: header1 h2: classPointer h3: LargeContextSize doFill: false format: 0 "ignored cuz doFill: is false"!
- self flag: #Dan.  "Check details of context sizes"
- 	^ self allocate: sizeInBytes headerSize: hdrSize h1: header1 h2: header2 h3: LargeContextSize doFill: false format: 0!

Item was changed:
  ----- Method: ObjectMemory>>instantiateSmallClass:sizeInBytes: (in category 'interpreter access') -----
  instantiateSmallClass: classPointer sizeInBytes: sizeInBytes
  	"This version of instantiateClass assumes that the total object 
  	size is under 256 bytes, the limit for objects with only one or 
  	two header words. Note that the size is specified in bytes 
  	and should include 4 or 8 bytes for the base header word. 
  	NOTE this code will only work for sizes that are an integral number of words
  		(like not a 32-bit LargeInteger in a 64-bit system). 
  	May cause a GC.
+ 	Note that the created small object IS NOT FILLED and must be completed before
+ 	returning it to Squeak. Since this call is used in routines that do just that we are safe.
+ 	Break this rule and die."
- 	Note that the created small object IS NOT FILLED and must be completed before returning it to Squeak. Since this call is used in routines that do jsut that we are safe. Break this rule and die."
  
+ 	| hash header1 hdrSize |
- 	| hash header1 header2 hdrSize |
  	(sizeInBytes bitAnd: (self wordSize-1)) = 0 ifFalse:
  		[self error: 'size must be integral number of words'].
  	hash := self newObjectHash.
  	header1 := (hash bitAnd: HashMaskUnshifted) << HashBitsOffset bitOr: (self formatOfClass: classPointer).
- 	header2 := classPointer.
  	hdrSize := (header1 bitAnd: CompactClassMask) > 0 "is this a compact class"
  				ifTrue: [1]
  				ifFalse: [2].
  	header1 := header1 + (sizeInBytes - (header1 bitAnd: SizeMask+Size4Bit)).
+ 	^self allocate: sizeInBytes headerSize: hdrSize h1: header1 h2: classPointer h3: 0 doFill: false format: 0 "ignored cuz doFill: is false"!
- 	^ self allocate: sizeInBytes headerSize: hdrSize h1: header1 h2: header2 h3: 0 doFill: false format: 0!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>instantiateClass:indexableSize: (in category 'instantiation') -----
  instantiateClass: classObj indexableSize: nElements
  	<api>
  	<var: #nElements type: #usqInt>
  	"Allocate an instance of a variable class, excepting CompiledMethod."
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	classIndex := self rawHashBitsOf: classObj.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self weakArrayFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[nElements > (self maxSlotsForAlloc / 2) ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrUnsupported.
  				 ^nil].
  			 numSlots := nElements * 2].
  		[self firstLongFormat]	->
  			[(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrBadReceiver.
  				 ^nil].
  			 numSlots := nElements].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (4 - nElements bitAnd: 3)] }
  		otherwise: "non-indexable"
+ 			["Some Squeak images include funky fixed subclasses of abstract variable
+ 			  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
+ 			  The (Threaded)FFIPlugin expects to be able to instantiate ExternalData via
+ 			  this method.
+ 			  Hence allow fixed classes to be instantiated here iff nElements = 0."
+ 			 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
+ 				[^nil].
+ 			 numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 			 fillValue := nilObj].
- 			[self cppIf: (PharoVM or: [true]) "Leave the old code but ignore it completely unless someone complains."
- 				ifTrue:
- 					[^nil]
- 				ifFalse:
- 					["some Squeak images include funky fixed subclasses of abstract variable
- 					  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
- 					  Allow fixed classes to be instantiated here iff nElements = 0."
- 					 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
- 						[^nil].
- 					 numSlots := self fixedFieldsOfClassFormat: classFormat.
- 					 fillValue := nilObj]].
  	classIndex = 0 ifTrue:
  		[classIndex := self ensureBehaviorHash: classObj.
  		 classIndex < 0 ifTrue:
  			[coInterpreter primitiveFailFor: classIndex negated.
  			 ^nil]].
  	numSlots > self maxSlotsForNewSpaceAlloc
  		ifTrue:
  			[numSlots > self maxSlotsForAlloc ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrUnsupported.
  				 ^nil].
  			 newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]
  		ifFalse:
  			[newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].
  	newObj ifNotNil:
  		[self fillObj: newObj numSlots: numSlots with: fillValue].
  	^newObj!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>instantiateClass:indexableSize: (in category 'instantiation') -----
  instantiateClass: classObj indexableSize: nElements
  	<api>
  	<var: #nElements type: #usqInt>
  	"Allocate an instance of a variable class, excepting CompiledMethod."
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	classIndex := self rawHashBitsOf: classObj.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self weakArrayFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[numSlots := nElements].
  		[self firstLongFormat]	->
  			[(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrBadReceiver.
  				 ^nil].
  			 numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (4 - nElements bitAnd: 3)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 7 // 8.
  			 instSpec := instSpec + (8 - nElements bitAnd: 7)] }
  		otherwise: "non-indexable"
+ 			["Some Squeak images include funky fixed subclasses of abstract variable
+ 			  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
+ 			  The (Threaded)FFIPlugin expects to be able to instantiate ExternalData via
+ 			  this method.
+ 			  Hence allow fixed classes to be instantiated here iff nElements = 0."
+ 			 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
+ 				[^nil].
+ 			 numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 			 fillValue := nilObj].
- 			[self cppIf: (PharoVM or: [true]) "Leave the old code but ignore it completely unless someone complains."
- 				ifTrue:
- 					[^nil]
- 				ifFalse:
- 					["some Squeak images include funky fixed subclasses of abstract variable
- 					  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
- 					  Allow fixed classes to be instantiated here iff nElements = 0."
- 					 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
- 						[^nil].
- 					 numSlots := self fixedFieldsOfClassFormat: classFormat.
- 					 fillValue := nilObj]].
  	classIndex = 0 ifTrue:
  		[classIndex := self ensureBehaviorHash: classObj.
  		 classIndex < 0 ifTrue:
  			[coInterpreter primitiveFailFor: classIndex negated.
  			 ^nil]].
  	numSlots > self maxSlotsForNewSpaceAlloc
  		ifTrue:
  			[numSlots > self maxSlotsForAlloc ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrUnsupported.
  				 ^nil].
  			 newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]
  		ifFalse:
  			[newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].
  	newObj ifNotNil:
  		[self fillObj: newObj numSlots: numSlots with: fillValue].
  	^newObj!

Item was added:
+ ----- Method: StackInterpreter>>getSnapshotScreenSize (in category 'internal interpreter access') -----
+ getSnapshotScreenSize
+ 	"Answer the screen size to write to the snapshot.
+ 	 If the actual screen size is zero then write the savedWindowSize instead."
+ 	| screenSize |
+ 	screenSize := self ioScreenSize.
+ 	((screenSize bitAnd: 16rFFFF) = 0
+ 	 or: [screenSize >> 16 = 0]) ifTrue:
+ 		[screenSize := savedWindowSize].
+ 	^screenSize!



More information about the Vm-dev mailing list