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

commits at source.squeak.org commits at source.squeak.org
Sun Sep 5 13:37:47 UTC 2021


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

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

Name: VMMaker.oscog-eem.3051
Author: eem
Time: 5 September 2021, 6:37:35.453761 am
UUID: 2dad9ef3-af23-4589-be9a-1e1954ba8bcc
Ancestors: VMMaker.oscog-eem.3050

CoInterpreter:
Run primitiveCopyObject on the Smalltalk stack (for Symbol>>intern:).
Have primitiveSetOrHasIdentityHash support all of
	e.g. Symbol primitiveSetIdentityHashOf: aSymbol to: hash
	anObject primitiveSetIdentityHash: hashValue isBehavior: boolean
	anObject primitiveSetIdentityHashTo: hash
Fix a spelling error PrimNumberUnoadModule => PrimNumberUnloadModule

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

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
  	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer CReturnAddress primTracePluginName'
+ 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberCopyObject PrimNumberObjectAtPut PrimTraceLogSize PrimitiveMetadataFlagsShift RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
- 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberObjectAtPut PrimTraceLogSize PrimitiveMetadataFlagsShift RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
  !CoInterpreter commentStamp: 'eem 3/31/2020 18:56' prior: 0!
  I am a variant of the StackInterpreter that can co-exist with the Cog JIT.  I interpret unjitted methods, either because they have been found for the first time or because they are judged to be too big to JIT.  See CogMethod class's comment for method interoperability.
  
  cogCodeSize
  	- the current size of the machine code zone
  
  cogCompiledCodeCompactionCalledFor
  	- a variable set when the machine code zone runs out of space, causing a machine code zone compaction at the next available opportunity
  
  cogMethodZone
  	- the manager for the machine code zone (instance of CogMethodZone)
  
  cogit
  	- the JIT (co-jit) (instance of SimpleStackBasedCogit, StackToRegisterMappoingCogit, etc)
  
  deferSmash
  	- a flag causing deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  deferredSmash
  	- a flag noting deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  desiredCogCodeSize
  	- the desred size of the machine code zone, set at startup or via primitiveVMParameter to be written at snapshot time
  
  flagInterpretedMethods
  	- true if methods that are interpreted shoudl have their flag bit set (used to identity methods that are interpreted because they're unjittable for some reason)
  
  gcMode
  	- the variable holding the gcMode, used to inform the cogit of how to scan the machine code zone for oops on GC
  
  heapBase
  	- the address in memory of the base of the objectMemory's heap, which is immediately above the machine code zone
  
  lastCoggableInterpretedBlockMethod
  	- a variable used to invoke the cogit for a block mehtod being invoked repeatedly in the interpreter
  
  lastUncoggableInterpretedBlockMethod
  	- a variable used to avoid invoking the cogit for an unjittable method encountered on block evaluation
  
  maxLiteralCountForCompile
  	- the variable controlling which methods to jit.  methods with a literal count above this value will not be jitted (on the grounds that large methods are typically used for initialization, and take up a lot of space in the code zone)
  
  minBackwardJumpCountForCompile
  	- the variable controlling when to attempt to jit a method being interpreted.  If as many backward jumps as this occur, the current method will be jitted
  
  primTraceLog
  	- a small array implementing a crcular buffer logging the last N primitive invocations, GCs, code compactions, etc used for crash reporting
  
  primTraceLogIndex
  	- the index into primTraceLog of the next entry
  
  reenterInterpreter
  	- the jmpbuf used to jmp back into the interpreter when transitioning from machine code to the interpreter
  
  statCodeCompactionCount
  	- the count of machine code zone compactions
  
  statCodeCompactionUsecs
  	- the total microseconds spent in machine code zone compactions
  
  traceLog
  	- a log of various events, used in debugging
  
  traceLogIndex
  	- the index into traceLog of the next entry
  
  traceSources
  	- the names associated with the codes of events in traceLog
  
  CFramePointer
  	- if in use, the value of the C frame pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
  
  CStackPointer
  	- the value of the C stack pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
  
  CReturnAddress
  	- the return address for the function call which invoked the interpreter at start-up.  Using this as teh return address when entering the interpreter via ceInvokeInterpeter maintains a valid stack.  Since this is effevtively a constant it does not need to be saved and restored once set.!

Item was changed:
  ----- Method: CoInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
  initializePrimitiveTable
  	super initializePrimitiveTable.
+ 
+ 	"These two are run on the Smalltalk stack under Spur.  See primitivePropertyFlagsForSpur:"
  	PrimNumberObjectAtPut := 69.
  	self assert: (PrimitiveTable at: PrimNumberObjectAtPut + 1) = #primitiveObjectAtPut.
+ 	PrimNumberCopyObject := 168.
+ 	self assert: (PrimitiveTable at: PrimNumberCopyObject + 1) = #primitiveCopyObject.
  
  	#(216 253) do:
  		[:pidx| self assert: (PrimitiveTable at: pidx + 1) = #primitiveFail].
  	self assert: (PrimitiveTable at: 215 + 1) = #primitiveFlushCacheByMethod.
  	PrimitiveTable
  		at: 253 + 1 put: #primitiveCollectCogCodeConstituents;
  		at: 215 + 1 put: #primitiveVoidVMStateForMethod;
  		at: 216 + 1 put: #primitiveMethodXray!

Item was changed:
  ----- Method: CoInterpreter>>isCodeCompactingPrimitiveIndex: (in category 'primitive support') -----
  isCodeCompactingPrimitiveIndex: primIndex
  	"If instVarAt:, slotAt: or shallowCopy operate on a Context then they compute a
  	 bytecode pc and hence may provoke a code compaction. Hence primitive invocation
  	 from these primitives must use a static return address (cePrimReturnEnterCogCode:).
  	 Note that the process switch primitives may also provoke a code compaction, which
  	 happens when switching to a process whose top context has a machine code pc but
  	 the method is no longer in the code cache.  However, in this case they are switching
  	 process and don't go through the normal return. So we don't include them here."
  	<inline: true>
  	self cCode: [] inSmalltalk: [#primitiveClone. #primitiveInstVarAt. #primitiveSlotAt. #primitiveFlushExternalPrimitives. #primitiveUnloadModule]. "For senders..."
  	^primIndex = PrimNumberInstVarAt
  	or: [primIndex = PrimNumberShallowCopy
  	or: [primIndex = PrimNumberSlotAt
  	or: [primIndex = PrimNumberFlushExternalPrimitives
+ 	or: [primIndex = PrimNumberUnloadModule]]]]!
- 	or: [primIndex = PrimNumberUnoadModule]]]]!

Item was changed:
  ----- Method: CoInterpreter>>primitivePropertyFlagsForSpur: (in category 'cog jit support') -----
  primitivePropertyFlagsForSpur: primIndex
  	<inline: true>
  	"Answer any special requirements of the given primitive.  Spur always needs to set
  	 primitiveFunctionPointer and newMethod so primitives can retry on failure due to forwarders."
  	| baseFlags |
  	self cCode: [] inSmalltalk: [#(primitiveObjectAtPut primitiveExternalCall primitiveCalloutToFFI)]. "For senders..."
  	baseFlags := profileSemaphore = objectMemory nilObject
  					ifTrue: [0]
  					ifFalse: [PrimCallCollectsProfileSamples].
+ 	(primIndex = PrimNumberObjectAtPut
+ 	 or: [primIndex = PrimNumberCopyObject]) ifTrue:
- 	primIndex = PrimNumberObjectAtPut ifTrue:
  		[^baseFlags + PrimCallOnSmalltalkStack].
  	baseFlags := baseFlags + PrimCallNeedsPrimitiveFunction + PrimCallNeedsNewMethod.
  
  	(self isCalloutPrimitiveIndex: primIndex) ifTrue: "For callbacks & module unloading"
  		[^baseFlags + PrimCallMayEndureCodeCompaction + PrimCallIsExternalCall].
  	(self isCodeCompactingPrimitiveIndex: primIndex) ifTrue: "For code reclamations"
  		[^baseFlags bitOr: PrimCallMayEndureCodeCompaction].
  
  	^baseFlags!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSetOrHasIdentityHash (in category 'object access primitives') -----
  primitiveSetOrHasIdentityHash
  	| hash oldHash thisReceiver isReceiverAClass |
  	argumentCount = 0 ifTrue:
  		[| hasHash |
  		 hasHash := (objectMemory isNonImmediate: self stackTop)
  						and: [objectMemory hasIdentityHash: self stackTop].
+ 		 ^self methodReturnBool: hasHash].
+ 	isReceiverAClass := false.
- 		 self pop: 1 thenPushBool: hasHash.
- 		 ^self].
  	argumentCount = 2 
  		ifTrue: 
+ 			[| lastArg |
+ 			 lastArg := self stackTop.
+ 			 (objectMemory isIntegerObject: lastArg)
+ 				ifTrue: "e.g. Symbol primitiveSetIdentityHashOf: aSymbol to: hash"
+ 					[hash := lastArg.
+ 					 thisReceiver := self stackValue: 1]
+ 				ifFalse: "anObject primitiveSetIdentityHash: hashValue isBehavior: boolean"
+ 					[thisReceiver := self stackValue: 2.
+ 					 hash := self stackValue: 1.
+ 					 lastArg = objectMemory trueObject
+ 						ifTrue: [isReceiverAClass := true]
+ 						ifFalse:
+ 							[lastArg = objectMemory falseObject ifFalse:
+ 								[^self primitiveFailFor: PrimErrBadArgument]]]]
+ 		ifFalse: "anObject primitiveSetIdentityHashTo: hash"
+ 			[thisReceiver := self stackValue: 1.
+ 			 hash := self stackTop].
+ 	(objectMemory isIntegerObject: hash) ifFalse:
+ 		 [^self primitiveFailFor: PrimErrBadArgument].
+ 	(objectMemory isNonImmediate: thisReceiver) ifFalse:
+ 		[^self primitiveFailFor: (thisReceiver = (self stackValue: argumentCount)
+ 									ifTrue: [PrimErrBadReceiver]
+ 									ifFalse: [PrimErrBadArgument])].
+ 	oldHash := objectMemory hashBitsOf: thisReceiver.
+ 	objectMemory setHashBitsOf: thisReceiver to: hash.
+ 	(isReceiverAClass and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ 		[objectMemory classAtIndex: hash put: thisReceiver.
+ 		"this figures out if the index is ambiguous and fixes all the instances if needed"
+ 		objectMemory allInstancesOf: thisReceiver].
+ 	 self methodReturnInteger: oldHash!
- 			[isReceiverAClass := self booleanValueOf: self stackTop.
- 			 self successful ifFalse:
- 				[^self primitiveFailFor: PrimErrBadArgument]]
- 		ifFalse: [isReceiverAClass := false].
- 	hash := self stackIntegerValue: argumentCount - 1.
- 	thisReceiver := self stackObjectValue: argumentCount.
- 	self successful ifTrue:
- 		[oldHash := objectMemory hashBitsOf: thisReceiver.
- 		 objectMemory setHashBitsOf: thisReceiver to: hash.
- 		 (isReceiverAClass and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
- 			[objectMemory classAtIndex: hash put: thisReceiver.
- 			"this figures out if the index is ambiguous and fixes all the instances if needed"
- 			objectMemory allInstancesOf: thisReceiver].
- 		 self methodReturnInteger: oldHash]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  SharedPool subclass: #VMBytecodeConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BytecodeSetHasDirectedSuperSend CtxtTempFrameStart LargeContextBit LargeContextSize LargeContextSlots NewsqueakV4BytecodeSet PrimNumberDoExternalCall PrimNumberDoPrimitive PrimNumberExternalCall PrimNumberFFICall PrimNumberFlushExternalPrimitives PrimNumberInstVarAt PrimNumberShallowCopy PrimNumberSlotAt PrimNumberUnloadModule SistaV1BytecodeSet SmallContextSize SmallContextSlots SqueakV3PlusClosuresBytecodeSet'
- 	classVariableNames: 'BytecodeSetHasDirectedSuperSend CtxtTempFrameStart LargeContextBit LargeContextSize LargeContextSlots NewsqueakV4BytecodeSet PrimNumberDoExternalCall PrimNumberDoPrimitive PrimNumberExternalCall PrimNumberFFICall PrimNumberFlushExternalPrimitives PrimNumberInstVarAt PrimNumberShallowCopy PrimNumberSlotAt PrimNumberUnoadModule SistaV1BytecodeSet SmallContextSize SmallContextSlots SqueakV3PlusClosuresBytecodeSet'
  	poolDictionaries: 'VMBasicConstants'
  	category: 'VMMaker-Interpreter'!
  
  !VMBytecodeConstants commentStamp: '<historical>' prior: 0!
  self ensureClassPool.
  #(CtxtTempFrameStart LargeContextBit LargeContextSize SmallContextSize) do:
  	[:k|
  	self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list