[Vm-dev] VM Maker: VMMaker-dtl.418.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 13 02:35:14 UTC 2020


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.418.mcz

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

Name: VMMaker-dtl.418
Author: dtl
Time: 12 August 2020, 10:35:02.257 pm
UUID: 39e895ba-407a-4226-ab73-3634b979ea77
Ancestors: VMMaker-dtl.417

VMMaker 4.19.2
In ObjectMemory, the expression "self sizeMask + self size4Bit)" is constant regardless of bytesPerWord, see interp.h for the declarations. In all cases, SIZE_MASK + SIZE_4_BIT equals 16rFC. Simplify accordingly.

=============== Diff against VMMaker-dtl.417 ===============

Item was changed:
  ----- Method: NewObjectMemory>>eeInstantiateAndInitializeClass:indexableSize: (in category 'interpreter access') -----
  eeInstantiateAndInitializeClass: 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.
  	 Will *not* cause a GC.  The instantiated object is initialized."
  
  	| hash header1 header2 cClass byteSize format binc header3 hdrSize sizeHiBits bm1 classFormat |
  	<inline: false>
  	"cannot have a negative indexable field count"
  	self assert: size >= 0.
  	hash := self newObjectHash.
  	classFormat := self formatOfClass: classPointer.
  	"Low 2 bits are 0"
  	header1 := (classFormat bitAnd: 16r1FF00) bitOr: (hash bitAnd: HashMaskUnshifted) << HashBitsOffset.
  	header2 := classPointer.
  	header3 := 0.
  	sizeHiBits := (classFormat bitAnd: 16r60000) >> 9.
  	cClass := header1 bitAnd: CompactClassMask. "compact class field from format word"
+ 	byteSize := (classFormat bitAnd: 16rFC) + sizeHiBits.
- 	byteSize := (classFormat bitAnd: self sizeMask + self 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 := classFormat >> 8 bitAnd: 15.
  	self flag: #sizeLowBits.
  	format < 8
  		ifTrue:
  			[format = 6
  				ifTrue: ["long32 bitmaps"
  					bm1 := self bytesPerWord-1.
  					byteSize := byteSize + (size * 4) + bm1 bitAnd: self 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: [byteSize := byteSize + (size * self bytesPerWord) "Arrays and 64-bit bitmaps"]
  			]
  		ifFalse:
  			["Strings and Methods"
  			bm1 := self bytesPerWord-1.
  			byteSize := byteSize + size + bm1 bitAnd: self 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) << 8.
  			"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
  		ifTrue: ["requires size header word"
  			header3 := byteSize.
  			header1 := header1]
  		ifFalse: [header1 := header1 bitOr: byteSize].
  	header3 > 0
  		ifTrue: ["requires full header"
  			hdrSize := 3]
  		ifFalse: [cClass = 0
  				ifTrue: [hdrSize := 2]
  				ifFalse: [hdrSize := 1]].
  	^self eeAllocate: byteSize headerSize: hdrSize h1: header1 h2: header2 h3: header3 doFill: true format: format!

Item was changed:
  ----- Method: NewObjectMemory>>eeInstantiateClass:indexableSize: (in category 'interpreter access') -----
  eeInstantiateClass: 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.
  	 Will *not* cause a GC.
  	 Note that the instantiated object IS NOT FILLED and must be completed before
  	 returning it to Smalltalk. Since this call is used in routines that do just that we are
  	 safe.  Break this rule and die."
  	<api>
  	| hash header1 header2 cClass byteSize format binc header3 hdrSize sizeHiBits bm1 classFormat |
  	<inline: false>
  	"cannot have a negative indexable field count"
  	self assert: size >= 0.
  	hash := self newObjectHash.
  	classFormat := self formatOfClass: classPointer.
  	"Low 2 bits are 0"
  	header1 := (classFormat bitAnd: 16r1FF00) bitOr: (hash bitAnd: HashMaskUnshifted) << HashBitsOffset.
  	header2 := classPointer.
  	header3 := 0.
  	sizeHiBits := (classFormat bitAnd: 16r60000) >> 9.
  	cClass := header1 bitAnd: CompactClassMask. "compact class field from format word"
+ 	byteSize := (classFormat bitAnd: 16rFC) + sizeHiBits.
- 	byteSize := (classFormat bitAnd: self sizeMask + self 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 := classFormat >> 8 bitAnd: 15.
  	self flag: #sizeLowBits.
  	format < 8
  		ifTrue:
  			[format = 6
  				ifTrue: ["long32 bitmaps"
  					bm1 := self bytesPerWord-1.
  					byteSize := byteSize + (size * 4) + bm1 bitAnd: self 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: [byteSize := byteSize + (size * self bytesPerWord) "Arrays and 64-bit bitmaps"]
  			]
  		ifFalse:
  			["Strings and Methods"
  			bm1 := self bytesPerWord-1.
  			byteSize := byteSize + size + bm1 bitAnd: self 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) << 8.
  			"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
  		ifTrue: ["requires size header word"
  			header3 := byteSize.
  			header1 := header1]
  		ifFalse: [header1 := header1 bitOr: byteSize].
  	header3 > 0
  		ifTrue: ["requires full header"
  			hdrSize := 3]
  		ifFalse: [cClass = 0
  				ifTrue: [hdrSize := 2]
  				ifFalse: [hdrSize := 1]].
  	^self eeAllocate: byteSize headerSize: hdrSize h1: header1 h2: header2 h3: header3!

Item was changed:
  ----- Method: NewObjectMemory>>eeInstantiateSmallClass:sizeInBytes: (in category 'interpreter access') -----
  eeInstantiateSmallClass: 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).
  	 Will *not* 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."
  
  	| hash header1 header2 hdrSize |
  	"size must be integral number of words"
  	self assert: (sizeInBytes bitAnd: (self bytesPerWord-1)) = 0.
  	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: 16rFC)).
- 	header1 := header1 + (sizeInBytes - (header1 bitAnd: self sizeMask+self size4Bit)).
  	^self eeAllocate: sizeInBytes headerSize: hdrSize h1: header1 h2: header2 h3: 0!

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."
  
  	| hash header1 header2 cClass byteSize format binc header3 hdrSize fillWord newObj sizeHiBits bm1 classFormat |
  	<inline: false>
  	DoAssertionChecks ifTrue: [size < 0
  				ifTrue: [self error: '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 << HashBitsOffset bitAnd: HashBits).
  	header2 := classPointer.
  	header3 := 0.
  	sizeHiBits := (classFormat bitAnd: 16r60000) >> 9.
  	cClass := header1 bitAnd: CompactClassMask. "compact class field from format word"
+ 	byteSize := (classFormat bitAnd: 16rFC) + sizeHiBits.
- 	byteSize := (classFormat bitAnd: self sizeMask + self 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 := classFormat >> 8 bitAnd: 15.
  	self flag: #sizeLowBits.
  	format < 8
  		ifTrue:
  			[format = 6
  				ifTrue: ["long32 bitmaps"
  					bm1 := self bytesPerWord - 1.
  					byteSize := byteSize + (size * 4) + bm1 bitAnd: self 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: [byteSize := byteSize + (size * self bytesPerWord) "Arrays and 64-bit bitmaps"]
  			]
  		ifFalse:
  			["Strings and Methods"
  			bm1 := self bytesPerWord - 1.
  			byteSize := byteSize + size + bm1 bitAnd: self 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) << 8.
  			"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
  		ifTrue: ["requires size header word"
  			header3 := byteSize.
  			header1 := header1]
  		ifFalse: [header1 := header1 bitOr: byteSize].
  	header3 > 0
  		ifTrue: ["requires full header"
  			hdrSize := 3]
  		ifFalse: [cClass = 0
  				ifTrue: [hdrSize := 2]
  				ifFalse: [hdrSize := 1]].
  	format <= 4
  		ifTrue: ["if pointers, fill with nil oop"
  			fillWord := nilObj]
  		ifFalse: [fillWord := 0].
  	newObj := self allocate: byteSize headerSize: hdrSize h1: header1 h2: header2 h3: header3 doFill: true with: fillWord.
  	^ newObj!

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 jsut that we are safe. Break this rule and die."
  
  	| hash header1 header2 hdrSize |
  	(sizeInBytes bitAnd: (self bytesPerWord - 1)) = 0 ifFalse:
  		[self error: 'size must be integral number of words'].
  	hash := self newObjectHash.
  	header1 := (hash << HashBitsOffset bitAnd: HashBits) bitOr: (self formatOfClass: classPointer).
  	header2 := classPointer.
  	(header1 bitAnd: CompactClassMask) > 0 "is this a compact class"
  		ifTrue: [hdrSize := 1]
  		ifFalse: [hdrSize := 2].
+ 	header1 := header1 + (sizeInBytes - (header1 bitAnd: 16rFC)).
- 	header1 := header1 + (sizeInBytes - (header1 bitAnd: self sizeMask + self size4Bit)).
  	^ self allocate: sizeInBytes headerSize: hdrSize h1: header1 h2: header2 h3: 0 doFill: false with: 0!

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
  
  	"VMMaker versionString"
  
+ 	^'4.19.2'!
- 	^'4.19.1'!



More information about the Vm-dev mailing list