Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Smalltalk imageFormatVersion
Last updated at 9:31 pm UTC on 26 May 2018
 Smalltalk imageFormatVersion 
evaluates to
    6521
in a Squeak6.0a 32bit image.

more formats see VM run utility script


Format no
 6502 
is for the interpreter VM. It is used by all Squeakland Etoys images.

Squeak 6.0a can load ImageSegments in the 6502 and 6521 formats.

List of ImageSegment types see package ImageFormat.


Implementation of method #imageFormatVersion in Squeak 6.0a
imageFormatVersion
	"Answer an integer identifying the type of image in memory. The image version number may
	identify the format of the image (e.g. 32 or 64-bit word size) or specific requirements
	of the image (e.g. block closure support required). This invokes an optional primitive
	that may not be available on all virtual machines."

	"Smalltalk image imageFormatVersion"

	<primitive: 'primitiveImageFormatVersion'>

	"Cog provides a VM parameter"
	^[Smalltalk vm vmParameterAt: 41]
		on: Error
		do: [self notify: 'This virtual machine does not support the optional ',
				'primitive #primitiveImageFormatVersion' translated.
			nil]


Identical implementation is in Squeak 4.4. However a regular VM in the Squeak 4.4 All-In-One package does not implement
= primitive #primitiveImageFormatVersion
so the method fails.

If you use the same 4.4 image with a newer VM you get
 Smalltalk imageFormatVersion 
     6505


  1. imageFormatVersion used in Squeak 6.0a

ImageSegment loadSegmentFrom:outPointers:


 loadSegmentFrom: segment outPointers: outPointers
	"Attempt to load the segment into memory (reify the objects in segment
	 as real objects), using outPointers to bind references to objects not in the
	 segment.  Answer a collection of all the objects in the segment."
	| segmentFormat |
	state == #imported ifTrue:
		[segmentFormat := segment first bitAnd: 16rFFFFFF.
		 segmentFormat = 6502 ifTrue:
			[LegacyImageSegment adoptInstance: self.
			 ^self loadSegmentFrom: segment outPointers: outPointers].
		 segmentFormat = Smalltalk imageFormatVersion ifTrue:
			[NativeImageSegment adoptInstance: self.
			 ^self loadSegmentFrom: segment outPointers: outPointers].
		 self error: 'no handling for format ', segmentFormat asString. ' in a ', Smalltalk imageFormatVersion asString, ' image.'].
	self subclassResponsibility