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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 1 11:52:27 UTC 2012


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

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

Name: ImageFormat-dtl.14
Author: dtl
Time: 1 November 2012, 7:52:14.48 am
UUID: 76bad473-3b56-48fa-8fa7-80d8c7afc523
Ancestors: ImageFormat-dtl.13

Add updates to ImageFormat to report #availableBits and bitAssignments.

Add ImageFileHeader and CogImageFileHeader with tests in ImageFileHeaderTest.

The purpose of ImageFileHeader is to document the current formats of Cog and interpreter image file headers, and to provide a convenient way to inspect the data values an image file header.

To explore the file header of an image file:

  | fs |
  fs := (FileStream readOnlyFileNamed: Smalltalk imageName) binary.
  ([CogImageFileHeader readFrom: fs] ensure: [fs close]) explore

=============== Diff against ImageFormat-dtl.13 ===============

Item was removed:
- SystemOrganization addCategory: #ImageFormat!

Item was added:
+ SystemOrganization addCategory: #'ImageFormat-Header'!
+ SystemOrganization addCategory: #'ImageFormat-Tests'!

Item was added:
+ ImageFileHeader subclass: #CogImageFileHeader
+ 	instanceVariableNames: 'desiredNumStackPages unknownShortOrCodeSizeInKs desiredEdenBytes maxExtSemTabSizeSet'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'ImageFormat-Header'!
+ 
+ !CogImageFileHeader commentStamp: 'dtl 10/31/2012 20:23' prior: 0!
+ CogImageFileHeader is an extension of ImageFileHeader with additional fields that are used by Cog and Stack VMs. Some of the additional fields are encoded as short short integers, which are 16 bits when the header word size is 32, and 32 bits when the header word size is 64. All current Cog VMs use 32 bit word size with 16 bit short integer fields.!

Item was added:
+ ----- Method: CogImageFileHeader>>desiredEdenBytes (in category 'accessing') -----
+ desiredEdenBytes
+ 
+ 	^ desiredEdenBytes!

Item was added:
+ ----- Method: CogImageFileHeader>>desiredEdenBytes: (in category 'accessing') -----
+ desiredEdenBytes: anObject
+ 
+ 	desiredEdenBytes := anObject!

Item was added:
+ ----- Method: CogImageFileHeader>>desiredNumStackPages (in category 'accessing') -----
+ desiredNumStackPages
+ 
+ 	^ desiredNumStackPages!

Item was added:
+ ----- Method: CogImageFileHeader>>desiredNumStackPages: (in category 'accessing') -----
+ desiredNumStackPages: anObject
+ 
+ 	desiredNumStackPages := anObject!

Item was added:
+ ----- Method: CogImageFileHeader>>maxExtSemTabSizeSet (in category 'accessing') -----
+ maxExtSemTabSizeSet
+ 
+ 	^ maxExtSemTabSizeSet!

Item was added:
+ ----- Method: CogImageFileHeader>>maxExtSemTabSizeSet: (in category 'accessing') -----
+ maxExtSemTabSizeSet: anObject
+ 
+ 	maxExtSemTabSizeSet := anObject!

Item was added:
+ ----- Method: CogImageFileHeader>>readFieldsFrom:startingAt:headerWordSize:littleEndian: (in category 'reading') -----
+ readFieldsFrom: aStream startingAt: imageOffset headerWordSize: headerWordSize littleEndian: littleEndian
+ 	"Read data fields and answer number of bytes read"
+ 
+ 	| remainder bytesRead |
+ 	bytesRead := super readFieldsFrom: aStream startingAt: imageOffset headerWordSize: headerWordSize littleEndian: littleEndian.
+ 	desiredNumStackPages := self nextNumber: headerWordSize / 2 from: aStream littleEndian: littleEndian.
+ 	unknownShortOrCodeSizeInKs := self nextNumber: headerWordSize / 2 from: aStream littleEndian: littleEndian.
+ 	desiredEdenBytes := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	maxExtSemTabSizeSet := self nextNumber: headerWordSize / 2 from: aStream littleEndian: littleEndian.
+ 	self nextNumber: headerWordSize / 2 from: aStream littleEndian: littleEndian.
+ 	remainder := headerSize - (12 * imageFormat wordSize).
+ 	self assert: remainder >= 0. "n.b. Mantis 7455 bug in original 64 bit image due to VMM error"
+ 	^3 * imageFormat wordSize + bytesRead.
+ !

Item was added:
+ ----- Method: CogImageFileHeader>>storeOn: (in category 'printing') -----
+ storeOn: aStream 
+ 	"Append to the argument aStream a sequence of characters that is an 
+ 	expression whose evaluation creates an object similar to the receiver."
+ 
+ 	super storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; desiredNumStackPages: '.
+ 	desiredNumStackPages storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; unknownShortOrCodeSizeInKs: '.
+ 	unknownShortOrCodeSizeInKs storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; desiredEdenBytes: '.
+ 	desiredEdenBytes storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; maxExtSemTabSizeSet: '.
+ 	maxExtSemTabSizeSet storeOn: aStream.
+ !

Item was added:
+ ----- Method: CogImageFileHeader>>unknownShortOrCodeSizeInKs (in category 'accessing') -----
+ unknownShortOrCodeSizeInKs
+ 
+ 	^ unknownShortOrCodeSizeInKs!

Item was added:
+ ----- Method: CogImageFileHeader>>unknownShortOrCodeSizeInKs: (in category 'accessing') -----
+ unknownShortOrCodeSizeInKs: anObject
+ 
+ 	unknownShortOrCodeSizeInKs := anObject!

Item was added:
+ ----- Method: CogImageFileHeader>>writeFieldsTo:littleEndian:headerWordSize: (in category 'writing') -----
+ writeFieldsTo: aStream littleEndian: littleEnder headerWordSize: headerWordSize
+ 	"Write data fields and answer number of bytes written"
+ 
+ 	| bytesWritten |
+ 	bytesWritten := super writeFieldsTo: aStream littleEndian: littleEnder headerWordSize: headerWordSize.
+ 	self nextNumber: headerWordSize / 2 put: desiredNumStackPages to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize / 2 put: unknownShortOrCodeSizeInKs to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: desiredEdenBytes to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize / 2 put: maxExtSemTabSizeSet to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize / 2 put: 0 to: aStream littleEndian: littleEnder.
+ 	^3 * imageFormat wordSize + bytesWritten.
+ !

Item was added:
+ Object subclass: #ImageFileHeader
+ 	instanceVariableNames: 'imageFormat headerSize imageBytes startOfMemory specialObjectsOop lastHash screenSize imageHeaderFlags extraVMMemory'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'ImageFormat-Header'!
+ 
+ !ImageFileHeader commentStamp: 'dtl 11/1/2012 07:46' prior: 0!
+ An ImageFileHeader represents the information in the header block of an image file, used by an interpreter VM. Subclasses may implement extensions for Cog or other header extensions.
+ 
+ Instance variables correspond to the fields in an image file header. An instance of ImageFileHeader may be created by reading from an image file, and an ImageFileHeader may be written to a file.
+ 
+ When stored to a file, the file header fields may be 32 or 64 bits in size, depending on the image format. The byte ordering of each field will be little endian or big endian, depending on the convention of the host platform. When reading from disk, endianness is inferred from the contents of the first data field.
+ 
+ To explore the file header of an image file:
+ 
+   | fs |
+   fs := (FileStream readOnlyFileNamed: Smalltalk imageName) binary.
+   ([ImageFileHeader readFrom: fs] ensure: [fs close]) explore
+ !

Item was added:
+ ----- Method: ImageFileHeader class>>readFrom: (in category 'instance creation') -----
+ readFrom: aStream
+ 
+ 	^self readFrom: aStream startingAt: 0!

Item was added:
+ ----- Method: ImageFileHeader class>>readFrom:startingAt: (in category 'instance creation') -----
+ readFrom: aStream startingAt: imageOffset
+ 
+ 	^self basicNew readFrom: aStream startingAt: imageOffset!

Item was added:
+ ----- Method: ImageFileHeader>>asByteArray (in category 'converting') -----
+ asByteArray
+ 	^ ByteArray
+ 		streamContents: [:strm | self writeTo: strm littleEndian: Smalltalk isLittleEndian]!

Item was added:
+ ----- Method: ImageFileHeader>>extraVMMemory (in category 'accessing') -----
+ extraVMMemory
+ 
+ 	^ extraVMMemory!

Item was added:
+ ----- Method: ImageFileHeader>>extraVMMemory: (in category 'accessing') -----
+ extraVMMemory: anObject
+ 
+ 	extraVMMemory := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>headerSize (in category 'accessing') -----
+ headerSize
+ 
+ 	^ headerSize!

Item was added:
+ ----- Method: ImageFileHeader>>headerSize: (in category 'accessing') -----
+ headerSize: anObject
+ 
+ 	headerSize := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>imageBytes (in category 'accessing') -----
+ imageBytes
+ 
+ 	^ imageBytes!

Item was added:
+ ----- Method: ImageFileHeader>>imageBytes: (in category 'accessing') -----
+ imageBytes: anObject
+ 
+ 	imageBytes := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>imageFormat (in category 'accessing') -----
+ imageFormat
+ 
+ 	^ imageFormat!

Item was added:
+ ----- Method: ImageFileHeader>>imageFormat: (in category 'accessing') -----
+ imageFormat: anObject
+ 
+ 	imageFormat := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>imageHeaderFlags (in category 'accessing') -----
+ imageHeaderFlags
+ 
+ 	^ imageHeaderFlags!

Item was added:
+ ----- Method: ImageFileHeader>>imageHeaderFlags: (in category 'accessing') -----
+ imageHeaderFlags: anObject
+ 
+ 	imageHeaderFlags := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>lastHash (in category 'accessing') -----
+ lastHash
+ 
+ 	^ lastHash!

Item was added:
+ ----- Method: ImageFileHeader>>lastHash: (in category 'accessing') -----
+ lastHash: anObject
+ 
+ 	lastHash := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>nextNumber:from:littleEndian: (in category 'reading') -----
+ nextNumber: length from: aStream littleEndian: littleEnder
+ 
+ 	littleEnder
+ 		ifTrue: [^aStream nextLittleEndianNumber: length]
+ 		ifFalse: [^aStream nextNumber: length]!

Item was added:
+ ----- Method: ImageFileHeader>>nextNumber:put:to:littleEndian: (in category 'writing') -----
+ nextNumber: n put: v to: aStream littleEndian: littleEnder
+ 
+ 	littleEnder
+ 		ifTrue: [^aStream nextLittleEndianNumber: n put: v]
+ 		ifFalse: [^aStream nextNumber: n put: v]!

Item was added:
+ ----- Method: ImageFileHeader>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 
+ 	super printOn: aStream.
+ 	imageFormat ifNotNil: [
+ 		aStream nextPutAll: ' for '.
+ 		imageFormat printDescriptionOn: aStream]!

Item was added:
+ ----- Method: ImageFileHeader>>readFieldsFrom:startingAt:headerWordSize:littleEndian: (in category 'reading') -----
+ readFieldsFrom: aStream startingAt: imageOffset headerWordSize: headerWordSize littleEndian: littleEndian
+ 	"Read data fields and answer number of bytes read"
+ 
+ 	| remainder |
+ 	headerSize := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	imageBytes := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	startOfMemory := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	specialObjectsOop := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	lastHash := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	self screenSize: (self nextNumber: headerWordSize from: aStream littleEndian: littleEndian).
+ 	imageHeaderFlags := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	extraVMMemory := self nextNumber: headerWordSize from: aStream littleEndian: littleEndian.
+ 	remainder := headerSize - (9 * imageFormat wordSize).
+ 	self assert: remainder >= 0. "n.b. Mantis 7455 bug in original 64 bit image due to VMM error"
+ 	^9 * imageFormat wordSize.
+ !

Item was added:
+ ----- Method: ImageFileHeader>>readFrom:startingAt: (in category 'reading') -----
+ readFrom: aStream startingAt: imageOffset
+ 
+ 	| remainder bytesRead headerWordSize littleEndian |
+ 	littleEndian := self readImageVersionFrom: aStream startingAt: imageOffset.
+ 	headerWordSize := aStream position - imageOffset.
+ 	bytesRead := self readFieldsFrom: aStream startingAt: imageOffset headerWordSize: headerWordSize littleEndian: littleEndian.
+ 	remainder := headerSize - bytesRead.
+ 	self assert: remainder >= 0. "n.b. Mantis 7455 bug in original 64 bit image due to VMM error"
+ 	aStream next: (headerSize - bytesRead).
+ !

Item was added:
+ ----- Method: ImageFileHeader>>readImageVersionFrom:startingAt: (in category 'reading') -----
+ readImageVersionFrom: aStream startingAt: imageOffset
+ 	"Look for image format in the next 4 or 8 bytes and set imageFormat. Answer true
+ 	if the header is written in little endian format."
+ 
+ 	(aStream nextNumber: 4) caseOf:
+ 		{
+ 			[ 16r00001966 "6502" ] -> [ imageFormat := ImageFormat fromInteger: 6502. ^false ] .
+ 			[ 16r66190000 "6502" ] -> [ imageFormat := ImageFormat fromInteger: 6502. ^true ] .
+ 			[ 16r00001968 "6504" ] -> [ imageFormat := ImageFormat fromInteger: 6504. ^false ] .
+ 			[ 16r68190000 "6504" ] -> [ imageFormat := ImageFormat fromInteger: 6504. ^true ] .
+ 			[ 16r00001969 "6505" ] -> [ imageFormat := ImageFormat fromInteger: 6505. ^false ] .
+ 			[ 16r69190000 "6505" ] -> [ imageFormat := ImageFormat fromInteger: 6505. ^true ] .
+ 			[ 16rA0090100 "68000" ] -> [ imageFormat := ImageFormat fromInteger: 68000. aStream next: 4. ^true ] .
+ 			[ 16rA2090100 "68002" ] -> [ imageFormat := ImageFormat fromInteger: 68002. aStream next: 4. ^true ] .
+ 			[ 16rA3090100 "68003" ] -> [ imageFormat := ImageFormat fromInteger: 68003. aStream next: 4. ^true ] .
+ 			[ 16r00000000 ] -> [
+ 				(aStream nextNumber: 4) caseOf: {
+ 					[ 16r000109A0 "68000" ] -> [ imageFormat := ImageFormat fromInteger: 68000. ^false ] .
+ 					[ 16r000109A2 "68002" ] -> [ imageFormat := ImageFormat fromInteger: 68002. ^false ] .
+ 					[ 16r000109A3 "68003" ] -> [ imageFormat := ImageFormat fromInteger: 68003. ^false ] .
+ 				} otherwise: [self error: self asString , ' unrecognized format number']
+ 			]
+ 		} otherwise: [self error: self asString , ' unrecognized format number']
+ 	
+ 	"ImageFormat versionNumberByteArrays do: [:e |
+ 		Transcript cr; show: e printString , ': ', (ImageFormat fromBytes: e) description]
+ 	
+ #[0 0 25 102]: A 32-bit image with no closure support and no native platform float word order requirement (6502)
+ #[102 25 0 0]: A 32-bit image with no closure support and no native platform float word order requirement (6502)
+ #[0 0 25 104]: A 32-bit image with closure support and no native platform float word order requirement (6504)
+ #[104 25 0 0]: A 32-bit image with closure support and no native platform float word order requirement (6504)
+ #[0 0 0 0 0 1 9 160]: A 64-bit image with no closure support and no native platform float word order requirement (68000)
+ #[160 9 1 0 0 0 0 0]: A 64-bit image with no closure support and no native platform float word order requirement (68000)
+ #[0 0 0 0 0 1 9 162]: A 64-bit image with closure support and no native platform float word order requirement (68002)
+ #[162 9 1 0 0 0 0 0]: A 64-bit image with closure support and no native platform float word order requirement (68002)
+ #[0 0 25 105]: A 32-bit image with closure support and float words stored in native platform order (6505)
+ #[105 25 0 0]: A 32-bit image with closure support and float words stored in native platform order (6505)
+ #[0 0 0 0 0 1 9 163]: A 64-bit mage with closure support and float words stored in native platform order (68003)
+ #[163 9 1 0 0 0 0 0]: A 64-bit image with closure support and float words stored in native platform order (68003)
+ 	
+ 	"
+ 	!

Item was added:
+ ----- Method: ImageFileHeader>>screenSize (in category 'accessing') -----
+ screenSize
+ 	"World extent at the time of image save, packed into 32 bit integer when
+ 	saved to file header."
+ 
+ 	"right=  windowBounds.x + ((unsigned)savedWindowSize >> 16);
+ 	bottom= windowBounds.y + (savedWindowSize & 0xFFFF);"
+ 
+ 	^ screenSize!

Item was added:
+ ----- Method: ImageFileHeader>>screenSize: (in category 'accessing') -----
+ screenSize: anIntegerOrPoint
+ 	"World extent at the time of image save, packed into 32 bit integer when
+ 	saved to file header."
+ 
+ 	"right=  windowBounds.x + ((unsigned)savedWindowSize >> 16);
+ 	bottom= windowBounds.y + (savedWindowSize & 0xFFFF);"
+ 
+ 	anIntegerOrPoint isInteger
+ 		ifTrue: [screenSize := ((anIntegerOrPoint >> 16) @ (anIntegerOrPoint bitAnd: 16rFFFF))]
+ 		ifFalse: [screenSize := anIntegerOrPoint]
+ !

Item was added:
+ ----- Method: ImageFileHeader>>specialObjectsOop (in category 'accessing') -----
+ specialObjectsOop
+ 
+ 	^ specialObjectsOop!

Item was added:
+ ----- Method: ImageFileHeader>>specialObjectsOop: (in category 'accessing') -----
+ specialObjectsOop: anObject
+ 
+ 	specialObjectsOop := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>startOfMemory (in category 'accessing') -----
+ startOfMemory
+ 
+ 	^ startOfMemory!

Item was added:
+ ----- Method: ImageFileHeader>>startOfMemory: (in category 'accessing') -----
+ startOfMemory: anObject
+ 
+ 	startOfMemory := anObject!

Item was added:
+ ----- Method: ImageFileHeader>>storeOn: (in category 'printing') -----
+ storeOn: aStream 
+ 	"Append to the argument aStream a sequence of characters that is an 
+ 	expression whose evaluation creates an object similar to the receiver."
+ 
+ 	aStream nextPutAll: self class name;
+ 		nextPutAll: ' new imageFormat: ('.
+ 	imageFormat storeOn: aStream.
+ 
+ 	aStream nextPutAll: '); headerSize: '.
+ 	headerSize storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; imageBytes: '.
+ 	imageBytes storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; startOfMemory: '.
+ 	startOfMemory storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; specialObjectsOop: '.
+ 	specialObjectsOop storeOn: aStream.
+ 
+ 	aStream nextPutAll: '; lastHash: '.
+ 	lastHash storeOn: aStream.
+ 	
+ 	aStream nextPutAll: '; screenSize: '.
+ 	screenSize storeOn: aStream.
+ 	
+ 	aStream nextPutAll: '; imageHeaderFlags: '.
+ 	imageHeaderFlags storeOn: aStream.
+ 	
+ 	aStream nextPutAll: '; extraVMMemory: '.
+ 	extraVMMemory storeOn: aStream.
+ 	
+ !

Item was added:
+ ----- Method: ImageFileHeader>>writeFieldsTo:littleEndian:headerWordSize: (in category 'writing') -----
+ writeFieldsTo: aStream littleEndian: littleEnder headerWordSize: headerWordSize
+ 	"Write data fields and answer number of bytes written"
+ 
+ 	self nextNumber: headerWordSize put: imageFormat asInteger to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: headerSize to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: imageBytes to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: startOfMemory to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: specialObjectsOop to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: lastHash to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: ((screenSize x) << 16 + (screenSize y)) to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: imageHeaderFlags to: aStream littleEndian: littleEnder.
+ 	self nextNumber: headerWordSize put: extraVMMemory to: aStream littleEndian: littleEnder.
+ 	^9 * imageFormat wordSize.
+ !

Item was added:
+ ----- Method: ImageFileHeader>>writeTo:littleEndian: (in category 'writing') -----
+ writeTo: aStream littleEndian: littleEnder
+ 
+ 	| headerWordSize remainder bytesWritten |
+ 	headerWordSize := imageFormat wordSize.
+ 	bytesWritten := self writeFieldsTo: aStream littleEndian: littleEnder headerWordSize: headerWordSize.
+ 	remainder := headerSize - bytesWritten.
+ 	self assert: remainder >= 0. "n.b. Mantis 7455 bug in original 64 bit image due to VMM error"
+ 	remainder timesRepeat: [aStream nextPut: 0].
+ !

Item was added:
+ TestCase subclass: #ImageFileHeaderTest
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'ImageFormat-Tests'!
+ 
+ !ImageFileHeaderTest commentStamp: 'dtl 10/31/2012 20:26' prior: 0!
+ ImageFileHeaderTest provides unit tests for ImageFileHeader and CogImageFileHeader. These tests verify conversion to and from disk file format for various word sizes, platform endianness, and image formats.!

Item was added:
+ ----- Method: ImageFileHeaderTest>>sample6504HeaderData (in category 'running') -----
+ sample6504HeaderData
+ 	"First 200 bytes of an image file saved by an interpreter VM, an ImageFileHeader
+ 	for a 32-bit image with closure support and no native platform float word order
+ 	requirement (6504)"
+ 
+ 	^#[104 25 0 0 64 0 0 0 4 127 88 8 16 0 0 0 196 175 67 5 175 67 0 0 151 3 160 4 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 209 143 131 0 5 0 0 30 89 145 131 0 5 0 160 24 149 144 131 0 5 0 12 23 15 129 56 0 140 122 24 0 12 22 0 0 4 1 0 0 36 49 132 0 0 50 188 26 88 198 24 0 3 0 0 0 8 197 24 0 3 0 0 0 64 188 24 0 3 0 0 0 88 188 24 0 3 0 0 0 76 188 24 0 3 0 0 0 52 188 24 0 3 0 0 0 72 124 24 0 3 0 0 0 112 129 24 0 3 0 0 0 36 199 24 0 3 0 0 0 100 199 24 0 3 0 0 0 132 197 24 0 3 0 0 0]!

Item was added:
+ ----- Method: ImageFileHeaderTest>>sample6505HeaderData (in category 'running') -----
+ sample6505HeaderData
+ 	"First 200 bytes of an image file saved by a Cog VM, an ImageFileHeader for
+ 	a 32-bit image with closure support and float words stored in native platform
+ 	order (6505)"
+ 
+ 	^#[105 25 0 0 64 0 0 0 28 181 88 8 0 224 70 183 180 143 138 188 71 229 231 47 151 3 160 4 2 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 193 111 202 183 5 0 0 30 73 113 202 183 5 0 160 24 133 112 202 183 5 0 12 23 15 129 56 0 124 90 95 183 252 245 70 183 4 1 0 0 20 17 203 183 0 50 188 26 72 166 95 183 3 0 0 0 248 164 95 183 3 0 0 0 48 156 95 183 3 0 0 0 72 156 95 183 3 0 0 0 60 156 95 183 3 0 0 0 36 156 95 183 3 0 0 0 56 92 95 183 3 0 0 0 96 97 95 183 3 0 0 0 20 167 95 183 3 0 0 0 84 167 95 183 3 0 0 0 116 165 95 183 3 0 0 0]!

Item was added:
+ ----- Method: ImageFileHeaderTest>>sample68002HeaderData (in category 'running') -----
+ sample68002HeaderData
+ 	"First 200 bytes of a 64-bit image file saved by an interpreter VM, an
+ 	ImageFileHeader for a 64-bit image with closure support and no native
+ 	platform float word order requirement (68002)"
+ 
+ 	^#[162 9 1 0 0 0 0 0 128 0 0 0 0 0 0 0 200 95 202 11 0 0 0 0 0 160 102 243 128 127 0 0 168 160 102 243 128 127 0 0 76 217 0 0 0 0 0 0 148 3 192 4 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 73 187 102 243 128 127 0 0 9 0 12 23 0 0 0 0 177 187 102 243 128 127 0 0 9 0 160 24 0 0 0 0 57 160 102 243 128 127 0 0 9 0 0 30 0 0 0 0 25 188 102 243 128 127 0 0 97 1 12 30 0 0 0 0 88 188 102 243 128 127 0 0]!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testAsByteArray (in category 'testing') -----
+ testAsByteArray
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := self sample6505HeaderData.
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: hdr asByteArray = b2.!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testCogStoreOn (in category 'testing') -----
+ testCogStoreOn
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 hdr2 |
+ 	b1 := ByteArray new: 64.
+ 	b1 at: 1 put: 104; at: 2 put: 25; at: 3 put: 0; at: 4 put: 0. "a valid image format number"
+ 	b1 at: 5 put: 64; at: 6 put: 0; at: 7 put: 0; at: 8 put: 0. "header size 64"
+ 	9 to: 64 do: [ :i | b1 at: i put: i ].
+ 	hdr := CogImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ''.
+ 	hdr storeOn: ws.
+ 	hdr2 := Compiler evaluate: ws contents.
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr2 writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 46) = (b1 first: 46).
+ 	self assert: (b2 last: (64 - 46)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWrite64BitBigEndian (in category 'testing') -----
+ testReadWrite64BitBigEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 128.
+ 	#[0 0 0 0 0 1 9 162 0 0 0 0 0 0 0 128] withIndexDo: [ :e :i | b1 at: i put: e].
+ 	17 to: 128 do: [ :i | b1 at: i put: i ].
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: false.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 72) = (b1 first: 72).
+ 	self assert: (b2 last: (128 - 72)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWrite64BitCogBigEndian (in category 'testing') -----
+ testReadWrite64BitCogBigEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 128.
+ 	#[0 0 0 0 0 1 9 162 0 0 0 0 0 0 0 128] withIndexDo: [ :e :i | b1 at: i put: e].
+ 	17 to: 128 do: [ :i | b1 at: i put: i ].
+ 	hdr := CogImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: false.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 92) = (b1 first: 92).
+ 	self assert: (b2 last: (128 - 92)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWrite64BitCogLittleEndian (in category 'testing') -----
+ testReadWrite64BitCogLittleEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 128.
+ 	#[162 9 1 0 0 0 0 0 128 0 0 0 0 0 0 0] withIndexDo: [ :e :i | b1 at: i put: e].
+ 	17 to: 128 do: [ :i | b1 at: i put: i ].
+ 	hdr := CogImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 92) = (b1 first: 92).
+ 	self assert: (b2 last: (128 - 92)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWrite64BitLittleEndian (in category 'testing') -----
+ testReadWrite64BitLittleEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 128.
+ 	#[162 9 1 0 0 0 0 0 128 0 0 0 0 0 0 0] withIndexDo: [ :e :i | b1 at: i put: e].
+ 	17 to: 128 do: [ :i | b1 at: i put: i ].
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 72) = (b1 first: 72).
+ 	self assert: (b2 last: (128 - 72)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWriteBigEndian (in category 'testing') -----
+ testReadWriteBigEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 64.
+ 	b1 at: 4 put: 104; at: 3 put: 25; at: 2 put: 0; at: 1 put: 0. "a valid image format number"
+ 	b1 at: 8 put: 64; at: 7 put: 0; at: 6 put: 0; at: 5 put: 0. "header size 64"
+ 	9 to: 64 do: [ :i | b1 at: i put: i ].
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: false.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 36) = (b1 first: 36).
+ 	self assert: (b2 last: (64 - 36)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWriteCogBigEndian (in category 'testing') -----
+ testReadWriteCogBigEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 64.
+ 	b1 at: 4 put: 104; at: 3 put: 25; at: 2 put: 0; at: 1 put: 0. "a valid image format number"
+ 	b1 at: 8 put: 64; at: 7 put: 0; at: 6 put: 0; at: 5 put: 0. "header size 64"
+ 	9 to: 64 do: [ :i | b1 at: i put: i ].
+ 	hdr := CogImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: false.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 46) = (b1 first: 46).
+ 	self assert: (b2 last: (64 - 46)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWriteCogLittleEndian (in category 'testing') -----
+ testReadWriteCogLittleEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 64.
+ 	b1 at: 1 put: 104; at: 2 put: 25; at: 3 put: 0; at: 4 put: 0. "a valid image format number"
+ 	b1 at: 5 put: 64; at: 6 put: 0; at: 7 put: 0; at: 8 put: 0. "header size 64"
+ 	9 to: 64 do: [ :i | b1 at: i put: i ].
+ 	hdr := CogImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 46) = (b1 first: 46).
+ 	self assert: (b2 last: (64 - 46)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testReadWriteLittleEndian (in category 'testing') -----
+ testReadWriteLittleEndian
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := ByteArray new: 64.
+ 	b1 at: 1 put: 104; at: 2 put: 25; at: 3 put: 0; at: 4 put: 0. "a valid image format number"
+ 	b1 at: 5 put: 64; at: 6 put: 0; at: 7 put: 0; at: 8 put: 0. "header size 64"
+ 	9 to: 64 do: [ :i | b1 at: i put: i ].
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 36) = (b1 first: 36).
+ 	self assert: (b2 last: (64 - 36)) asSet size = 1. "all zeros"!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testSample6504Header (in category 'testing') -----
+ testSample6504Header
+ 	"Using data from a real file header, verify conversions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := self sample6504HeaderData.
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: b2 = (b1 first: 64).!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testSample6505Header (in category 'testing') -----
+ testSample6505Header
+ 	"Using data from a real file header, verify conversions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := self sample6505HeaderData.
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: b2 = (b1 first: 64).!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testSample68002Header (in category 'testing') -----
+ testSample68002Header
+ 	"Using data from a real file header, verify conversions"
+ 
+ 	| hdr ws b1 b2 |
+ 	b1 := self sample68002HeaderData.
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: b2 = (b1 first: 128).!

Item was added:
+ ----- Method: ImageFileHeaderTest>>testStoreOn (in category 'testing') -----
+ testStoreOn
+ 	"Read and write with data in all byte positions"
+ 
+ 	| hdr ws b1 b2 hdr2 |
+ 	b1 := ByteArray new: 64.
+ 	b1 at: 1 put: 104; at: 2 put: 25; at: 3 put: 0; at: 4 put: 0. "a valid image format number"
+ 	b1 at: 5 put: 64; at: 6 put: 0; at: 7 put: 0; at: 8 put: 0. "header size 64"
+ 	9 to: 64 do: [ :i | b1 at: i put: i ].
+ 	hdr := ImageFileHeader readFrom: (ReadStream on: b1).
+ 	ws := WriteStream on: ''.
+ 	hdr storeOn: ws.
+ 	hdr2 := Compiler evaluate: ws contents.
+ 	ws := WriteStream on: ByteArray new.
+ 	hdr2 writeTo: ws littleEndian: true.
+ 	b2 := ws contents.
+ 	self assert: (b2 first: 36) = (b1 first: 36).
+ 	self assert: (b2 last: (64 - 36)) asSet size = 1. "all zeros"!

Item was changed:
  Object subclass: #ImageFormat
  	instanceVariableNames: 'wordSize requiresClosureSupport requiresNativeFloatWordOrder'
  	classVariableNames: 'BaseVersionMask BaseVersionNumbers CapabilitiesBitsMask KnownVersionNumbers PlatformByteOrderBit ReservedBitsMask'
  	poolDictionaries: ''
+ 	category: 'ImageFormat-Header'!
- 	category: 'ImageFormat'!
  
  !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>>allVersionNumberByteArrays (in category 'utility') -----
- ----- Method: ImageFormat class>>allVersionNumberByteArrays (in category 'image formats') -----
  allVersionNumberByteArrays
  	"All known version numbers expressed as byte arrays of size 4 and 8 in little
  	endian and big endian byte ordering."
  
  	"ImageFormat allVersionNumberByteArrays"
  
  	| byteArrays |
  	byteArrays := OrderedCollection new.
  	KnownVersionNumbers do: [:version |
  		byteArrays add: ((WriteStream on: (ByteArray new: 4)) nextNumber: 4 put: version; yourself) contents.
  		byteArrays add: ((WriteStream on: (ByteArray new: 8)) nextNumber: 8 put: version; yourself) contents.
  		byteArrays add: ((WriteStream on: (ByteArray new: 4)) nextLittleEndianNumber: 4 put: version; yourself) contents.
  		byteArrays add: ((WriteStream on: (ByteArray new: 8)) nextLittleEndianNumber: 8 put: version; yourself) contents].
  	^byteArrays!

Item was added:
+ ----- Method: ImageFormat class>>availableBits (in category 'image formats') -----
+ availableBits
+ 	"Bits available for use as capability bits. Reserve high order bit as the
+ 	extension bit, to be set true if additional bits are required in the future."
+ 	
+ 	"ImageFormat availableBits printStringBase: 2"
+ 
+ 	| mask |
+ 	mask := 0.
+ 	self bitAssignments doWithIndex: [ :e :i |
+ 		mask := mask bitAt: i put: (e isNil ifTrue: [ 1 ] ifFalse: [ 0 ])].
+ 	^ mask
+ !

Item was changed:
+ ----- Method: ImageFormat class>>baseVersionMask (in category 'image formats') -----
- ----- Method: ImageFormat class>>baseVersionMask (in category 'initialize-release') -----
  baseVersionMask
  	"Mask the bits associated with base format number exclusive of capability bits"
  
  	"ImageFormat baseVersionMask printStringBase: 2"
  
  	^ BaseVersionNumbers
  		inject: 0
  		into: [:accum :e | accum bitOr: e]
  !

Item was changed:
+ ----- Method: ImageFormat class>>baseVersionNumbers (in category 'image formats') -----
- ----- Method: ImageFormat class>>baseVersionNumbers (in category 'initialize-release') -----
  baseVersionNumbers
  	"The well-known image format versions for basic 32 and 64 bit images,
  	including images that require closure bytecode support. These base
  	format numbers my be modified by application of various capability bits
  	representing additional requirements that the image expects to be
  	supported by the virtual machine."
  
  	^#(6502 6504 68000 68002)
  !

Item was added:
+ ----- Method: ImageFormat class>>bitAssignments (in category 'initialize-release') -----
+ 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: nil.	"unassigned bit available for future image formats"
+ 	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: 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>>bitsInUse (in category 'image formats') -----
  bitsInUse
  	"Answer a mask of the bits used by all known version format numbers"
  
  	"Transcript cr; show: (ImageFormat bitsInUse printStringBase: 2)"
  
+ 	| mask |
+ 	mask := 0.
+ 	self bitAssignments doWithIndex: [ :e :i |
+ 		mask := mask bitAt: i put: (e notNil ifTrue: [ 1 ] ifFalse: [ 0 ])].
+ 	^ mask
+ !
- 	^ self baseVersionMask bitOr: self capabilitiesBitsMask!

Item was changed:
+ ----- Method: ImageFormat class>>capabilitiesBitsMask (in category 'image formats') -----
- ----- Method: ImageFormat class>>capabilitiesBitsMask (in category 'initialize-release') -----
  capabilitiesBitsMask
  	"Bits currently used as capability bits."
  	
  	"ImageFormat capabilitiesBitsMask printStringBase: 2"
  
  	^PlatformByteOrderBit "only one so far"
  !

Item was changed:
+ ----- Method: ImageFormat class>>createCkStatusProgram (in category 'ckformat') -----
- ----- Method: ImageFormat class>>createCkStatusProgram (in category 'utility') -----
  createCkStatusProgram
  	"Create ckformat source file in the default directory"
  
  	"ImageFormat createCkStatusProgram"
  
  	^self storeCkstatusOnFile: 'ckformat.c' !

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

Item was changed:
  ----- Method: ImageFormat class>>knownVersionNumbers (in category 'initialize-release') -----
  knownVersionNumbers
+ 	"Version numbers currently in use or likely to be used (e.g. 64-bit Cog formats)"
- 	"Version number 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 four variants"
+ 		{
+ 			6505 .	"Cog and StackVM"
+ 			68003	"Cog and StackVM running 64-bit image"
+ 				" ... add others here as bits are allocated to represent requirements of other image formats"
+ 		}
+ !
- 	^ #(6502 6504 6505 68000 68002 68003)!

Item was removed:
- ----- Method: ImageFormat class>>reservedBitsMask (in category 'initialize-release') -----
- reservedBitsMask
- 	"Bits available for use as capability bits. Reserve high order bit as the
- 	extension bit, to be set true if additional bits are required in the future."
- 	
- 	"ImageFormat reservedBitsMask printStringBase: 2"
- 
- 	^(16rFFFFFFFF bitXor: BaseVersionMask)
- 		bitAt: PlatformByteOrderBit put: 0
- !

Item was changed:
+ ----- Method: ImageFormat class>>storeCkstatusOnFile: (in category 'ckformat') -----
- ----- Method: ImageFormat class>>storeCkstatusOnFile: (in category 'utility') -----
  storeCkstatusOnFile: fileName
  	"Store source code for an image format version reader in a file. The program
  	is intended for testing image file format from a unix shell script such that
  	the shell script can decide what VM to run based on image requirements."
  
  	| f |
  	f := CrLfFileStream newFileNamed: fileName.
  	[self generateCkStatusProgram: 'ckformat' on: f]
  		ensure: [f ifNotNil: [f close]].
  	^fileName!

Item was changed:
+ ----- Method: ImageFormat class>>versionDescriptions (in category 'utility') -----
- ----- Method: ImageFormat class>>versionDescriptions (in category 'image formats') -----
  versionDescriptions
  
  	"ImageFormat versionDescriptions"
  	"ImageFormat versionDescriptions do: [:e | Transcript cr; show: e]"
  
  	^ Dictionary
  		withAll: (KnownVersionNumbers
  				collect: [:e | e -> (self fromInteger: e) description])!

Item was changed:
+ ----- Method: ImageFormat class>>versionNumberByteArrays (in category 'utility') -----
- ----- Method: ImageFormat class>>versionNumberByteArrays (in category 'image formats') -----
  versionNumberByteArrays
  	"All byte array expressions of known version numbers. These are the possible values
  	that may appear in the first 4 or 8 bytes of a saved image file. A 64 bit image saves
  	its image format number as a 64 bit value in the file header, and a 32 bit image saves
  	its image format as a 32 bit value. The value may be stored in little endian or big endian
  	byte ordering depending on the host platform."
  
  	"ImageFormat versionNumberByteArrays do: [:e |
  		Transcript cr; show: e printString , ': ', (ImageFormat fromBytes: e) description]"
  
  	^self allVersionNumberByteArrays select: [:e |
  		e size = (self fromBytes: e) wordSize]
  !

Item was changed:
  ----- Method: ImageFormat>>printDescriptionOn: (in category 'printing') -----
  printDescriptionOn: stream
  
+ 		stream nextPutAll: 'a ';
- 		stream nextPutAll: 'A ';
  			nextPutAll: (wordSize * 8) asString;
  			nextPutAll: '-bit 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'].
  		stream nextPutAll: ' (';
  			nextPutAll: self asInteger asString;
  			nextPut: $).
  		^ stream
  !

Item was added:
+ ----- Method: ImageFormat>>storeOn: (in category 'printing') -----
+ storeOn: aStream 
+ 	"Append to the argument aStream a sequence of characters that is an 
+ 	expression whose evaluation creates an object similar to the receiver."
+ 
+ 	aStream nextPutAll: self class name;
+ 		nextPutAll: ' fromInteger: ';
+ 		nextPutAll: self asInteger asString!

Item was changed:
  TestCase subclass: #ImageFormatTest
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'ImageFormat-Tests'!
- 	category: 'ImageFormat'!
  
  !ImageFormatTest commentStamp: 'dtl 9/5/2010 13:41' prior: 0!
  Verify and document the values of ImageFormat. The image format is an integer value that identifies the format of an image snapshot and the capabilities that the image expects of the virtual machine.!



More information about the Vm-dev mailing list