[Vm-dev] VM Maker: ImageFormat-dtl.37.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jul 20 21:24:00 UTC 2019


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

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

Name: ImageFormat-dtl.37
Author: dtl
Time: 20 July 2019, 5:23:59.004 pm
UUID: 52b464d5-0bf7-4326-bde3-4f18ad70b239
Ancestors: ImageFormat-dtl.36

Identify extended bytecodes for Sista in the image format number. Bit 10 identifies an image that contains extended bytecodes. Thus a 32 bit Spur image is 6521, with Sista it is 7033, and a 64 bit Spur image is 68021, with Sista it is 68533.

It is expected that additional bytecode sets can be identified by an additional field in the image header, probably 32 bits containing two 16 bit fields,  if both zero then Sista.

Per discussion with Eliot and Bert in a Squeak oversight board meeting 2019-05-15.

=============== Diff against ImageFormat-dtl.36 ===============

Item was changed:
  Object subclass: #ImageFormat
+ 	instanceVariableNames: 'wordSize requiresClosureSupport requiresNativeFloatWordOrder requiresSpurSupport requiresNewSpur64TagAssignment requiresMultipleBytecodeSupport'
+ 	classVariableNames: 'BaseVersionMask BaseVersionNumbers CapabilitiesBitsMask KnownVersionNumbers MultipleBytecodeBit PlatformByteOrderBit ReservedBitsMask SpurObjectBit'
- 	instanceVariableNames: 'wordSize requiresClosureSupport requiresNativeFloatWordOrder requiresSpurSupport requiresNewSpur64TagAssignment'
- 	classVariableNames: 'BaseVersionMask BaseVersionNumbers CapabilitiesBitsMask KnownVersionNumbers PlatformByteOrderBit ReservedBitsMask SpurObjectBit'
  	poolDictionaries: ''
  	category: 'ImageFormat-Header'!
  
  !ImageFormat commentStamp: 'dtl 11/7/2010 22:13' prior: 0!
  ImageFormat represents the requirements of the image in terms of capabilities that must be supported by the virtual machine. The image format version is saved as an integer value in the header of an image file. When an image is loaded, the virtual machine checks the image format version to determine whether it is capable of supporting the requirements of that image.
  
  The image format version value is treated as a bit map of size 32, derived from the 32-bit integer value saved in the image header. Bits in the bit map represent image format requirements. For example, if the image sets bit 15 to indicate that it requires some capability from the VM, then the VM can check bit 15 and decide whether it is able to satisfy that requirement.
  
  The base image format numbers (6502, 6504, 68000, and 68002) utiliize 10 of the 32 available bits. The high order bit is reserved as an extension bit for future use. The remaining 21 bits are used to represent additional image format requirements. For example, the low order bit is used to indication that the image uses (and requires support for) the platform byte ordering implemented in the StackInterpreter (Cog) VM.
  
  	"(ImageFormat fromFile: Smalltalk imageName) description"
  !

Item was changed:
  ----- Method: ImageFormat class>>bitAssignments (in category 'bit assignments') -----
  bitAssignments
  
  	"ImageFormat bitAssignments
  		doWithIndex: [ :e :i | Transcript cr; show: 'bit ', i asString, ' is ', (e ifNil: ['unused'])]"
  
  	| bits |
  	bits := Array new: 32.
  		"If bit 1 is set, the high and low order 32-bit words of a Float are stored in
  		platform word order. If bit 1 is not set, big-endian word order is used for Float
  		regardless of the platform." 
  	bits at: 1 put: 'the use platform float word order bit (Cog and StackInterpreter)'.
  	bits at: 2 put: 'used in base version numbers'.
  	bits at: 3 put: 'used in base version numbers'.
  	bits at: 4 put: 'used in base version numbers'.
  	bits at: 5 put: 'the Spur object format bit'.
  	bits at: 6 put: 'used in base version numbers'.
  	bits at: 7 put: 'used in base version numbers'.
  	bits at: 8 put: 'used in base version numbers'.
  	bits at: 9 put: 'used in base version numbers'.
+ 	bits at: 10 put: 'the multiple bytecode bit for Sista'..
- 	bits at: 10 put: nil.	"unassigned bit available for future image formats"
  	bits at: 11 put: nil.	"unassigned bit available for future image formats"
  	bits at: 12 put: 'used in base version numbers'.
  	bits at: 13 put: 'used in base version numbers'.
  	bits at: 14 put: nil.	"unassigned bit available for future image formats"
  	bits at: 15 put: nil.	"unassigned bit available for future image formats"
  	bits at: 16 put: nil.	"unassigned bit available for future image formats"
  	bits at: 17 put: 'used in base version numbers'.
  	bits at: 18 put: nil.	"unassigned bit available for future image formats"
  	bits at: 19 put: nil.	"unassigned bit available for future image formats"
  	bits at: 20 put: nil.	"unassigned bit available for future image formats"
  	bits at: 21 put: nil.	"unassigned bit available for future image formats"
  	bits at: 22 put: nil.	"unassigned bit available for future image formats"
  	bits at: 23 put: nil.	"unassigned bit available for future image formats"
  	bits at: 24 put: nil.	"unassigned bit available for future image formats"
  	bits at: 25 put: nil.	"unassigned bit available for future image formats"
  	bits at: 26 put: nil.	"unassigned bit available for future image formats"
  	bits at: 27 put: nil.	"unassigned bit available for future image formats"
  	bits at: 28 put: nil.	"unassigned bit available for future image formats"
  	bits at: 29 put: nil.	"unassigned bit available for future image formats"
  	bits at: 30 put: nil.	"unassigned bit available for future image formats"
  	bits at: 31 put: nil.	"unassigned bit available for future image formats"
  		"If bit 32 is set, additional image format information will be stored in one or
  		more additional words. Currently this is unused, and bit 32 is always zero."
  	bits at: 32 put: 'the extension bit (reserved for future use)'.
  	^bits
  !

Item was changed:
  ----- Method: ImageFormat class>>capabilitiesBitsMask (in category 'image formats') -----
  capabilitiesBitsMask
  	"Bits currently used as capability bits."
  	
  	"ImageFormat capabilitiesBitsMask printStringBase: 2"
  
+ 	^ { PlatformByteOrderBit . SpurObjectBit . MultipleBytecodeBit }
+ 		inject: 0
+ 		into: [:accum :bitNumber | accum bitAt: bitNumber put: 1]
- 	^ (0 bitAt: PlatformByteOrderBit put: 1)
- 		bitAt: SpurObjectBit put: 1
  !

Item was changed:
  ----- Method: ImageFormat class>>initialize (in category 'initialize-release') -----
  initialize
  	"ImageFormat initialize"
  
  	PlatformByteOrderBit := 1.
  	SpurObjectBit := 5.
+ 	MultipleBytecodeBit := 10.
  	BaseVersionNumbers := self baseVersionNumbers.
  	BaseVersionMask := self baseVersionMask.
  	CapabilitiesBitsMask := self capabilitiesBitsMask.
  	ReservedBitsMask := self availableBits.
  	KnownVersionNumbers := self knownVersionNumbers.
  !

Item was changed:
  ----- Method: ImageFormat class>>knownVersionNumbers (in category 'image formats') -----
  knownVersionNumbers
  	"Version numbers currently in use or likely to be used (e.g. 64-bit Cog formats)"
  
  	"ImageFormat knownVersionNumbers collect: [:e | (ImageFormat fromInteger: e) description]"
  
  	^ ( self baseVersionNumbers, "the original format number variants"
  		{
  			6505 .	"Cog and StackVM"
  			68003 .	"Cog and StackVM running 64-bit image"
  			6521 .	"Spur 32 bit object memory"
+ 			7033 .	"Spur 32 bit with Sista bytecodes"
  			68019 .	"Spur 64 bit object memory (early)"
  			68021 .	"Spur 64 bit object memory"
+ 			68533 .	"Spur 64 bit with Sista bytecodes"
  				" ... add others here as bits are allocated to represent requirements of other image formats"
  		} ) sort.
  !

Item was changed:
  ----- Method: ImageFormat class>>wordSize:spur: (in category 'instance creation') -----
  wordSize: bytesPerWord spur: spurRequired
  	"Answer a Spur image format, or default to Cog if Spur is not specified"
  
  	| update64 |
  	update64 := bytesPerWord == 8. "The 64 bit Spur image has an updated version"
+ 	^ self
+ 		wordSize: bytesPerWord
+ 		spur: spurRequired
+ 		requiresNewSpur64TagAssignment: update64
+ 		multipleBytecodes: false!
- 	^self wordSize: bytesPerWord spur: spurRequired requiresNewSpur64TagAssignment: update64!

Item was added:
+ ----- Method: ImageFormat class>>wordSize:spur:multipleBytecodes: (in category 'instance creation') -----
+ wordSize: bytesPerWord spur: spurRequired multipleBytecodes: isSista
+ 
+ 	| update64 |
+ 	update64 := bytesPerWord == 8. "The 64 bit Spur image has an updated version"
+ 	^(self wordSize: bytesPerWord)
+ 		setClosureSupportRequirement: true;
+ 		setCogSupportRequirement: true;
+ 		setSpurSupportRequirement: spurRequired;
+ 		setRequiresNewSpur64TagAssignmentRequirement: update64;
+ 		setRequiresMultipleBytecodeSupport: isSista
+ !

Item was changed:
  ----- Method: ImageFormat class>>wordSize:spur:requiresNewSpur64TagAssignment: (in category 'instance creation') -----
  wordSize: bytesPerWord spur: spurRequired requiresNewSpur64TagAssignment: newSpur64
- 	"Answer a Spur image format, or default to Cog if Spur is not specified"
  
+ 	^ self
+ 		wordSize: bytesPerWord
+ 		spur: spurRequired
+ 		requiresNewSpur64TagAssignment: newSpur64
+ 		multipleBytecodes: false!
- 	^(self wordSize: bytesPerWord)
- 		setClosureSupportRequirement: true;
- 		setCogSupportRequirement: true;
- 		setSpurSupportRequirement: spurRequired;
- 		setRequiresNewSpur64TagAssignmentRequirement: newSpur64
- !

Item was added:
+ ----- Method: ImageFormat class>>wordSize:spur:requiresNewSpur64TagAssignment:multipleBytecodes: (in category 'instance creation') -----
+ wordSize: bytesPerWord spur: spurRequired requiresNewSpur64TagAssignment: newSpur64 multipleBytecodes: isSpur
+ 
+ 	^(self wordSize: bytesPerWord)
+ 		setClosureSupportRequirement: true;
+ 		setCogSupportRequirement: true;
+ 		setSpurSupportRequirement: spurRequired;
+ 		setRequiresNewSpur64TagAssignmentRequirement: newSpur64;
+ 		setRequiresMultipleBytecodeSupport: isSpur
+ !

Item was changed:
  ----- Method: ImageFormat>>asInteger (in category 'converting') -----
  asInteger
  	"Answer an integer representation of this image format suitable for storage
  	in an image file header. The stored value in the file header will be used when
  	loading the image from the snapshot file."
  
  	| val |
  	val := wordSize = 4
  		ifTrue: [6502]
  		ifFalse: [68000].
  	self requiresClosureSupport ifTrue: [val := val + 2].
  	self requiresNativeFloatWordOrder ifTrue: [val := val + 1].
  	self requiresSpurSupport ifTrue: [val := val + 2r10000].
  	self requiresNewSpur64TagAssignment ifTrue: [val := val + 2].
+ 	self requiresMultipleBytecodeSupport ifTrue: [val := val + 2r1000000000].
  	^val
  !

Item was changed:
  ----- Method: ImageFormat>>fromInteger: (in category 'initialize-release') -----
  fromInteger: anInteger
  	"Initialize a new instance from anInteger obtained from an image file header."
  
  	| baseVersion capabilitiesBits |
  	(anInteger bitAnd: ReservedBitsMask) ~= 0
  		ifTrue: [self error: 'invalid format number ', anInteger printString].
  	baseVersion := self  baseVersionBitsOf: anInteger.
  	((baseVersion = 6504 or: [baseVersion = 68002]) or: [baseVersion = 68004])
  		ifTrue: [requiresClosureSupport := true].
  	(baseVersion = 6502 or: [baseVersion = 6504])
  		ifTrue: [wordSize := 4]
  		ifFalse: [((baseVersion = 68000 or: [baseVersion = 68002]) or: [baseVersion = 68004])
  			ifTrue: [wordSize := 8.
  					baseVersion = 68004
  						ifTrue: [self setRequiresNewSpur64TagAssignmentRequirement: true]]
  			ifFalse: [self error: 'invalid format number ', anInteger printString]].
  	capabilitiesBits := anInteger bitAnd: CapabilitiesBitsMask.
  	(capabilitiesBits bitAt: PlatformByteOrderBit) = 1
  		ifTrue: [requiresNativeFloatWordOrder := true.
  			requiresClosureSupport
  				ifFalse: [self error: 'Images requiring platform byte order also require closure support (Cog)'].
  			capabilitiesBits := capabilitiesBits bitAt: PlatformByteOrderBit put: 0].
  	(capabilitiesBits bitAt: SpurObjectBit) = 1
  		ifTrue: [requiresSpurSupport := true.
  			requiresClosureSupport
  				ifFalse: [self error: 'Images requiring Spur also require closure support'].
  			requiresNativeFloatWordOrder
  				ifFalse: [self error: 'Images requiring Spur also require native float word order support'].
  			capabilitiesBits := capabilitiesBits bitAt: SpurObjectBit put: 0].
+ 	(capabilitiesBits bitAt: MultipleBytecodeBit) = 1
+ 		ifTrue: [requiresMultipleBytecodeSupport := true.
+ 			capabilitiesBits := capabilitiesBits bitAt: MultipleBytecodeBit put: 0].
+ 
  	"add additional capability bit handling here"
  	capabilitiesBits == 0
  		ifFalse: [self error: 'invalid format number ', anInteger printString]
  	
  !

Item was changed:
  ----- Method: ImageFormat>>initialize (in category 'initialize-release') -----
  initialize
  	requiresClosureSupport := false.
  	requiresNativeFloatWordOrder := false.
  	requiresSpurSupport := false.
+ 	requiresNewSpur64TagAssignment := false.
+ 	requiresMultipleBytecodeSupport := false.!
- 	requiresNewSpur64TagAssignment := false.!

Item was changed:
  ----- Method: ImageFormat>>printDescriptionOn: (in category 'printing') -----
  printDescriptionOn: stream
  "
  The classic squeak image, aka V3, is 32-bit with magic 6502. The first 64-bit
  Squeak image was generated from V3 image made by Dan Ingalls and Ian Piumarta
  in 2005. Later, the magic code was changed to 68000.
  
  After full closure support came to Squeak, the magic code changed to 6504 for
  32-bit and 68002 for 64-bit images by setting a capability bit.
  
  Cog VM introduced a native order for floats under 6505 magic code.  Its
  corresponding 64b code would have been 68003 but no such image was produced.
  Older Interpreter VMs would simply load 6505 by flipping word order back.
  
  Cog VM also introduced a new object layout for 64-bit images called Spur layout
  under a new magic code - 68021. A few images were also generated with 68019,
  but this magic is now considered obsolete and deprecated.
  "
  	stream nextPutAll: 'a ';
  		nextPutAll: (wordSize * 8) asString;
  		nextPutAll: '-bit ';
  		nextPutAll: (self requiresSpurSupport
  			ifTrue: [ 'Spur' ]
  			ifFalse: [ 'V3' ]);
  		nextPutAll: ' image with '.
  	self requiresClosureSupport ifFalse: [stream nextPutAll: 'no '].
  	stream nextPutAll: 'closure support and '.
  	self requiresNativeFloatWordOrder
  		ifTrue: [stream nextPutAll: 'float words stored in native platform order']
  		ifFalse: [stream nextPutAll: 'no native platform float word order requirement'].
  	self requiresSpurSupport
  		ifTrue: [stream nextPutAll: ' using Spur object format'.
  			(self is64Bit and: [self requiresNewSpur64TagAssignment not])
  				ifTrue: [stream nextPutAll: ' (obsolete)']].
+ 	self requiresMultipleBytecodeSupport
+ 		ifTrue: [ stream nextPutAll: ' and Sista ' ].
  	stream nextPutAll: ' (';
  		nextPutAll: self asInteger asString;
  		nextPut: $).
  	^ stream
  !

Item was changed:
  ----- Method: ImageFormat>>printTerseDescriptionOn: (in category 'printing') -----
  printTerseDescriptionOn: stream
  	"Shortened description as may be required for unix magic file entries"
  
  	stream
  		nextPutAll: self simpleName;
  		nextPutAll: ' image '.
  	self requiresClosureSupport ifTrue: [stream nextPutAll: '+C'].
  	self requiresNativeFloatWordOrder ifTrue: [stream nextPutAll: '+NF'].
  	self requiresNewSpur64TagAssignment ifTrue: [stream nextPutAll: '+Tag' ].
+ 	self requiresMultipleBytecodeSupport ifTrue: [stream nextPutAll: '+BC' ].
  	stream nextPutAll: ' (%d)'.
  	^ stream
  !

Item was added:
+ ----- Method: ImageFormat>>requiresMultipleBytecodeSupport (in category 'testing') -----
+ requiresMultipleBytecodeSupport
+ 	"True if this image contains extended bytecodes such as the Sista bytecode set.
+ 	An additional field in the image header may be used to specify a specific bytecode
+ 	or extension. If false, the image contains only the traditional bytecodes."
+ 
+ 	^requiresMultipleBytecodeSupport!

Item was added:
+ ----- Method: ImageFormat>>setRequiresMultipleBytecodeSupport: (in category 'initialize-release') -----
+ setRequiresMultipleBytecodeSupport: aBoolean
+ 	"True if this image contains extended bytecodes such as the Sista bytecode set.
+ 	An additional field in the image header may be used to specify a specific bytecode
+ 	or extension. If false, the image contains only the traditional bytecodes."
+ 
+ 	requiresMultipleBytecodeSupport := aBoolean!

Item was added:
+ ----- Method: ImageFormatTest>>testFormat68533 (in category 'testing') -----
+ testFormat68533
+ 
+ 	| spur |
+ 	spur := ImageFormat fromInteger: 68533.
+ 	self assert: spur asInteger = 68533.
+ 	self assert: (ImageFormat wordSize: 8 spur: true multipleBytecodes: true) asInteger = 68533.
+ 	self assert: (ImageFormat fromInteger: 68533) asInteger = 68533.
+ 	self assert: spur wordSize = 8.
+ 	self assert: spur requiresClosureSupport.
+ 	self assert: spur requiresNativeFloatWordOrder.
+ 	self deny: spur is32Bit.
+ 	self assert: spur is64Bit.
+ 	self assert: spur requiresSpurSupport.
+ 	self assert: (ImageFormat fromInteger: 68533) asInteger = 68533!

Item was added:
+ ----- Method: ImageFormatTest>>testFormat7033 (in category 'testing') -----
+ testFormat7033
+ 
+ 	| spur |
+ 	spur := ImageFormat fromInteger: 7033.
+ 	self assert: spur asInteger = 7033.
+ 	self assert: (ImageFormat wordSize: 4 spur: true multipleBytecodes: true) asInteger = 7033.
+ 	self assert: (ImageFormat fromInteger: 7033) asInteger = 7033.
+ 	self assert: spur wordSize = 4.
+ 	self assert: spur requiresClosureSupport.
+ 	self assert: spur requiresNativeFloatWordOrder.
+ 	self assert: spur is32Bit.
+ 	self deny: spur is64Bit.
+ 	self assert: spur requiresSpurSupport.
+ 	self assert: (ImageFormat fromInteger: 7033) asInteger = 7033!



More information about the Vm-dev mailing list