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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 28 23:52:00 UTC 2021


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

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

Name: VMMaker.oscog-eem.3077
Author: eem
Time: 28 September 2021, 4:51:48.850793 pm
UUID: 8ad52133-62f2-4e1e-bf92-9b29ba104d62
Ancestors: VMMaker.oscog-eem.3076

StaclInterpreter: eliminate some warnings in the wake of the printing putsch.  In particular do not map %p to PRIxSQPTR.

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

Item was changed:
  ----- Method: CoInterpreter>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'cog jit support') -----
  functionPointerForCompiledMethod: methodObj primitiveIndex: primitiveIndex primitivePropertyFlagsInto: flagsPtr
  	<api>
  	<returnTypeC: 'void (*functionPointerForCompiledMethodprimitiveIndexprimitivePropertyFlagsInto(sqInt methodObj, sqInt primitiveIndex, sqInt *flagsPtr))(void)'>
  	| functionPointer flags |
  	<var: #functionPointer declareC: #'void (*functionPointer)(void)'>
  	flagsPtr ifNotNil:
  		[flagsPtr at: 0 put: (flags := self primitivePropertyFlags: primitiveIndex)].
  	functionPointer := self functionPointerFor: primitiveIndex inClass: nil.
  	functionPointer == #primitiveCalloutToFFI ifTrue:
  		[^self functionForPrimitiveCallout].
  	functionPointer == #primitiveExternalCall ifTrue:
  		[| lit |
  		 lit := self attemptToLinkExternalPrimitive: methodObj.
  		 "N.B. We only support the FastCPrimitiveFlag on Spur because Spur
  		  will *not* run a GC to satisfy an allocation in a primitive. The V3
  		  ObjectMemory will and hence the depth of stack needed in a V3
  		  primitive is probably too large to safely execute on a stack page."
  		  objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[| metadataFlags shiftedMetadataFlags |
  			 metadataFlags := objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit.
  		 	 (objectMemory isIntegerObject: metadataFlags) ifTrue:
  				[shiftedMetadataFlags := ((objectMemory integerValueOf: metadataFlags)
  											bitAnd: SpurPrimitiveFlagsMask)
  												bitShift: PrimitiveMetadataFlagsShift.
  				 shiftedMetadataFlags > 0 ifTrue:
  					["Intentionally clear all other flags if there are Spur metadata flags..."
  					 flags := shiftedMetadataFlags]]].
  		 (self object: (objectMemory fetchPointer: ExternalCallLiteralTargetFunctionIndex ofObject: lit)
+ 				equalsString: 'primitiveProfileSemaphore') ifTrue:
- 				equalsString: #primitiveProfileSemaphore) ifTrue:
  			[flags := flags bitOr: PrimCallMayEndureCodeCompaction].
  		 profileSemaphore ~= objectMemory nilObject ifTrue:
  			[flags := flags bitOr: PrimCallCollectsProfileSamples].
  		 flagsPtr at: 0 put: flags.
  		 ^self functionForPrimitiveExternalCall: methodObj].
  	^functionPointer!

Item was changed:
  ----- Method: CoInterpreter>>printMethodCacheFor: (in category 'debug printing') -----
  printMethodCacheFor: thing
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	| n |
  	n := 0.
  	0 to: MethodCacheSize - 1 by: MethodCacheEntrySize do:
  		[:i | | s c m p |
  		s := methodCache at: i + MethodCacheSelector.
  		c := methodCache at: i + MethodCacheClass.
  		m := methodCache at: i + MethodCacheMethod.
  		p := methodCache at: i + MethodCachePrimFunction.
  		((thing = -1 or: [s = thing or: [c = thing or: [p = thing or: [m = thing
  			or: [(objectMemory addressCouldBeObj: m)
  				and: [(self maybeMethodHasCogMethod: m)
  				and: [(self cogMethodOf: m) asInteger = thing]]]]]]])
  		 and: [(objectMemory addressCouldBeOop: s)
  		 and: [c ~= 0
  		 and: [(self addressCouldBeClassObj: c)
  			or: [self addressCouldBeClassObj: (objectMemory classForClassTag: c)]]]]) ifTrue:
  			[n := n + 1.
  			 self cCode: [] inSmalltalk: [self transcript ensureCr].
  			 self printNum: i; space; printHexnp: i; cr; tab.
  			 (objectMemory isBytesNonImm: s)
+ 				ifTrue: ['%p %.*s\n' f: transcript printf: { s. (objectMemory numBytesOfBytes: s) signedIntFromLong. objectMemory firstIndexableField: s }]
- 				ifTrue: ['%p %.*s\n' f: transcript printf: { s. objectMemory numBytesOfBytes: s. objectMemory firstIndexableField: s }]
  				ifFalse: [self shortPrintOop: s].
  			 self tab.
  			 (self addressCouldBeClassObj: c)
  				ifTrue: [self shortPrintOop: c]
  				ifFalse: [self printNum: c; space; printHexnp: c; space; shortPrintOop: (objectMemory classForClassTag: c)].
  			self tab; shortPrintOop: m; tab.
  			self cCode:
  					[p > 1024
  						ifTrue: [self printHexnp: p]
  						ifFalse: [self printNum: p]]
  				inSmalltalk:
  					[p isSymbol ifTrue: [self print: p] ifFalse: [self printNum: p]].
  			self cr]].
  	n > 1 ifTrue:
  		[self printNum: n; cr]!

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 |
+ 	<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>
- 	<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>
  
  	transcript := #stdout.		"stdout is not available at compile time.  this is the earliest available point."
  	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
  						+ 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]].
  
  	"allocateJITMemory will assign the actual size allocated, which is rounded up to a page boundary."
+ 	cogCodeBase := (self allocateJITMemory: (self addressOf: cogCodeSize)) asInteger.
- 	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].
  
  	"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.
  	^dataSize!

Item was added:
+ ----- Method: CogVMSimulator>>headFramePointer (in category 'accessing') -----
+ headFramePointer
+ 	^localFP ifNil: [framePointer]!

Item was changed:
  ----- Method: CogVMSimulator>>printCallStack (in category 'debug printing') -----
  printCallStack
+ 	"This is almost the same as StackInterpreter's implementation but in simulation this will print from the machince code head frame."
- 	<inline: false>
  	cogit headFramePointer
  		ifNil: [self printCallStackOf: (objectMemory fetchPointer: SuspendedContextIndex ofObject: self activeProcess)]
  		ifNotNil: [:fp| self printCallStackFP: fp]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveListBuiltinModule (in category 'plugin primitives') -----
  primitiveListBuiltinModule
  	"Primitive. Return the n-th builtin module name."
  	| index |
+ 	<var: 'moduleName' type: #'char *'>
  	self methodArgumentCount = 1 ifFalse:
  		[^self primitiveFail].
  	index := self stackIntegerValue: 0.
  	(self failed or: [index <= 0]) ifTrue:
  		[^self primitiveFail].
  	(self ioListBuiltinModule: index)
  		ifNil: [self methodReturnValue: objectMemory nilObject]
  		ifNotNil: [:moduleName| self methodReturnString: moduleName]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveListExternalModule (in category 'plugin primitives') -----
  primitiveListExternalModule
  	"Primitive. Answer the n-th loaded external module name."
  	| index |
+ 	<var: 'moduleName' type: #'char *'>
  	self methodArgumentCount = 1 ifFalse:
  		[^self primitiveFail].
  	index := self stackIntegerValue: 0.
  	(self failed or: [index <= 0]) ifTrue:
  		[^self primitiveFail].
  	(self ioListLoadedModule: index)
  		ifNil: [self methodReturnValue: objectMemory nilObject]
  		ifNotNil: [:moduleName| self methodReturnString: moduleName]!

Item was changed:
  ----- Method: PrintfNumberFormatDescriptor>>transformForVMMaker (in category '*VMMaker-C code generation') -----
  transformForVMMaker
  	('duxX' includes: operator) ifTrue:
  		[^'%" PRI', (String with: operator), 'SQINT "'].
- 	('pP' includes: operator) ifTrue:
- 		[^'%" PRI', (String with: (operator = $p ifTrue: [$x] ifFalse: [$X])), 'SQPTR "'].
  	^super transformForVMMaker!

Item was added:
+ ----- Method: StackInterpreter>>headFramePointer (in category 'accessing') -----
+ headFramePointer
+ 	"Answer the framePointer for the active frame.  In the production VM all we can
+ 	 get our hands on is framePointer.  localFP is a register variable inside interpret.
+ 	 But in the simulator we have access to localFP and so this mehtod is reimplemented there-in"
+ 	<inline: #always>
+ 	^framePointer asInteger!

Item was changed:
  ----- Method: StackInterpreter>>object:equalsString: (in category 'utilities') -----
  object: anOop equalsString: aCString
+ 	<var: 'aCString' type: #'char *'>
+ 	<inline: true>
  	^self object: anOop equalsString: aCString ofSize: (self strlen: aCString)!

Item was changed:
  ----- Method: StackInterpreter>>object:equalsString:ofSize: (in category 'utilities') -----
  object: anOop equalsString: aCString ofSize: aCStringStrlen
+ 	<var: 'aCString' type: #'char *'>
- 	| size |
  	^(objectMemory isBytes: anOop)
+ 	 and: [(objectMemory numBytesOfBytes: anOop) = aCStringStrlen
- 	 and: [(size := objectMemory numBytesOfBytes: anOop) = aCStringStrlen
  	 and: [(self strncmp: aCString _: (objectMemory firstIndexableField: anOop)  _: aCStringStrlen) = 0]]!

Item was changed:
  ----- Method: StackInterpreter>>printAllStacks (in category 'debug printing') -----
  printAllStacks
  	"Print all the stacks of all running processes, including those that are currently suspended."
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	| proc semaphoreClass mutexClass schedLists p processList |
  	<inline: false>
  	proc := self activeProcess.
  	self printNameOfClass: (objectMemory fetchClassOf: proc) count: 5; space; printHex: proc.
  	self print: ' priority '; printNum: (self quickFetchInteger: PriorityIndex ofObject: proc); cr.
+ 	self printCallStack. "first the current activation"
- 	self printCallStackFP: framePointer. "first the current activation"
  	schedLists := objectMemory fetchPointer: ProcessListsIndex ofObject: self schedulerPointer.
  	"then the runnable processes"
  	p := highestRunnableProcessPriority = 0
  			ifTrue: [objectMemory numSlotsOf: schedLists]
  			ifFalse: [highestRunnableProcessPriority].
  	p - 1 to: 0 by: -1 do:
  		[:pri|
  		processList := objectMemory fetchPointer: pri ofObject: schedLists.
  		(self isEmptyList: processList) ifFalse:
  			[self cr; print: 'processes at priority '; printNum: pri + 1.
  			 self printProcsOnList: processList]].
  	self cr; print: 'suspended processes'.
  	semaphoreClass := objectMemory classSemaphore.
  	mutexClass := objectMemory classMutex.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[semaphoreClass := objectMemory compactIndexOfClass: semaphoreClass.
  			 mutexClass := objectMemory compactIndexOfClass: mutexClass.
  			 objectMemory allHeapEntitiesDo:
  				[:obj| | classIdx |
  				 classIdx := objectMemory classIndexOf: obj.
  				 (classIdx = semaphoreClass
  				  or: [classIdx = mutexClass]) ifTrue:
  					[self printProcsOnList: obj]]]
  		ifFalse:
  			[objectMemory allObjectsDoSafely:
  				[:obj| | classObj |
  				 classObj := objectMemory fetchClassOfNonImm: obj.
  				 (classObj = semaphoreClass
  				  or: [classObj = mutexClass]) ifTrue:
  					[self printProcsOnList: obj]]]!

Item was changed:
  ----- Method: StackInterpreter>>printCallStackOf: (in category 'debug printing') -----
  printCallStackOf: aContextOrProcessOrFrame
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	| context |
  	<inline: false>
  	(stackPages couldBeFramePointer: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackFP: (self cCoerceSimple: aContextOrProcessOrFrame to: #'char *')].
  	aContextOrProcessOrFrame = self activeProcess ifTrue:
+ 		[^self printCallStackOf: self headFramePointer].
- 		[^self printCallStackOf: (self cCode: [framePointer asInteger] inSmalltalk: [self headFramePointer])].
  	(self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackOf: (objectMemory
  									fetchPointer: SuspendedContextIndex
  									ofObject: aContextOrProcessOrFrame)].
  	context := aContextOrProcessOrFrame.
  	[context = objectMemory nilObject] whileFalse:
  		[(self isMarriedOrWidowedContext: context)
  			ifTrue:
  				[(self checkIsStillMarriedContext: context currentFP: framePointer) ifFalse:
  					[self shortPrintContext: context.
  					 ^nil].
  				 context := self shortReversePrintFrameAndCallers: (self frameOfMarriedContext: context)]
  			ifFalse:
  				[context := self printContextCallStackOf: context]]!

Item was changed:
  ----- Method: StackInterpreter>>printStackCallStackOf: (in category 'debug printing') -----
  printStackCallStackOf: aContextOrProcessOrFrame
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	| theFP context |
  	<var: #theFP type: #'char *'>
  	(self cCode: [false] "In the stack simulator, frame pointers are negative which upsets addressCouldBeObj:"
  		inSmalltalk: [stackPages couldBeFramePointer: aContextOrProcessOrFrame]) ifFalse:
  		[(objectMemory addressCouldBeObj: aContextOrProcessOrFrame) ifTrue:
  			[((objectMemory isContext: aContextOrProcessOrFrame)
  			  and: [self checkIsStillMarriedContext: aContextOrProcessOrFrame currentFP: nil]) ifTrue:
  				[^self printStackCallStackOf: (self frameOfMarriedContext: aContextOrProcessOrFrame) asInteger].
  			 aContextOrProcessOrFrame = self activeProcess ifTrue:
+ 				[^self printStackCallStackOf: self headFramePointer].
- 				[^self printStackCallStackOf: (self cCode: [framePointer asInteger] inSmalltalk: [self headFramePointer])].
  			 (self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
  				[^self printCallStackOf: (objectMemory
  											fetchPointer: SuspendedContextIndex
  											ofObject: aContextOrProcessOrFrame)].
  			 ^nil]].
  
  	theFP := aContextOrProcessOrFrame asVoidPointer.
  	[context := self shortReversePrintFrameAndCallers: theFP.
  	 ((self isMarriedOrWidowedContext: context)
  	  and:
  		[theFP := self frameOfMarriedContext: context.
  		 self checkIsStillMarriedContext: context currentFP: theFP]) ifFalse:
  			[^nil]] repeat!

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>
- 	<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>
  
  	transcript := #stdout.		"stdout is not available at compile time.  this is the earliest available point."
  	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].
  
  	"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 added:
+ ----- Method: StackInterpreterSimulator>>headFramePointer (in category 'accessing') -----
+ headFramePointer
+ 	^localFP ifNil: [framePointer]!



More information about the Vm-dev mailing list