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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 8 05:15:09 UTC 2023


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

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

Name: VMMaker.oscog-eem.3304
Author: eem
Time: 7 February 2023, 9:14:49.862781 pm
UUID: d2a7fa73-fe36-4db6-b473-554e09c396e5
Ancestors: VMMaker.oscog-eem.3303

Cog: provide a vmParameter accessor for maxLiteralCountForCompile (vmParameterAt: 50), and have it persist in the image header.  Fix a bug in continuing in the interoreter; the old code did not fix up instructionPointer if it was set to ceReturnToInterpreterPC.

In doing so better factor flushing of methods for vm parameters 50 & 75\, avoidig code duplication in primitiveSetVMParameter:arg:.

Fix in-image compilation with the full blocks..

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

Item was added:
+ ----- Method: CoInterpreter>>cogMethodHasTooManyLiterals: (in category 'frame access') -----
+ cogMethodHasTooManyLiterals: aCogMethod
+ 	<api>
+ 	<var: 'aCogMethod' type: #'CogMethod *'>
+ 	^(self methodWithHeaderShouldBeCogged: aCogMethod methodHeader) not!

Item was changed:
  ----- Method: CoInterpreter>>divorceAllFramesSuchThat: (in category 'frame access') -----
  divorceAllFramesSuchThat: criterion
+ 	"Divorce all frames that satisfy criterion and answer the current activeContext."
+ 	<inline: false>
- 	"Divorce all frames that satisfy criterion nd answer the current activeContext."
  	<var: #criterion declareC: 'sqInt (*criterion)(char *fp)'>
  	| activeContext divorcedSome |
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	self ensurePushedInstructionPointer.
  	self externalWriteBackHeadFramePointers.
  	[stackPage ifNotNil: "This is needed for the assert in externalDivorceFrame:andContext:"
  		[stackPages markStackPageMostRecentlyUsed: stackPage].
  	 "Slang can't currently cope with the lack of the variable here.
  	  Something to do with the preceding statement.  Take it out
  	  and the code is good.  leave it in and we get do { ... } while(l1:)"
  	 divorcedSome := self divorceSomeFramesIf: criterion.
  	 divorcedSome] whileTrue.
  	^activeContext!

Item was added:
+ ----- Method: CoInterpreter>>ensureAllContextsHaveBytecodePCsIf: (in category 'frame access') -----
+ ensureAllContextsHaveBytecodePCsIf: criterion
+ 	"Map all native pcs to bytecoded pcs in all contexts whose method matches criterion."
+ 	<inline: false>
+ 	<var: #criterion declareC: 'sqInt (*criterion)(sqInt methodOop)'>
+ 	objectMemory allObjectsDo:
+ 		[:oop| | pc |
+ 		 ((objectMemory isContextNonImm: oop)
+ 		 and: [(objectMemory isIntegerObject: (pc := objectMemory fetchPointer: InstructionPointerIndex ofObject: oop))
+ 		 and: [pc < 0 "oops are signed; hence if integerValueOf: foo is negative so is foo"
+ 		 and: [self perform: criterion with: (objectMemory followObjField: MethodIndex ofObject: oop)]]]) ifTrue:
+ 			[self widowOrForceToBytecodePC: oop]]!

Item was removed:
- ----- Method: CoInterpreter>>ensureAllContextsWithMachineCodeMethodsFlaggedForBecomeHaveBytecodePCs (in category 'frame access') -----
- ensureAllContextsWithMachineCodeMethodsFlaggedForBecomeHaveBytecodePCs
- 	"Map all native pcs to bytecoded pcs in all contexts that have a method with a cog method flagged for become
- 	 See the comment in primitiveArrayBecome."
- 	<inline: true>
- 	objectMemory allObjectsDo:
- 		[:oop| | methodHeader |
- 		 (objectMemory isContextNonImm: oop) ifTrue:
- 			[method := objectMemory followObjField: MethodIndex ofObject: oop.
- 			 methodHeader := self rawHeaderOf: (objectMemory fetchPointer: MethodIndex ofObject: oop).
- 			 ((self isCogMethodReference: methodHeader)
- 			  and: [(self cCoerceSimple: methodHeader to: #'CogMethod *') isCMMethodFlaggedForBecome]) ifTrue:
- 				[self widowOrForceToBytecodePC: oop]]]!

Item was removed:
- ----- Method: CoInterpreter>>ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs (in category 'frame access') -----
- ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs
- 	"Map all native pcs to bytecoded pcs in all contexts that have a method with a cog method with a machine code primitive.
- 	 Used to implement flushMethodsWithMachineCodePrimitivesAndContinueAnswering:/vmParameterAt: 75 put: aBool."
- 	<inline: true>
- 	objectMemory allObjectsDo:
- 		[:oop| | methodHeader |
- 		 (objectMemory isContextNonImm: oop) ifTrue:
- 			[methodHeader := self rawHeaderOf: (objectMemory fetchPointer: MethodIndex ofObject: oop).
- 			 ((self isCogMethodReference: methodHeader)
- 			  and: [cogit cogMethodHasMachineCodePrim: (self cCoerceSimple: methodHeader to: #'CogMethod *')]) ifTrue:
- 				[self widowOrForceToBytecodePC: oop]]]!

Item was changed:
  ----- Method: CoInterpreter>>flushExternalPrimitives (in category 'plugin primitive support') -----
  flushExternalPrimitives
  	"Flush the references to external functions from plugin primitives.
  	 Then continue execution answering self.
  	 This will force a reload of those primitives when accessed next. 
  	 Note: We must flush the method cache here also, so that any failed
  	 primitives are looked up again.
  	 Override to ensure that any and all activations of an external method
  	 have a bytecode pc so that if code generation changes (e.g. a primitive
  	 method is used, unloaded, and the reloaded primitive is marked with
  	 the FastCPrimitiveFlag) stale machine code pcs have been eliminated.
  	 THIS MUST BE INVOKED IN THE CONTEXT OF A PRIMITIVE."
  	| activeContext theFrame thePage |
  	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameForExternalPrimitiveMethod:.
  	objectMemory allObjectsDo:
  		[:oop|
  		(objectMemory isCompiledMethod: oop)
  			ifTrue:
  				[self flushExternalPrimitiveOf: oop]
  			ifFalse:
  				[(objectMemory isContext: oop) ifTrue:
  					[self mapToBytecodePCIfActivationOfExternalMethod: oop]]].
  	cogit unlinkSendsToMethodsSuchThat: #cogMethodHasExternalPrim: AndFreeIf: true.
  	self flushMethodCache.
  	self flushExternalPrimitiveTable.
  	self cCode: '' inSmalltalk:
  		[self assert: (cogit methodZone cogMethodsSelect: [:cogMethod| cogMethod isCMFree not and: [cogit cogMethodHasExternalPrim: cogMethod]]) isEmpty].
  	"If flushing led to divorce continue in the interpreter."
  	(self isStillMarriedContext: activeContext) ifFalse:
  		[self nilStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		 self popStack. "pop pushed instructionPointer"
  		 self pop: argumentCount.
  		 cogit ceInvokeInterpret
  		 "NOTREACHED"].
  	"If not, work out where we are and continue"
  	theFrame := self frameOfMarriedContext: activeContext.
  	thePage := stackPages stackPageFor: theFrame.
  	self assert: thePage headFP = theFrame.
  	self setStackPageAndLimit: thePage.
  	self setStackPointersFromPage: thePage.
  	instructionPointer := self popStack.
+ 	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
+ 		[instructionPointer := self iframeSavedIP: framePointer].
  	self pop: argumentCount!

Item was changed:
  ----- Method: CoInterpreter>>flushMethodsWithMachineCodePrimitivesAndContinueAnswering: (in category 'primitive support') -----
  flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result
  	"Arrange that any and all cog methods with machine code primitives can be and are discarded.
  	 Hence scan contexts and map their PCs to bytecode PCs if required, and scan frames, divorcing
  	 the frames of activations if required.  Then continue execution answering result.  THIS MUST BE
  	 INVOKED IN THE CONTEXT OF A PRIMITIVE.  It exists to support vmParameterAt:put:."
  	| activeContext theFrame thePage |
  	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameForCogMethodWithMachineCodePrim:.
+ 	self ensureAllContextsHaveBytecodePCsIf: #methodHasMachineCodePrimitiveMethod:.
- 	self ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs.
  	cogit unlinkSendsToMethodsSuchThat: #cogMethodHasMachineCodePrim: AndFreeIf: true.
  
  	"If the top frame was divorced then continue in the interpreter."
  	(self isStillMarriedContext: activeContext) ifFalse:
  		[self nilStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		"pop bogus machine-code instructionPointer, arguments and receiver"
  		 self pop: argumentCount + 2 thenPush: result.
  		 cogit ceInvokeInterpret
  		 "NOTREACHED"].
  	"If not, work out where we are and continue"
  	theFrame := self frameOfMarriedContext: activeContext.
  	thePage := stackPages stackPageFor: theFrame.
  	self assert: thePage headFP = theFrame.
  	self setStackPageAndLimit: thePage.
  	self setStackPointersFromPage: thePage.
  	instructionPointer := self popStack.
+ 	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
+ 		[instructionPointer := self iframeSavedIP: framePointer].
  	 self pop: argumentCount + 1 thenPush: result!

Item was added:
+ ----- Method: CoInterpreter>>flushMethodsWithNumLiteralsAboveLimitAndContinueAnswering: (in category 'primitive support') -----
+ flushMethodsWithNumLiteralsAboveLimitAndContinueAnswering: result
+ 	"Arrange that any and all cog methods with numLiterals above maxLiteralCountForCompile are discarded.
+ 	 Hence scan contexts and map their PCs to bytecode PCs if required, and scan frames, divorcing
+ 	 the frames of activations if required.  Then continue execution answering result.  THIS MUST BE
+ 	 INVOKED IN THE CONTEXT OF A PRIMITIVE.  It exists to support vmParameterAt:put:."
+ 	| activeContext theFrame thePage |
+ 	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameForCogMethodWithTooManyLiterals:.
+ 	self ensureAllContextsHaveBytecodePCsIf: #methodHasTooManyLiterals:.
+ 	cogit unlinkSendsToMethodsSuchThat: #cogMethodHasTooManyLiterals: AndFreeIf: true.
+ 
+ 	"If the top frame was divorced then continue in the interpreter."
+ 	(self isStillMarriedContext: activeContext) ifFalse:
+ 		[self nilStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
+ 		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
+ 		"pop bogus machine-code instructionPointer, arguments and receiver"
+ 		 self pop: argumentCount + 2 thenPush: result.
+ 		 cogit ceInvokeInterpret
+ 		 "NOTREACHED"].
+ 	"If not, work out where we are and continue"
+ 	theFrame := self frameOfMarriedContext: activeContext.
+ 	thePage := stackPages stackPageFor: theFrame.
+ 	self assert: thePage headFP = theFrame.
+ 	self setStackPageAndLimit: thePage.
+ 	self setStackPointersFromPage: thePage.
+ 	instructionPointer := self popStack.
+ 	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
+ 		[instructionPointer := self iframeSavedIP: framePointer].
+ 	 self pop: argumentCount + 1 thenPush: result!

Item was added:
+ ----- Method: CoInterpreter>>getMaxLiteralCountForCompile (in category 'internal interpreter access') -----
+ getMaxLiteralCountForCompile
+ 	^objectMemory integerObjectOf: maxLiteralCountForCompile!

Item was changed:
  ----- Method: CoInterpreter>>insulateFramesAndContextsFromCogMethodsFlaggedForBecome (in category 'object access primitives') -----
  insulateFramesAndContextsFromCogMethodsFlaggedForBecome
   	| activeContext |
  	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameForCogMethodFlaggedForBecome:.
  	self popStack. "divorceAllFramesSuchThat: sends ensurePushedInstructionPointer, which is a side-effect we don't want here (but need elsewhere)"
  	"Mapping native pcs in contexts whose methods are flagged for become will not ensure that pcs are mapped reliably.
  	 Consider this arc: a context on a method that has been jitted exists with a native pc.
  	 The method is unjitted to make room for other methods to be jitted.
  	 The method is becommed.
+ 	 So the scan is only effective for methods in the code zone.  Slowing down become so that a rare
- 	 So the scan is only effective for methods in the jit.  Slowing down become so that a rare
  	 case may fail more comprehensibly, when its going to fail anyway, is a waste of effort."
  	false ifTrue:
+ 		[self ensureAllContextsHaveBytecodePCsIf: #methodIsCoggedFlaggedForBecome:].
- 		[self ensureAllContextsWithMachineCodeMethodsFlaggedForBecomeHaveBytecodePCs].
  	self assert: (framePointer ~= 0) == (self isStillMarriedContext: activeContext).
  	(self isStillMarriedContext: activeContext) ifFalse:
  		[objectMemory storePointer: SuspendedContextIndex ofObject: self activeProcess withValue: activeContext]!

Item was added:
+ ----- Method: CoInterpreter>>isMachineCodeFrameForCogMethodWithTooManyLiterals: (in category 'plugin primitive support') -----
+ isMachineCodeFrameForCogMethodWithTooManyLiterals: theFP
+ 	<var: #theFP type: #'char *'>
+ 	^(self isMachineCodeFrame: theFP)
+ 	  and: [(self methodWithHeaderShouldBeCogged: (self mframeHomeMethod: theFP) methodHeader) not]!

Item was added:
+ ----- Method: CoInterpreter>>methodHasMachineCodePrimitiveMethod: (in category 'primitive support') -----
+ methodHasMachineCodePrimitiveMethod: methodObj
+ 	| methodHeader |
+ 	methodHeader := self rawHeaderOf: methodObj.
+ 	^(self isCogMethodReference: methodHeader)
+ 	  and: [cogit cogMethodHasMachineCodePrim: (self cCoerceSimple: methodHeader to: #'CogMethod *')]!

Item was added:
+ ----- Method: CoInterpreter>>methodHasTooManyLiterals: (in category 'primitive support') -----
+ methodHasTooManyLiterals: methodObj
+ 	^(self methodWithHeaderShouldBeCogged: (self methodHeaderOf: methodObj)) not!

Item was added:
+ ----- Method: CoInterpreter>>methodIsCoggedFlaggedForBecome: (in category 'primitive support') -----
+ methodIsCoggedFlaggedForBecome: methodObj
+ 	| methodHeader |
+ 	methodHeader := self rawHeaderOf: (objectMemory fetchPointer: MethodIndex ofObject: methodObj).
+ 	^(self isCogMethodReference: methodHeader)
+ 	  and: [(self cCoerceSimple: methodHeader to: #'CogMethod *') isCMMethodFlaggedForBecome]!

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: 'desiredHeapSize' type: #usqInt>
+ 	<var: 'imageOffset' type: #squeakFileOffsetType>
+ 
+ 	| swapBytes headerStart headerSize headerFlags dataSize bytesRead bytesToShift heapSize
+ 	  oldBaseAddr minimumMemory allocationReserve cogCodeBase firstSegSize
+ 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize hdrMaxExtSemTabSize |
  	<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.
- 	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].
+ 	the2ndUnknownShort := self getShortFromFile: f swap: swapBytes.
+ 	"Set maxLiteralCountForCompile unless it has already been set on the command line."
+ 	maxLiteralCountForCompile < 0 ifTrue:
+ 		[maxLiteralCountForCompile := the2ndUnknownShort ~= 0
+ 											ifTrue: [the2ndUnknownShort]
+ 											ifFalse: [MaxLiteralCountForCompile]].
- 	"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.
  
  	"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: CoInterpreter>>setMaxLiteralCountForCompile: (in category 'internal interpreter access') -----
+ setMaxLiteralCountForCompile: mlcfc
+ 	<inline: true>
+ 	"the2ndUnknownShort is the value written to the image; so set both the limit and the value saved."
+ 	maxLiteralCountForCompile := the2ndUnknownShort := mlcfc!

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialize-release') -----
  initialize
  	"Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  	 primary responsibility of this method is to allocate Smalltalk Arrays for variables
  	 that will be declared as statically-allocated global arrays in the translated code."
  	super initialize.
  
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := InitializationOptions
  								at: #ObjectMemorySimulator
  								ifPresent: [:className| (Smalltalk classNamed: className) new]
  								ifAbsent: [self class objectMemoryClass simulatorClass new]].
  	cogit ifNil:
  		[cogit := self class cogitClass new setInterpreter: self].
  	objectMemory coInterpreter: self cogit: cogit.
  
  	(cogit numRegArgs > 0
  	 and: [VMClass initializationOptions at: #CheckStackDepth ifAbsent: [true]]) ifTrue:
  		[debugStackDepthDictionary := Dictionary new].
  
  	cogThreadManager ifNotNil:
  		[super initialize].
  
  	self assert: ConstMinusOne = (objectMemory integerObjectOf: -1).
  
  	cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  	enableCog := true.
  
  	methodCache := Array new: MethodCacheSize.
  	nsMethodCache := Array new: NSMethodCacheSize.
  	atCache := nil.
  	self flushMethodCache.
  	cogCompiledCodeCompactionCalledFor := false.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	self initializePluginEntries.
  	desiredNumStackPages := InitializationOptions at: #desiredNumStackPages ifAbsent: [0].
  	desiredEdenBytes := InitializationOptions at: #desiredEdenBytes ifAbsent: [0].
  	desiredCogCodeSize  := InitializationOptions at: #desiredCogCodeSize ifAbsent: [0].
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := lastYieldMicroseconds := self ioUTCStartMicroseconds.
+ 	maxLiteralCountForCompile := -1. "This allows seeing if maxLiteralCountForCompile has been set on the command line."
- 	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^self close].
  	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  	suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  	systemAttributes := Dictionary new.
  	primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  	primTraceLogIndex := 0.
  	traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  	traceLogIndex := 0.
  	traceSources := TraceSources.
  	statCodeCompactionCount := 0.
  	statCodeCompactionUsecs := 0.
  	extSemTabSize := 256.
  	zeroNextProfileTickCount := 0.
  	printFrameRange := 0 to: 0.
  	printfConversions := IdentityDictionary new!

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].
+ 	the2ndUnknownShort := self getShortFromFile: f swap: swapBytes.
+ 	"Set maxLiteralCountForCompile unless it has already been set on the command line."
+ 	maxLiteralCountForCompile < 0 ifTrue:
+ 		[maxLiteralCountForCompile := the2ndUnknownShort ~= 0
+ 											ifTrue: [the2ndUnknownShort]
+ 											ifFalse: [MaxLiteralCountForCompile]].
- 	"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 + Cogit guardPageSize]
  								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"
  
  	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!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>isFullBlockMethod: (in category 'testing') -----
+ isFullBlockMethod: anInteger 
+ 	^false!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>isFullBlockMethod: (in category 'testing') -----
+ isFullBlockMethod: methodOop 
+ 	^(self objectForOop: methodOop) isCompiledBlock!

Item was added:
+ ----- Method: StackInterpreter>>flushMethodsWithNumLiteralsAboveLimitAndContinueAnswering: (in category 'primitive support') -----
+ flushMethodsWithNumLiteralsAboveLimitAndContinueAnswering: result
+ 	"In the StackInterpreter this is simply a no op"!

Item was added:
+ ----- Method: StackInterpreter>>getMaxLiteralCountForCompile (in category 'internal interpreter access') -----
+ getMaxLiteralCountForCompile
+ 	"This is nil in the StackVM"
+ 	^objectMemory nilObject!

Item was added:
+ ----- Method: StackInterpreter>>setMaxLiteralCountForCompile: (in category 'internal interpreter access') -----
+ setMaxLiteralCountForCompile: mlcfc
+ 	<inline: true>
+ 	"This should perhaps be a no-op in the StackVM, but we implement it for the convenience of bootstrap scripts etc."
+ 	the2ndUnknownShort := mlcfc!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveAllVMParameters: (in category 'system control primitives') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveGetVMParameter: (in category 'system control primitives') -----
  primitiveGetVMParameter: arg 
  	"See primitiveVMParameter method comment.
  	 N.B. written as a returning case to avoid branch limits in the V3 bytecode set."
  	arg caseOf: {
  			[1]  ->	[^self positiveMachineIntegerFor: objectMemory oldSpaceSize].
  			[2]  ->	[^objectMemory integerObjectOf: objectMemory newSpaceSize].
  			[3]  ->	[^self positiveMachineIntegerFor: objectMemory totalMemorySize].
  			[6]  ->	[^objectMemory integerObjectOf: objectMemory tenuringThreshold].
  			[7]  ->	[^objectMemory integerObjectOf: objectMemory statFullGCs].
  			[8]  ->	[^objectMemory integerObjectOf: objectMemory statFullGCUsecs + 500 // 1000].
  			[9]  ->	[^objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
  														ifTrue: [objectMemory statScavenges]
  														ifFalse: [objectMemory statIncrGCs])].
  			[10] ->	[^objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
  														ifTrue: [objectMemory statScavengeGCUsecs]
  														ifFalse: [objectMemory statIncrGCUsecs]) + 500 // 1000].
  			[11] ->	[^objectMemory integerObjectOf: objectMemory statTenures].
  			[12] ->	[^objectMemory integerObjectOf: eventTraceMask].
  			[13] ->	[^self getVMTickerStartUSecs].
  			[14] ->	[^self getVMTickerCount].
  			[15] ->	[^self getVMTickeeCallCount].
  			[16] ->	[^self positive64BitIntegerFor: statIdleUsecs].
  			[17] ->	[^(SistaVM and: [self isCog])
  						ifTrue: [objectMemory floatObjectOf: self getCogCodeZoneThreshold]
  						ifFalse: [ConstZero]].
  			[18] ->	[^objectMemory hasSpurMemoryManagerAPI
  						ifTrue: [objectMemory integerObjectOf: objectMemory statCompactionUsecs + 500 // 1000]
  						ifFalse: [ConstZero]].
  			[19] ->	[^objectMemory hasSpurMemoryManagerAPI
  						ifTrue: [objectMemory integerObjectOf: objectMemory scavengeThresholdAsExtent]
  						ifFalse: [ConstZero]].
  			[20] ->	[^objectMemory positive64BitIntegerFor: self ioUTCStartMicroseconds].
  			[21] ->	[^objectMemory integerObjectOf: objectMemory rootTableCount].
  			[22] ->	[^objectMemory integerObjectOf: objectMemory statRootTableOverflows].
  			[23] ->	[^objectMemory integerObjectOf: extraVMMemory].
  			[24] ->	[^objectMemory integerObjectOf: objectMemory shrinkThreshold].
  			[25] ->	[^objectMemory integerObjectOf: objectMemory growHeadroom].
  			[26] ->	[^objectMemory integerObjectOf: self ioHeartbeatMilliseconds].
  			[27] ->	[^objectMemory integerObjectOf: objectMemory statMarkCount].
  			[28] ->	[^objectMemory integerObjectOf: objectMemory statSweepCount].
  			[29] ->	[^objectMemory integerObjectOf: objectMemory statMkFwdCount].
  			[30] ->	[^objectMemory integerObjectOf: objectMemory statCompMoveCount].
  			[31] ->	[^objectMemory integerObjectOf: objectMemory statGrowMemory].
  			[32] ->	[^objectMemory integerObjectOf: objectMemory statShrinkMemory].
  			[33] ->	[^objectMemory integerObjectOf: objectMemory statRootTableCount].
  			[34] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:"was statAllocationCount"
  						[objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes]].
  			[35] ->	[^objectMemory integerObjectOf: objectMemory statSurvivorCount].
  			[36] ->	[^objectMemory integerObjectOf: (self microsecondsToMilliseconds: objectMemory statGCEndUsecs)].
  			[37] ->	[^objectMemory integerObjectOf: objectMemory statSpecialMarkCount].
  			[38] ->	[^objectMemory integerObjectOf: objectMemory statIGCDeltaUsecs + 500 // 1000].
  			[39] ->	[^objectMemory integerObjectOf: statPendingFinalizationSignals].
  			[40] ->	[^objectMemory integerObjectOf: objectMemory wordSize].
  			[41] ->	[^objectMemory integerObjectOf: self imageFormatVersion].
  			[42] ->	[^objectMemory integerObjectOf: numStackPages].
  			[43] ->	[^objectMemory integerObjectOf: desiredNumStackPages].
  			[44] ->	[^objectMemory integerObjectOf: objectMemory edenBytes].
  			[45] ->	[^objectMemory integerObjectOf: desiredEdenBytes].
  			[46] ->	[^self getCogCodeSize].
  			[47] ->	[^self getDesiredCogCodeSize].
  			[48] ->	[^self getImageHeaderFlagsParameter].
  			[49] ->	[^objectMemory integerObjectOf: self ioGetMaxExtSemTableSize].
+ 			[50] -> [^self getMaxLiteralCountForCompile].
  			[52] ->	[^objectMemory integerObjectOf: objectMemory rootTableCapacity].
  			[53] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory integerObjectOf: objectMemory numSegments]].
  			[54] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory integerObjectOf: objectMemory freeSize]].
  			[55] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio]].
  			[56] ->	[^self positive64BitIntegerFor: statProcessSwitch].
  			[57] ->	[^self positive64BitIntegerFor: statIOProcessEvents].
  			[58] ->	[^self positive64BitIntegerFor: statForceInterruptCheck].
  			[59] ->	[^self positive64BitIntegerFor: statCheckForEvents].
  			[60] ->	[^self positive64BitIntegerFor: statStackOverflow].
  			[61] ->	[^self positive64BitIntegerFor: statStackPageDivorce].
  			[62] ->	[^self getCodeCompactionCount].
  			[63] ->	[^self getCodeCompactionMSecs].
  			[64] ->	[^self getCogMethodCount].
  			[65] ->	[^self getCogVMFeatureFlags].
  			[66] ->	[^objectMemory integerObjectOf: stackPages bytesPerPage].
  			[67] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[self positiveMachineIntegerFor: objectMemory maxOldSpaceSize]].
  			[68] ->	[^objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping].
  			[69] ->	[^objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping].
  			[70] ->	[^objectMemory integerObjectOf: self vmProxyMajorVersion].
  			[71] ->	[^objectMemory integerObjectOf: self vmProxyMinorVersion].
  			[72] ->	[^objectMemory integerObjectOf: objectMemory statMarkUsecs + 500 // 1000].
  			[73] ->	[^objectMemory integerObjectOf: objectMemory statSweepUsecs + 500 // 1000].
  			[74] ->	[^objectMemory hasSpurMemoryManagerAPI ifTrue:
  						[objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000]].
  			[75] ->	[^objectMemory booleanObjectOf: self primitiveDoMixedArithmetic].
  			[76] ->	[^objectMemory integerObjectOf: self minimumUnusedHeadroom] }
  		otherwise: [^nil]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveSetVMParameter:arg: (in category 'system control primitives') -----
  primitiveSetVMParameter: index arg: argOop
  	"See primitiveVMParameter method comment"
  	| arg result |
  
  	"argOop read & checks; in most cases this is an integer parameter. Handle the exceptions."
  	index
  		caseOf: {
  		[17]	->	[((objectMemory isFloatInstance: argOop)
  				 	 or: [objectMemory isIntegerObject: argOop]) ifFalse:
  						[primFailCode := PrimErrBadArgument]].
  		[55]	->	[((objectMemory isFloatInstance: argOop)
  				 	 or: [objectMemory isIntegerObject: argOop]) ifFalse:
  						[primFailCode := PrimErrBadArgument]].
  		[68]	->	[((objectMemory isFloatInstance: argOop)
  				 	 or: [objectMemory isIntegerObject: argOop]) ifFalse:
  						[primFailCode := PrimErrBadArgument]].
  		[67]	->	[arg := self positiveMachineIntegerValueOf: argOop].
  		[75]	->	[arg := objectMemory booleanValueOf: argOop] }
  		otherwise: [arg := objectMemory integerValueOf: argOop].
  	self failed ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  
  	"assume failure, then set success for handled indices"
  	self primitiveFailFor: PrimErrBadArgument.
  	index caseOf: {
  		[5] ->	[objectMemory hasSpurMemoryManagerAPI ifFalse:
  					["Was:
  							result := allocationsBetweenGCs.
  							allocationsBetweenGCs := arg."
  						"Ignore for now, because old images won't start up otherwise.
  						 See 45 for eden size setting."
  					 result := objectMemory nilObject.
  					 self initPrimCall]].
  		[6] ->	[result := objectMemory integerObjectOf: objectMemory tenuringThreshold.
  				 primFailCode := objectMemory tenuringThreshold: arg].
  		[12] ->	[result := objectMemory integerObjectOf: eventTraceMask.
  				 eventTraceMask := arg.
  				 self initPrimCall].
  		[11] ->	[arg >= 0 ifTrue:
  					[result := objectMemory integerObjectOf: objectMemory statTenures.
  					 objectMemory statTenures: arg.
  					 self initPrimCall]].
  		[17] ->	[(SistaVM and: [self isCog]) ifTrue:
  					[result := objectMemory floatObjectOf: self getCogCodeZoneThreshold.
  					 primFailCode := self setCogCodeZoneThreshold: (self noInlineLoadFloatOrIntFrom: argOop)]].
  		[23] ->	[result := objectMemory integerObjectOf: extraVMMemory.
  				 extraVMMemory := arg.
  				 self initPrimCall].
  		[24] ->	[arg > 0 ifTrue:
  					[result := objectMemory integerObjectOf: objectMemory shrinkThreshold.
  					 objectMemory shrinkThreshold: arg.
  					 self initPrimCall]].
  		[25] ->	[arg > 0 ifTrue:
  					[result := objectMemory integerObjectOf: objectMemory growHeadroom.
  					 objectMemory growHeadroom: arg.
  					 self initPrimCall]].
  		[26] ->	[arg >= 0 ifTrue: "0 turns off the heartbeat"
  					[result := objectMemory integerObjectOf: self ioHeartbeatMilliseconds.
  					 self ioSetHeartbeatMilliseconds: arg.
  					 self initPrimCall]].
  		[34] ->	[(objectMemory hasSpurMemoryManagerAPI "was statAllocationCount; now statAllocatedBytes"
  				  and: [arg >= 0]) ifTrue:
  					[result := objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes.
  					 objectMemory setCurrentAllocatedBytesTo: arg.
  					 self initPrimCall]].
  		[43] ->	[(arg between: 0 and: 65535) ifTrue:
  					[result := objectMemory integerObjectOf: desiredNumStackPages.
  					 desiredNumStackPages := arg.
  					 self initPrimCall]].
  		[45] ->	[arg >= 0 ifTrue:
  					[result := objectMemory integerObjectOf: desiredEdenBytes.
  					 desiredEdenBytes := arg.
  					 self initPrimCall]].
  		[47] ->	[(self isCog
  				  and: [arg between: 0 and: self maxCogCodeSize]) ifTrue:
  					[result := objectMemory integerObjectOf: self getDesiredCogCodeSize.
  					 self setDesiredCogCodeSize: arg.
  					 self initPrimCall]].
  		[48] ->	[arg >= 0 ifTrue:
  					[| oldPrimitiveDoMixedArithmetic |
  					 oldPrimitiveDoMixedArithmetic := primitiveDoMixedArithmetic.
  					 result := self getImageHeaderFlagsParameter.
  					 self initPrimCall. "i.e. setImageHeaderFlags: can fail"
  					 self setImageHeaderFlags: arg.
  					 (primFailCode = 0
  					  and: [oldPrimitiveDoMixedArithmetic ~= primitiveDoMixedArithmetic]) ifTrue:
  						[self flushMethodCache.
+ 						 ^self flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result
- 						 self flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result
  						 "NOT REACHED (in CoInterpreter)"]]].
  		[49] ->	[(arg between: 0 and: 65535) ifTrue:
  					[result := objectMemory integerObjectOf: self ioGetMaxExtSemTableSize.
  					 self initPrimCall. "i.e. ioSetMaxExtSemTableSize: is allowed to fail"
  					 self setMaxExtSemSizeTo: arg]].
+ 		[50] ->	[(self isCog
+ 				  and: [arg between: 0 and: 32767]) ifTrue:
+ 					[result := objectMemory integerObjectOf: self getMaxLiteralCountForCompile.
+ 					 self setMaxLiteralCountForCompile: arg.
+ 					 self initPrimCall.
+ 					 ^self flushMethodsWithNumLiteralsAboveLimitAndContinueAnswering: result
+ 						 "NOT REACHED (in CoInterpreter)"]].
  		[55] ->	[objectMemory hasSpurMemoryManagerAPI ifTrue:
  					[result := objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio.
  					 primFailCode := objectMemory setHeapGrowthToSizeGCRatio: (self noInlineLoadFloatOrIntFrom: argOop)]].
  		[67] ->	[(arg >= 0
  				  and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
  					[result := self positiveMachineIntegerFor: objectMemory maxOldSpaceSize.
  					 primFailCode := objectMemory setMaxOldSpaceSize: arg]].
  		[68] ->	[result := objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping.
  				 self initPrimCall. "i.e. statAverageLivePagesWhenMapping: is allowed to fail"
  				 stackPages statAverageLivePagesWhenMapping: (self noInlineLoadFloatOrIntFrom: argOop)].
  		[69] ->	[arg >= 0 ifTrue:
  					[result := objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping.
  					 stackPages statMaxPageCountWhenMapping: arg.
  					 self initPrimCall]].
  		[74] ->	[(arg >= 0
  				  and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
  					[result := objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000.
  					 stackPages statMaxAllocSegmentTime: arg. "usually 0"
  					 self initPrimCall]].
  		[75] ->	[| mustFlush |
  				 result := objectMemory booleanObjectOf: self primitiveDoMixedArithmetic.
  				 self initPrimCall.
  				 mustFlush := primitiveDoMixedArithmetic ~= arg.
  				 primitiveDoMixedArithmetic := arg.
  				 mustFlush ifTrue:
  					[self flushMethodCache.
+ 					 ^self flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result
- 					 self flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result
  					 "NOT REACHED (in CoInterpreter)"]] }
  		otherwise: [].
  
  	self successful
  		ifTrue: [self methodReturnValue: result]  "return old value"
  		ifFalse: [self primitiveFailFor: PrimErrInappropriate] "attempting to write a read-only or non-existent parameter"!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
  primitiveVMParameter
  	"Behaviour depends on argument count:
  		0 args:	return an Array of VM parameter values;
  		1 arg:	return the indicated VM parameter;
  		2 args:	set the VM indicated parameter.
  	VM parameters are numbered as follows:
  		1	end (v3)/size(Spur) of old-space (0-based, read-only)
  		2	end (v3)/size(Spur) of young/new-space (read-only)
  		3	end (v3)/size(Spur) of heap (read-only)
  		4	nil (was allocationCount (read-only))
  		5	nil (was allocations between GCs (read-write)
  		6	survivor count tenuring threshold (read-write)
  		7	full GCs since startup (read-only)
  		8	total milliseconds in full GCs since startup (read-only)
  		9	incremental GCs (SqueakV3) or scavenges (Spur) since startup (read-only)
  		10	total milliseconds in incremental GCs (SqueakV3) or scavenges (Spur) since startup (read-only)
  		11	tenures of surving objects since startup or reset (read-write)
  		12-20 were specific to ikp's JITTER VM, now 12 16 open for use
  		13	if started, the start time in utc microseconds of the high-priority ticker
  		14	if started, the number of checkHighPriorityTickees calls
  		15	if started, the number of tickee calls from checkHighPriorityTickees
  		16	total microseconds at idle since start-up (if non-zero)
  		17	fraction of the code zone to use (Sista only; used to control code zone use to preserve sendAndBranchData on counter tripped callback)
  		18	total milliseconds in compaction phase of full GC since start-up (Spur only)
  		19	scavenge threshold, the effective size of eden.  When eden fills to the threshold a scavenge is scheduled. Newer Spur VMs only.
  		20	utc microseconds at VM start-up (actually at time initialization, which precedes image load).
  		21	root/remembered table size (occupancy) (read-only)
  		22	root table overflows since startup (read-only)
  		23	bytes of extra memory to reserve for VM buffers, plugins, etc (stored in image file header).
  		24	memory threshold above which shrinking object memory (rw)
  		25	memory headroom when growing object memory (rw)
  		26	interruptChecksEveryNms - force an ioProcessEvents every N milliseconds (rw)
  		27	number of times mark loop iterated for current IGC/FGC (read-only) includes ALL marking
  		28	number of times sweep loop iterated for current IGC/FGC (read-only)
  		29	number of times make forward loop iterated for current IGC/FGC (read-only)
  		30	number of times compact move loop iterated for current IGC/FGC (read-only)
  		31	number of grow memory requests (read-only)
  		32	number of shrink memory requests (read-only)
  		33	number of root table entries used for current IGC/FGC (read-only)
  		34	Spur: bytes allocated in total since start-up or reset (read-write) (Used to be number of allocations done before current IGC/FGC (read-only))
  		35	number of survivor objects after current IGC/FGC (read-only)
  		36	millisecond clock when current IGC/FGC completed (read-only)
  		37	number of marked objects for Roots of the world, not including Root Table entries for current IGC/FGC (read-only)
  		38	milliseconds taken by current IGC (read-only)
  		39	Number of finalization signals for Weak Objects pending when current IGC/FGC completed (read-only)
  		40	BytesPerOop for this image
  		41	imageFormatVersion for the VM
  		42	number of stack pages in use
  		43	desired number of stack pages (stored in image file header, max 65535)
  		44	size of eden, in bytes
  		45	desired size of eden, in bytes (stored in image file header)
  		46	machine code zone size, in bytes (Cog only; otherwise nil)
  		47	desired machine code zone size (stored in image file header; Cog only; otherwise nil)
  		48	various header flags.  See getImageHeaderFlags.
  		49	max size the image promises to grow the external semaphore table to (0 sets to default, which is 256 as of writing)
+ 		50	max literal count for JIT compile (stored in image file header; Cog only; otherwise nil)
+ 		51 nil; reserved for VM parameters that persist in the image (such as eden above)
- 		50-51 nil; reserved for VM parameters that persist in the image (such as eden above)
  		52	root/remembered table capacity
  		53	number of segments (Spur only; otherwise nil)
  		54	total size of free old space (Spur only, otherwise nil)
  		55	ratio of growth and image size at or above which a GC will be performed post scavenge
  		56	number of process switches since startup (read-only)
  		57	number of ioProcessEvents calls since startup (read-only)
  		58	number of ForceInterruptCheck calls since startup (read-only)
  		59	number of check event calls since startup (read-only)
  		60	number of stack page overflows since startup (read-only)
  		61	number of stack page divorces since startup (read-only)
  		62	compiled code compactions since startup (read-only; Cog only; otherwise nil)
  		63	total milliseconds in compiled code compactions since startup (read-only; Cog only; otherwise nil)
  		64	the number of methods that currently have jitted machine-code
  		65	various VM feature flags; see getCogVMFeatureFlags
  		66	the byte size of a stack page
  		67	the max allowed size of old space (Spur only; nil otherwise; 0 implies no limit except that of the underlying platform)
  		68	the average number of live stack pages when scanned by GC (at scavenge/gc/become et al) (read-write)
  		69	the maximum number of live stack pages when scanned by GC (at scavenge/gc/become et al) (read-write)
  		70	the vmProxyMajorVersion (the interpreterProxy VM_MAJOR_VERSION)
  		71	the vmProxyMinorVersion (the interpreterProxy VM_MINOR_VERSION)
  		72 total milliseconds in full GCs Mark phase since startup (read-only)
  		73 total milliseconds in full GCs Sweep phase since startup (read-only, can be 0 depending on compactors)
  		74 maximum pause time due to segment allocation
  		75 whether the arithmetic primitives perform conversion in case of mixed SmallInteger/Float (true) or fail (false)
  		76 the minimum unused headroom in all stack pages; Cog VMs only
  		
  	Note: Thanks to Ian Piumarta for this primitive."
  
  	| paramsArraySize index |
  	paramsArraySize := 76.
  	argumentCount = 0 ifTrue: [^self primitiveAllVMParameters: paramsArraySize].
  	argumentCount > 2 ifTrue: [^self primitiveFailFor: PrimErrBadNumArgs].
  	
  	"index read & checks"
  	index := self stackValue: (argumentCount = 1 ifTrue: [0] ifFalse: [1]).
  	(objectMemory isIntegerObject: index) ifFalse: [^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	(index < 1 or: [index > paramsArraySize]) ifTrue: [^self primitiveFailFor: PrimErrBadIndex].
  	
  	argumentCount = 1 ifTrue:	 "read VM parameter; written this way to avoid branch limits in V3 bytecode set"
+ 		[| result | "written thus to enable Slang inlining of primitiveGetVMParameter:"
- 		[| result |
  		 result := self primitiveGetVMParameter: index.
  		 ^self methodReturnValue: (result ifNil: [objectMemory nilObject])].
  
  	"write a VM parameter"
  	self primitiveSetVMParameter: index arg: self stackTop!



More information about the Vm-dev mailing list