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

commits at source.squeak.org commits at source.squeak.org
Fri Jul 2 01:30:59 UTC 2021


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

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

Name: VMMaker.oscog-eem.2976
Author: eem
Time: 1 July 2021, 6:30:50.354591 pm
UUID: cbac1851-3b99-4b47-b5e7-2b313c2e9f61
Ancestors: VMMaker.oscog-eem.2975

Fix 16r80000000 < 16r8000000000000000 on ARMv8

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

Item was changed:
  ----- Method: CoInterpreter>>initStackPagesAndInterpret (in category 'initialization') -----
  initStackPagesAndInterpret
  	"Initialize the stack pages and enter interpret. Use alloca'ed memory so that when
  	 we have a JIT its stack pointer will be on the native stack since alloca allocates
  	 memory on the stack. Certain thread systems use the native stack pointer as the
  	 frame ID so putting the stack anywhere else can confuse the thread system."
  
  	"Override to establish the setjmp/longjmp handler for reentering the interpreter
  	 from machine code, and disable executablity on the heap and stack pages."
  
  	"This should be in its own initStackPages method but Slang can't inline
  	 C code strings."
  	| stackPageBytes stackPagesBytes theStackMemory |
  	<var: #theStackMemory type: #'char *'>
  	stackPageBytes := self stackPageByteSize.
  	stackPagesBytes := self computeStackZoneSize.
  	theStackMemory := self
  							cCode: [self alloca: stackPagesBytes]
  							inSmalltalk: [stackPages initializeWithByteSize: stackPagesBytes for: self].
  	self cCode: [self memset: theStackMemory _: 0 _: stackPagesBytes].
- 	self sqMakeMemoryNotExecutableFrom: objectMemory startOfMemory asUnsignedInteger
- 		To: objectMemory memoryLimit asUnsignedInteger.
- 	self sqMakeMemoryNotExecutableFrom: theStackMemory asUnsignedInteger
- 		To: theStackMemory asUnsignedInteger + stackPagesBytes.
  	stackPages
  		initializeStack: theStackMemory
  		numSlots: stackPagesBytes / objectMemory wordSize
  		pageSize: stackPageBytes / objectMemory wordSize.
  	self assert: self minimumUnusedHeadroom = stackPageBytes.
  
  	"Once the stack pages are initialized we can continue to bootstrap the system."
  	self loadInitialContext.
  	"We're ready for the heartbeat (poll interrupt)"
  	self ioInitHeartbeat.
  	self initialEnterSmalltalkExecutive.
  	^nil!

Item was removed:
- ----- Method: CoInterpreter>>initializeCodeGenerator (in category 'initialization') -----
- initializeCodeGenerator
- 	cogit
- 		initializeCodeZoneFrom: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize])
- 		upTo: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize]) + cogCodeSize!

Item was removed:
- ----- Method: CoInterpreter>>initializeCodeGenerator:executableZone: (in category 'initialization') -----
- initializeCodeGenerator: writableCodeZone executableZone: executableZone
- 	"If the OS platform requires dual mapping to achieve a writable code zone
- 	 then writableCodeZone will be the non-zero address of the read/write zone
- 	 and executableZone will be the address of the read/execute zone.  If the OS
- 	 platform does not require dual mapping then writableCodeZone will be the
- 	 first address past the guard page  and executableZone will be zero (i.e. we
- 	 use the first cogCodeSize bytes of memory to house the code zone)."
- 	cogit
- 		initializeCodeZoneFrom: executableZone
- 		upTo: executableZone + cogCodeSize
- 		writableCodeZone: writableCodeZone.
- 	self assert: heapBase >= (writableCodeZone + cogCodeSize max: executableZone + cogCodeSize)!

Item was changed:
  ----- Method: CoInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating an amount of memory to its object heap.
  	
  	 V3: desiredHeapSize is the total size of the heap.  Fail if the image has an unknown format or
  	 requires more than the specified amount of memory.
  
  	 Spur: desiredHeapSize is ignored; this routine will attempt to provide at least extraVMMemory's
  	 ammount of free space after the image is loaded, taking any free space in the image into account.
  	 extraVMMemory is stored in the image header and is accessible as vmParameterAt: 23.  If
  	 extraVMMemory is 0, the value defaults to the default grow headroom.  Fail if the image has an
  	 unknown format or if sufficient memory cannot be allocated.
  
  	 Details: This method detects when the image was stored on a machine with the opposite byte
  	 ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header
  	 information to start 512 bytes into the file, since some file transfer programs for the Macintosh
  	 apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix
  	 area could also be used to store an exec command on Unix systems, allowing one to launch
  	 Smalltalk by invoking the image name as a command."
  
+ 	| swapBytes headerStart headerSize headerFlags dataSize bytesRead bytesToShift heapSize
+ 	  oldBaseAddr minimumMemory allocationReserve cogCodeBase
+ 	  firstSegSize hdrNumStackPages hdrEdenBytes hdrCogCodeSize hdrMaxExtSemTabSize |
- 	| swapBytes headerStart headerSize dataSize oldBaseAddr
- 	  minimumMemory heapSize bytesRead bytesToShift firstSegSize
- 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize allocationReserve |
  	<var: #f type: #sqImageFile>
  	<var: #heapSize type: #usqInt>
  	<var: #dataSize type: #'size_t'>
  	<var: #minimumMemory type: #usqInt>
  	<var: #desiredHeapSize type: #usqInt>
  	<var: #allocationReserve type: #usqInt>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #imageOffset type: #squeakFileOffsetType>
  
  	metaclassNumSlots := 6.	"guess Metaclass instSize"
  	classNameIndex := 6.		"guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - 4.  "record header start position"
  
  	headerSize			:= self getWord32FromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes. "N.B.  ignored in V3."
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default.  Can be changed via vmParameterAt: 43 put: n.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [cogit defaultCogCodeSize]
  									ifFalse: [desiredCogCodeSize := hdrCogCodeSize]]. "set for vmParameter 47"
  	cogCodeSize > cogit maxCogCodeSize ifTrue:
  		[cogCodeSize := cogit maxCogCodeSize].
  	hdrEdenBytes		:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	minimumMemory := cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ objectMemory newSpaceBytes
  						+ allocationReserve.
+ 	"Compute how much space is needed for the initial heap allocation.
+ 	 no need to include the stackZone; this is alloca'ed.
+ 	 no need to include the JIT code zone size; this is allocated separately."
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
+ 						  dataSize
- 						   cogCodeSize "no need to include the stackZone; this is alloca'ed"
- 						+ dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
+ 			[heapSize :=  desiredHeapSize
- 			[heapSize :=  cogCodeSize "no need to include the stackZone; this is alloca'ed"
- 						+ desiredHeapSize
  						+ objectMemory newSpaceBytes
  						+ (desiredHeapSize - dataSize > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve]).
  			 heapSize < minimumMemory ifTrue:
  				[self insufficientMemorySpecifiedError]].
  
+ 	"allocateJITMemory will assign the actual size allocated, which is rounded up to a page boundary."
+ 	cogCodeBase := self allocateJITMemory: (self addressOf: cogCodeSize).
+ 
  	"allocate a contiguous block of memory for the Squeak heap and ancilliary data structures"
+ 	(self
+ 			allocateMemory: heapSize
+ 			minimum: minimumMemory
+ 			imageFile: f
+ 			headerSize: headerSize) asUnsignedInteger
+ 		ifNil: [self insufficientMemoryAvailableError]
+ 		ifNotNil:
+ 			[:mem| "cannot clash with the variable memory still in use in NewCoObjectMemory and superclasses"
+ 			objectMemory
+ 				setHeapBase: (heapBase := mem)
+ 				memoryLimit: mem + heapSize
+ 				endOfMemory: mem + dataSize].
- 	objectMemory memory: (self
- 								allocateMemory: heapSize
- 								minimum: minimumMemory
- 								imageFile: f
- 								headerSize: headerSize) asUnsignedInteger.
- 	objectMemory memory ifNil:
- 		[self insufficientMemoryAvailableError].
  
- 	heapBase := objectMemory
- 					setHeapBase: objectMemory memory + cogCodeSize
- 					memoryLimit: objectMemory memory + heapSize
- 					endOfMemory: objectMemory memory + cogCodeSize + dataSize.
- 
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
+ 	cogit initializeCodeZoneFrom: cogCodeBase upTo: cogCodeBase + cogCodeSize.
- 	self initializeCodeGenerator.
  	^dataSize!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMulOverflowRRR (in category 'generate machine code - concretize processor-specific') -----
  concretizeMulOverflowRRR
  	"ARMv8 has no multiply overflow detection.  Instead it is synthesized from the two halves of
  	 a 64x64=>128 bit multiply. The upper 64-bits are tested.  The sequence is
  		low64 := MUL a,b
  		high64 := SMULH a,b
  		signBit := low64 >> 63
  		high64 := high64 + signBit
  	 If high64 is zero after this sequence then the multiply has not overflowed, since
  	 high64 is an extension of signBit if no overflow (either 0 or -1) and -1 + 1 = 0.
  	 However, since we restrict ourselves to three concrete ARMv8 instructions per abstract instruction
  	 we move the last operation of the sequence to concretizeMulOverflowJump
  
  	 C6.2.196	MUL				C6-1111
  	 C6.2.242	SMULH				C6-1184
  	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
  
  	<inline: true>
  	| reg1 reg2 reg3 |
  	reg1 := operands at: 0.
  	reg2 := operands at: 1.
  	reg3 := operands at: 2.
+ 	"RISCTempReg := high(reg1 * reg2); must orecede destructive MUL"
- 	"reg3 := reg1 * reg2"
  	machineCode
  		at: 0
+ 		put: 2r1001101101 << 22
- 		put: 2r10011011 << 24
  			+ (reg1 << 16)
  			+ (XZR << 10)
  			+ (reg2 << 5)
+ 			+ RISCTempReg.
+ 	"reg3 := reg1 * reg2"
- 			+ reg3.
- 	"RISCTempReg := high(reg1 * reg2)"
  	machineCode
  		at: 1
+ 		put: 2r10011011 << 24
- 		put: 2r1001101101 << 22
  			+ (reg1 << 16)
  			+ (XZR << 10)
  			+ (reg2 << 5)
+ 			+ reg3.
- 			+ RISCTempReg.
  	"CArg1Reg := sign(reg3)"
  	machineCode
  		at: 2
  		put: 2r1101001101 << 22
  			+ (63 << 16) "constant to shift by"
  			+ (63 << 10)
  			+ (reg3 << 5)
  			+ CArg1Reg. "cuz CArg0Reg == TempReg"
  	"RISCTempReg := RISCTempReg + CArg1Reg/sign
  	 is in concretizeMulOverflowJump"
  	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
  	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
  	"cogit processor disassembleInstructionAt: 8 In: machineCode object"
  	^12!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialize-release') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize hdrCogCodeSize
  	  stackZoneSize methodCacheSize primTraceLogSize allocationReserve |
  	"open image file and read the header"
  
  	(f := self openImageFileNamed: fileName) ifNil: [^self].
  
  	"Set the image name and the first argument; there are
  	 no arguments during simulation unless set explicitly."
  	systemAttributes at: 1 put: fileName.
  
  	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
  
  	version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := version byteSwap32) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getWord32FromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [cogit defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  	hdrEdenBytes	:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * objectMemory wordSize.
  	primTraceLogSize := primTraceLog size * objectMemory wordSize.
  
  	"To cope with modern OSs that disallow executing code in writable memory we dual-map
  	 the code zone, one mapping with read/write permissions and the other with read/execute
  	 permissions. In simulation all we can do is use memory, so if we're simulating dual mapping
  	 we use double the memory and simulate the memory sharing in the Cogit's backEnd."
  	effectiveCogCodeSize := (InitializationOptions at: #DUAL_MAPPED_CODE_ZONE ifAbsent: [false])
  								ifTrue: [cogCodeSize * 2]
  								ifFalse: [cogCodeSize].
  
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
  	heapBase := (Cogit guardPageSize
  				+ effectiveCogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  dataSize
  						+ extraBytes
  						+ objectMemory newSpaceBytes
  						+ (extraBytes > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])].
  	"allocate interpreter memory"
+ 	heapBase := objectMemory
+ 					setHeapBase: heapBase
+ 					memoryLimit: heapBase + heapSize
+ 					endOfMemory: heapBase + dataSize. "bogus for Spur"
- 	heapBase := objectMemory startOfMemory.
- 	objectMemory
- 		setHeapBase: heapBase
- 		memoryLimit: heapBase + heapSize
- 		endOfMemory: heapBase + dataSize. "bogus for Spur"
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
  	objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	count ~= dataSize ifTrue: [self halt]]
  		ensure: [f close].
  	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize.
  	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	UIManager default
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
+ 	cogit
+ 		initializeCodeZoneFrom: Cogit guardPageSize
+ 		upTo: Cogit guardPageSize + cogCodeSize!
- 	self initializeCodeGenerator!

Item was changed:
  ----- Method: Cogit class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are
  	 accessed from VM support code, or that need visibility at the gdb/lldb level."
  	^#('ceBaseFrameReturnTrampoline' ceCaptureCStackPointers 'ceCheckForInterruptTrampoline'
  		ceEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverReg
  		ceCallCogCodePopReceiverReg realCECallCogCodePopReceiverReg
  		ceCallCogCodePopReceiverAndClassRegs realCECallCogCodePopReceiverAndClassRegs
  		ceInvokeInterpret 'ceReturnToInterpreterTrampoline' 'ceCannotResumeTrampoline'
  		ceTryLockVMOwner
  		'cmEntryOffset' 'cmNoCheckEntryOffset' 'cmDynSuperEntryOffset' 'cmSelfSendEntryOffset'
  		'missOffset' 'cbEntryOffset' 'cbNoSwitchEntryOffset' 'blockNoContextSwitchOffset' breakPC
  		ceGetFP ceGetSP cFramePointerInUse
+ 		methodZoneBase
  		traceFlags traceStores)
  			includes: var!

Item was changed:
  ----- Method: Cogit>>minCogMethodAddress (in category 'debugging') -----
  minCogMethodAddress
  	<api>
+ 	<cmacro: '() methodZoneBase'>
  	^methodZoneBase!

Item was changed:
  ----- Method: NewCoObjectMemory>>growObjectMemory: (in category 'allocation') -----
  growObjectMemory: delta 
  	"Attempt to grow the object memory by the given delta amount."
  	| limit |
  	statGrowMemory := statGrowMemory + 1.
  	limit := self sqGrowMemory: memoryLimit By: delta.
  	limit = memoryLimit ifFalse:
  		[self setMemoryLimit: limit - 24. "remove a tad for safety"
+ 		 self initializeMemoryFirstFree: freeStart]!
- 		 self initializeMemoryFirstFree: freeStart.
- 		 coInterpreter sqMakeMemoryNotExecutableFrom: self startOfMemory To: memoryLimit]!

Item was changed:
  VMClass subclass: #ObjectMemory
+ 	instanceVariableNames: 'memory youngStart endOfMemory memoryLimit nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount rootTableOverflowed extraRoots extraRootCount weakRoots weakRootCount child field parentField freeBlock lastHash allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount allocationsBetweenGCs tenuringThreshold gcBiasToGrow gcBiasToGrowGCLimit gcBiasToGrowThreshold statFullGCs statIncrGCs statFullGCUsecs statIncrGCUsecs statGCEndTime statIGCDeltaUsecs statTenures statRootTableOverflows freeContexts freeLargeContexts interruptCheckCounter totalObjectCount shrinkThreshold growHeadroom headerTypeBytes youngStartLocal statMarkCount statMarkCountLocal statSweepCount statMkFwdCount statCompMoveCount statGrowMemory statShrinkMemory statRootTableCount statAllocationCount statSurvivorCount statSpecialMarkCount forceTenureFlag gcStartUsecs oldSpaceStart'
- 	instanceVariableNames: 'memory youngStart endOfMemory memoryLimit nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount rootTableOverflowed extraRoots extraRootCount weakRoots weakRootCount child field parentField freeBlock lastHash allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount allocationsBetweenGCs tenuringThreshold gcBiasToGrow gcBiasToGrowGCLimit gcBiasToGrowThreshold statFullGCs statIncrGCs statFullGCUsecs statIncrGCUsecs statGCEndTime statIGCDeltaUsecs statTenures statRootTableOverflows freeContexts freeLargeContexts interruptCheckCounter totalObjectCount shrinkThreshold growHeadroom headerTypeBytes youngStartLocal statMarkCount statMarkCountLocal statSweepCount statMkFwdCount statCompMoveCount statGrowMemory statShrinkMemory statRootTableCount statAllocationCount statSurvivorCount statSpecialMarkCount forceTenureFlag gcStartUsecs'
  	classVariableNames: 'AllButHashBits AllButImmutabilityBit AllButMarkBit AllButMarkBitAndTypeMask AllButRootBit Done ExtraRootSize GCTopMarker HashBits HeaderTypeClass HeaderTypeExtraBytes HeaderTypeFree HeaderTypeGC LongSizeNumBits NilContext RemapBufferSize RootTableRedZone RootTableSize StartField StartObj Upward WeakRootTableSize WordMask'
  	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMObjectIndices VMSqueakClassIndices VMSqueakV3ObjectRepresentationConstants'
  	category: 'VMMaker-Interpreter'!
  
  !ObjectMemory commentStamp: '<historical>' prior: 0!
  This class describes a 32-bit direct-pointer object memory for Smalltalk.  The model is very simple in principle:  a pointer is either a SmallInteger or a 32-bit direct object pointer.
  
  SmallIntegers are tagged with a low-order bit equal to 1, and an immediate 31-bit 2s-complement signed value in the rest of the word.
  
  All object pointers point to a header, which may be followed by a number of data fields.  This object memory achieves considerable compactness by using a variable header size (the one complexity of the design).  The format of the 0th header word is as follows:
  
  	3 bits	reserved for gc (mark, root, unused)
  	12 bits	object hash (for HashSets)
  	5 bits	compact class index
  	4 bits	object format
  	6 bits	object size in 32-bit words
  	2 bits	header type (0: 3-word, 1: 2-word, 2: forbidden, 3: 1-word)
  
  If a class is in the compact class table, then this is the only header information needed.  If it is not, then it will have another header word at offset -4 bytes with its class in the high 30 bits, and the header type repeated in its low 2 bits.  It the objects size is greater than 255 bytes, then it will have yet another header word at offset -8 bytes with its full word size in the high 30 bits and its header type repeated in the low two bits.
  
  The object format field provides the remaining information as given in the formatOf: method (including isPointers, isVariable, isBytes, and the low 2 size bits of byte-sized objects).
  
  This implementation includes incremental (2-generation) and full garbage collection, each with compaction and rectification of direct pointers.  It also supports a bulk-become (exchange object identity) feature that allows many objects to be becomed at once, as when all instances of a class must be grown or shrunk.
  
  There is now a simple 64-bit version of the object memory.  It is the simplest possible change that could work.  It merely sign-extends all integer oops, and extends all object headers and oops by adding 32 zeroes in the high bits.  The format of the base header word is changed in one minor, not especially elegant, way.  Consider the old 32-bit header:
  	ggghhhhhhhhhhhhcccccffffsssssstt
  The 64-bit header is almost identical, except that the size field (now being in units of 8 bytes, has a zero in its low-order bit.  At the same time, the byte-size residue bits for byte objects, which are in the low order bits of formats 8-11 and 12-15, are now in need of another bit of residue.  So, the change is as follows:
  	ggghhhhhhhhhhhhcccccffffsssssrtt
  where bit r supplies the 4's bit of the byte size residue for byte objects.  Oh, yes, this is also needed now for 'variableWord' objects, since their size in 32-bit words requires a low-order bit.
  
  See the comment in formatOf: for the change allowing for 64-bit wide bitmaps, now dubbed 'variableLong'.!

Item was changed:
  ----- Method: ObjectMemory>>memory (in category 'accessing') -----
  memory
+ 	"memory is a simulation thing, but much more convenient to declare here than in every simulator subclass."
- 	<cmacro: '() GIV(memory)'>
  	^memory!

Item was changed:
  ----- Method: ObjectMemory>>setHeapBase:memoryLimit:endOfMemory: (in category 'initialization') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
  	"Set the dimensions of the heap, answering the start of oldSpace."
+ 	memory := baseOfHeap.
  	self setMemoryLimit: memLimit.
  	self setEndOfMemory: memEnd.
+ 	oldSpaceStart := baseOfHeap.
  	^baseOfHeap!

Item was removed:
- ----- Method: Spur32BitCoMemoryManager>>assimilateNewSegment: (in category 'growing/shrinking memory') -----
- assimilateNewSegment: segInfo
- 	"Update after adding a segment.
- 	 Here we make sure the new segment is not executable."
- 	<var: #segInfo type: #'SpurSegmentInfo *'>
- 	super assimilateNewSegment: segInfo.
- 	coInterpreter sqMakeMemoryNotExecutableFrom: segInfo segStart To: segInfo segLimit!

Item was changed:
  ----- Method: Spur32BitCoMemoryManager>>isInHeapBounds: (in category 'debug support') -----
  isInHeapBounds: address 
  	"Answer if the given address is within the entire range ST object memory.
  	 For quick checking during leak checking only!!"
+ 	^(self oop: address isGreaterThanOrEqualTo: cogit minCogMethodAddress)
- 	^(self oop: address isGreaterThanOrEqualTo: memory)
  	  and: [self oop: address isLessThan: endOfMemory]!

Item was removed:
- ----- Method: Spur32BitMMLECoSimulator>>isInHeapBounds: (in category 'debug support') -----
- isInHeapBounds: address 
- 	"Answer if the given address is within the entire range ST object memory.
- 	 For quick checking during leak checking only!!"
- 	^(self oop: address isGreaterThanOrEqualTo: cogit cogCodeBase)
- 	  and: [self oop: address isLessThan: endOfMemory]!

Item was removed:
- ----- Method: Spur64BitCoMemoryManager>>assimilateNewSegment: (in category 'growing/shrinking memory') -----
- assimilateNewSegment: segInfo
- 	"Update after adding a segment.
- 	 Here we make sure the new segment is not executable."
- 	<var: #segInfo type: #'SpurSegmentInfo *'>
- 	super assimilateNewSegment: segInfo.
- 	coInterpreter sqMakeMemoryNotExecutableFrom: segInfo segStart To: segInfo segLimit!

Item was changed:
  ----- Method: Spur64BitCoMemoryManager>>isInHeapBounds: (in category 'debug support') -----
  isInHeapBounds: address 
  	"Answer if the given address is within the entire range ST object memory.
  	 For quick checking during leak checking only!!"
+ 	^(self oop: address isGreaterThanOrEqualTo: cogit minCogMethodAddress)
- 	^(self oop: address isGreaterThanOrEqualTo: memory)
  	  and: [self oop: address isLessThan: endOfMemory]!

Item was removed:
- ----- Method: Spur64BitMMLECoSimulator>>isInHeapBounds: (in category 'debug support') -----
- isInHeapBounds: address 
- 	"Answer if the given address is within the entire range ST object memory.
- 	 For quick checking during leak checking only!!"
- 	^(self oop: address isGreaterThanOrEqualTo: cogit cogCodeBase)
- 	  and: [self oop: address isLessThan: endOfMemory]!

Item was changed:
  ----- Method: SpurMemoryManager class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
+ 	aCCodeGenerator removeVariable: 'memory'. "memory is a simulation time thing only"
+ 	self declareCAsOop: #(	freeStart scavengeThreshold newSpaceStart newSpaceLimit pastSpaceStart
- 	self declareCAsOop: #(	memory freeStart scavengeThreshold newSpaceStart newSpaceLimit pastSpaceStart
  							lowSpaceThreshold freeOldSpaceStart oldSpaceStart endOfMemory)
  		in: aCCodeGenerator.
  	self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs']), #(statAllocatedBytes)
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #lastHash type: #usqInt;
  		var: #freeListsMask type: #usqInt;
  		var: #freeLists type: #'sqInt *';
  		var: #objStackInvalidBecause type: #'char *';
  		var: #unscannedEphemerons type: #SpurContiguousObjStack;
  		var: #heapGrowthToSizeGCRatio type: #float;
  		var: #heapSizeAtPreviousGC type: #usqInt;
  		var: #totalFreeOldSpace type: #usqInt;
  		var: #maxOldSpaceSize type: #usqInt.
  	aCCodeGenerator
  		var: #oldSpaceUsePriorToScavenge type: #sqLong.
  	aCCodeGenerator
  		var: #remapBuffer
  		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #extraRoots
  		declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'!

Item was changed:
  ----- Method: SpurMemoryManager>>memory (in category 'accessing') -----
  memory
+ 	"memory is a simulation thing, but much more convenient to declare here than in every simulator subclass."
- 	<cmacro: '() GIV(memory)'>
  	^memory!

Item was changed:
  ----- Method: StackInterpreter>>dumpImage: (in category 'image save/restore') -----
  dumpImage: fileName
  	"Dump the entire image out to the given file. Intended for debugging only.  Doesn't work for Spur."
- 	| f dataSize result |
  	<notOption: #SpurObjectMemory>
  	<export: true>
  	<var: #f type: #sqImageFile>
  
+ 	(self sqImageFile: (self pointerForOop: fileName) Open: 'wb')
+ 		ifNil: [^-1]
+ 		ifNotNil:
+ 			[:f| | result |
+ 			result := self sq: (self pointerForOop: objectMemory startOfMemory)
+ 						Image: (self sizeof: #'unsigned char')
+ 						File: objectMemory endOfMemory - objectMemory startOfMemory
+ 						Write: f.
+ 			self sqImageFileClose: f.
+ 			^result]!
- 	f := self sqImageFile: (self pointerForOop: fileName) Open: 'wb'.
- 	f = nil ifTrue: [^-1].
- 	dataSize := objectMemory endOfMemory - objectMemory startOfMemory.
- 	result := self sq: (self pointerForOop: self memory) Image: (self sizeof: #'unsigned char') File: dataSize Write: f.
- 	self sqImageFileClose: f.
- 	^result!

Item was changed:
  ----- Method: StackInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating an amount of memory to its object heap.
  	
  	 V3: desiredHeapSize is the total size of the heap.  Fail if the image has an unknown format or
  	 requires more than the specified amount of memory.
  
  	 Spur: desiredHeapSize is ignored; this routine will attempt to provide at least extraVMMemory's
  	 ammount of free space after the image is loaded, taking any free space in teh image into account.
  	 extraVMMemory is stored in the image header and is accessible as vmParameterAt: 23.  If
  	 extraVMMemory is 0, the value defaults to the default grow headroom.  Fail if the image has an
  	 unknown format or if sufficient memory cannot be allocated.
  
  	 Details: This method detects when the image was stored on a machine with the opposite byte
  	 ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header
  	 information to start 512 bytes into the file, since some file transfer programs for the Macintosh
  	 apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix
  	 area could also be used to store an exec command on Unix systems, allowing one to launch
  	 Smalltalk by invoking the image name as a command."
  
  	| headerStart headerSize headerFlags dataSize oldBaseAddr swapBytes
  	  minimumMemory bytesRead bytesToShift heapSize firstSegSize
  	  hdrEdenBytes hdrMaxExtSemTabSize hdrNumStackPages allocationReserve |
  	<var: #f type: #sqImageFile>
  	<var: #heapSize type: #usqInt>
  	<var: #dataSize type: #'size_t'>
  	<var: #minimumMemory type: #usqInt>
  	<var: #desiredHeapSize type: #usqInt>
  	<var: #allocationReserve type: #usqInt>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #imageOffset type: #squeakFileOffsetType>
  
  	metaclassNumSlots := 6.	"guess Metaclass instSize"
  	classNameIndex := 6.		"guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - 4.  "record header start position"
  
  	headerSize			:= self getWord32FromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default.  Can be changed via vmParameterAt: 43 put: n.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 It is used for the cog code size in Cog.  Preserve it to be polite to other VMs."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	hdrEdenBytes		:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	minimumMemory := dataSize
  						+ objectMemory newSpaceBytes
  						+ allocationReserve.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  desiredHeapSize
  						+ objectMemory newSpaceBytes
  						+ (desiredHeapSize - dataSize > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve]).
  			 heapSize < minimumMemory ifTrue:
  				[self insufficientMemorySpecifiedError]].
  
  	"allocate a contiguous block of memory for the Squeak heap"
+ 	(self
+ 			allocateMemory: heapSize
+ 			minimum: minimumMemory
+ 			imageFile: f
+ 			headerSize: headerSize) asUnsignedInteger
+ 		ifNil: [self insufficientMemoryAvailableError]
+ 		ifNotNil:
+ 			[:mem|
+ 			objectMemory
+ 				setHeapBase: mem
+ 				memoryLimit: mem + heapSize
+ 				endOfMemory: mem + dataSize].
- 	objectMemory memory: (self
- 								allocateMemory: heapSize
- 								minimum: minimumMemory
- 								imageFile: f
- 								headerSize: headerSize) asUnsignedInteger.
- 	objectMemory memory ifNil: [self insufficientMemoryAvailableError].
  
- 	objectMemory
- 		setHeapBase: objectMemory memory
- 		memoryLimit: objectMemory memory + heapSize
- 		endOfMemory: objectMemory memory + dataSize.
- 
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  	^dataSize!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openOn:extraMemory: (in category 'initialize-release') -----
  openOn: fileName extraMemory: extraBytes
  	"StackInterpreterSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags heapBase firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize allocationReserve |
  	"open image file and read the header"
  
  	(f := self openImageFileNamed: fileName) ifNil: [^self].
  
  	"Set the image name and the first argument; there are
  	 no arguments during simulation unless set explicitly."
  	systemAttributes at: 1 put: fileName.
  
  	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
  
  	version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := version byteSwap32) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getWord32FromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 It is used for the cog code size in Cog.  Preserve it to be polite to other VMs."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  	hdrEdenBytes		:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (hdrEdenBytes = 0
  							ifTrue: [objectMemory defaultEdenBytes]
  							ifFalse: [hdrEdenBytes]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  dataSize
  						+ extraBytes
  						+ objectMemory newSpaceBytes
  						+ (extraBytes > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])].
  	"allocate interpreter memory"
+ 	heapBase := objectMemory
+ 					setHeapBase: objectMemory startOfMemory
+ 					memoryLimit: objectMemory startOfMemory + heapSize
+ 					endOfMemory: objectMemory startOfMemory + dataSize. "bogus for Spur"
- 	heapBase := objectMemory startOfMemory.
- 	objectMemory
- 		setHeapBase: heapBase
- 		memoryLimit: heapBase + heapSize
- 		endOfMemory: heapBase + dataSize. "bogus for Spur"
  	objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	count ~= dataSize ifTrue: [self halt]]
  		ensure: [f close].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	UIManager default
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift]!




More information about the Vm-dev mailing list