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

commits at source.squeak.org commits at source.squeak.org
Sat Sep 26 21:12:52 UTC 2020


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

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

Name: VMMaker.oscog-eem.2824
Author: eem
Time: 26 September 2020, 2:12:42.907612 pm
UUID: 8f091e5b-fc0f-4b4b-ab5e-e90e598f75ee
Ancestors: VMMaker.oscog-eem.2823

Cog: Fix the crash when runnign tests in ImageSegmentTest>>#testContextsShouldBeWritableToaFile (see http://forum.world.st/corruption-of-PC-in-context-objects-or-not-tt5121662.html#none). In mapping a machine code pc, a code compaction may occur. In this case return through machine code is impossible without updating a C call stack return address, since the machine code method that invoked this primitive could have moved.  So if this happens, map to an interpreter frame and return to the interpreter.

Refactor CoInterpreter>>ceSendMustBeBooleanTo:interpretingAtDelta: to extract CoInterpreter>>convertToInterpreterFrame:,  Have CoInterpreterPrimitives>>primitiveClone, primitiveInstVarAt, primitiveSlotAt monitor newMethod's header and return to the interpreter if it has changed, indicating that a reclamation affecting newMethod has occurred.
In V3 make sure that newMethod is set in jitted shallowCopy, instvarAt, slotAt: (newMethod is assigned by default in Spur).

Again the split JIT/CoInterpreter design comes to the rescue in fixing a very tricky issue, code moving underneath one.  Being able to simply continue in the interpreter (impossible in e.g. HPS) means the solution is relatively straight-forward, and requires very little set-up.

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

Item was changed:
  ----- Method: CoInterpreter>>ceSendMustBeBooleanTo:interpretingAtDelta: (in category 'trampolines') -----
  ceSendMustBeBooleanTo: aNonBooleanObject interpretingAtDelta: jumpSize
  	"For RegisterAllocatingCogit we want the pc following a conditional branch not to be reachable, so
  	 we don't have to generate code to reload registers.  But notionally the pc following a conditional
  	 branch is reached when continuing from a mustBeBoolean error.  Instead of supporting this in the
  	 JIT, simply convert to an interpreter frame, backup the pc to the branch, reenter the interpreter
  	 and hence retry the mustBeBoolean send therein.  N.B. We could do this for immutability violations
  	 too, but immutability is used in actual applications and so should be performant, whereas
  	 mustBeBoolean errors are extremely rare and so we choose brevity over performance in this case."
  	<api>
- 	| cogMethod methodObj methodHeader startBcpc |
- 	<var: 'cogMethod' type: #'CogBlockMethod *'>
- 	<var: 'p' type: #'char *'>
  	self assert: (objectMemory addressCouldBeOop: aNonBooleanObject).
- 	cogMethod := self mframeCogMethod: framePointer.
- 	((self mframeIsBlockActivation: framePointer)
- 	 and: [cogMethod cmIsFullBlock not])
- 		ifTrue:
- 			[methodHeader := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodHeader.
- 			 methodObj := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodObject.
- 			 startBcpc := cogMethod startpc]
- 		ifFalse:
- 			[methodHeader := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodHeader.
- 			 methodObj := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodObject.
- 			 startBcpc := self startPCOfMethod: methodObj].
- 
- 	"Map the machine code instructionPointer to the interpreter instructionPointer of the branch."
  	instructionPointer := self popStack.
+ 	self convertToInterpreterFrame: jumpSize.
- 	instructionPointer := cogit bytecodePCFor: instructionPointer startBcpc: startBcpc in: cogMethod.
- 	instructionPointer := methodObj + objectMemory baseHeaderSize + instructionPointer - jumpSize - 1. "pre-decrement"
- 
- 	"Make space for the two extra fields in an interpreter frame"
- 	stackPointer to: framePointer + FoxMFReceiver by: objectMemory wordSize do:
- 		[:p| | oop |
- 		 oop := objectMemory longAt: p.
- 		 objectMemory
- 			longAt: p - objectMemory wordSize - objectMemory wordSize
- 			put: (objectMemory longAt: p)].
- 	stackPointer := stackPointer - objectMemory wordSize - objectMemory wordSize.
  	self push: aNonBooleanObject.
- 	"Fill in the fields"
- 	objectMemory
- 		longAt: framePointer + FoxIFrameFlags
- 			put: (self
- 					encodeFrameFieldHasContext: (self mframeHasContext: framePointer)
- 					isBlock: (self mframeIsBlockActivation: framePointer)
- 					numArgs: cogMethod cmNumArgs);
- 		longAt: framePointer + FoxIFSavedIP
- 			put: 0;
- 		longAt: framePointer + FoxMethod
- 			put: methodObj.
  
  	"and now reenter the interpreter..."
- 	self setMethod: methodObj methodHeader: methodHeader.
  	cogit ceInvokeInterpret.
  	"NOTREACHED"
  	^nil!

Item was added:
+ ----- Method: CoInterpreter>>convertToInterpreterFrame: (in category 'frame access') -----
+ convertToInterpreterFrame: pcDelta
+ 	"Convert the top machine code frame to an interpeeter frame.  Support for
+ 	 mustBeBoolean in the RegisterAllocatingCogit and for cloneContext: in shallowCopy
+ 	 when a code compaction is caused by machine code to bytecode pc mapping."
+ 
+ 	|  cogMethod methodHeader methodObj startBcpc |
+ 	<var: 'cogMethod' type: #'CogBlockMethod *'>
+ 	<var: 'p' type: #'char *'>
+ 
+ 	self assert: (self isMachineCodeFrame: framePointer).
+ 
+ 	cogMethod := self mframeCogMethod: framePointer.
+ 	((self mframeIsBlockActivation: framePointer)
+ 	 and: [cogMethod cmIsFullBlock not])
+ 		ifTrue:
+ 			[methodHeader := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodHeader.
+ 			 methodObj := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodObject.
+ 			 startBcpc := cogMethod startpc]
+ 		ifFalse:
+ 			[methodHeader := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodHeader.
+ 			 methodObj := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodObject.
+ 			 startBcpc := self startPCOfMethod: methodObj].
+ 
+ 	"Map the machine code instructionPointer to the interpreter instructionPointer of the branch."
+ 	instructionPointer := cogit bytecodePCFor: instructionPointer startBcpc: startBcpc in: cogMethod.
+ 	instructionPointer := methodObj + objectMemory baseHeaderSize + instructionPointer - pcDelta - 1. "pre-decrement"
+ 	 self validInstructionPointer: instructionPointer inMethod: methodObj framePointer: framePointer.
+ 
+ 	"Make space for the two extra fields in an interpreter frame"
+ 	stackPointer to: framePointer + FoxMFReceiver by: objectMemory wordSize do:
+ 		[:p| | oop |
+ 		 oop := objectMemory longAt: p.
+ 		 objectMemory
+ 			longAt: p - objectMemory wordSize - objectMemory wordSize
+ 			put: (objectMemory longAt: p)].
+ 	stackPointer := stackPointer - objectMemory wordSize - objectMemory wordSize.
+ 	"Fill in the fields"
+ 	objectMemory
+ 		longAt: framePointer + FoxIFrameFlags
+ 			put: (self
+ 					encodeFrameFieldHasContext: (self mframeHasContext: framePointer)
+ 					isBlock: (self mframeIsBlockActivation: framePointer)
+ 					numArgs: cogMethod cmNumArgs);
+ 		longAt: framePointer + FoxIFSavedIP
+ 			put: instructionPointer;
+ 		longAt: framePointer + FoxMethod
+ 			put: methodObj.
+ 
+ 	self setMethod: methodObj methodHeader: methodHeader!

Item was changed:
  ----- Method: CoInterpreter>>primitivePropertyFlagsForV3: (in category 'cog jit support') -----
  primitivePropertyFlagsForV3: primIndex
  	<inline: true>
  	"Answer any special requirements of the given primitive"
  	| baseFlags |
  	baseFlags := profileSemaphore ~= objectMemory nilObject
  					ifTrue: [PrimCallNeedsNewMethod + PrimCallCollectsProfileSamples]
  					ifFalse: [0].
  
  	longRunningPrimitiveCheckSemaphore ifNotNil:
  		[baseFlags := baseFlags bitOr: PrimCallNeedsNewMethod].
  
- 	self cCode: [] inSmalltalk: [#(primitiveExternalCall primitiveCalloutToFFI)]. "For senders..."
  	(self isCalloutPrimitiveIndex: primIndex) ifTrue: "For callbacks"
  		[baseFlags := baseFlags bitOr: PrimCallNeedsNewMethod + PrimCallNeedsPrimitiveFunction + PrimCallMayCallBack].
+ 	(self isCodeCompactingPrimitiveIndex: primIndex) ifTrue:
+ 		[baseFlags := baseFlags bitOr: PrimCallNeedsNewMethod].
  
  	^baseFlags!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>cloneContext: (in category 'primitive support') -----
+ cloneContext: aContext
+ 	"Copy a Context.  There are complications here.
+ 	 Fields of married contexts must be mapped to image-level values.
+ 	 In mapping a machine code pc, a code compaction may occur.
+ 	 In this case return through machine code is impossible without
+ 	 updating a C call stack return address, since the machine code
+ 	 method that invoked this primitive could have moved.  So if this
+ 	 happens, map to an interpreter frame and return to the interpreter."
+ 	| cloned couldBeCogMethod |
+ 	self assert: ((objectMemory isCompiledMethod: newMethod)
+ 				and: [(self primitiveIndexOf: newMethod) > 0]).
+ 
+ 	couldBeCogMethod := objectMemory methodHeaderOf: newMethod.
+ 	cloned := super cloneContext: aContext.
+ 
+ 	"If the header has changed in any way then it is most likely that machine code
+ 	 has been moved or reclaimed for this method and so normal return is impossible."
+ 	couldBeCogMethod ~= (objectMemory methodHeaderOf: newMethod) ifTrue:
+ 		[self convertToInterpreterFrame: 0.
+ 		 self push: cloned.
+ 		 cogit ceInvokeInterpret
+ 		 "NOTREACHED"].
+ 
+ 	^cloned!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveInstVarAt (in category 'object access primitives') -----
+ primitiveInstVarAt
+ 	"Override to deal with potential code compaction on accessing context pcs"
+ 	| index rcvr hdr fmt totalLength fixedFields value |
+ 	self assert: ((objectMemory isCompiledMethod: newMethod)
+ 				and: [(self primitiveIndexOf: newMethod) > 0]).
+ 
+ 	index := self stackTop.
+ 	rcvr := self stackValue: 1.
+ 	((objectMemory isNonIntegerObject: index)
+ 	 or: [argumentCount > 1 "e.g. object:instVarAt:"
+ 		and: [objectMemory isOopForwarded: rcvr]]) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	(objectMemory isImmediate: rcvr) ifTrue: [^self primitiveFailFor: PrimErrInappropriate].
+ 	index := objectMemory integerValueOf: index.
+ 	hdr := objectMemory baseHeader: rcvr.
+ 	fmt := objectMemory formatOfHeader: hdr.
+ 	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
+ 	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
+ 	(index >= 1 and: [index <= fixedFields]) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadIndex].
+ 	(fmt = objectMemory indexablePointersFormat
+ 	 and: [objectMemory isContextHeader: hdr])
+ 		ifTrue:
+ 			[| methodHeader |
+ 			 self externalWriteBackHeadFramePointers.
+ 			 "Note newMethod's header to check for potential code compaction
+ 			  in mapping the context's pc from machine code to bytecode."
+ 			 index = InstructionPointerIndex ifTrue:
+ 				[methodHeader := objectMemory methodHeaderOf: newMethod].
+ 			 value := self externalInstVar: index - 1 ofContext: rcvr.
+ 			"If the header has changed in any way then it is most likely that machine code
+ 			 has been moved or reclaimed for this method and so normal return is impossible."
+ 			 (index = InstructionPointerIndex
+ 			  and: [methodHeader ~= (objectMemory methodHeaderOf: newMethod)]) ifTrue:
+ 					[self pop: argumentCount + 1.
+ 					 self convertToInterpreterFrame: 0.
+ 					 self push: value.
+ 					 cogit ceInvokeInterpret
+ 					 "NOTREACHED"]]
+ 		ifFalse: [value := self subscript: rcvr with: index format: fmt].
+ 	self pop: argumentCount + 1 thenPush: value!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveSlotAt (in category 'object access primitives') -----
+ primitiveSlotAt
+ 	"Answer a slot in an object.  This numbers all slots from 1, ignoring the distinction between
+ 	 named and indexed inst vars.  In objects with both named and indexed inst vars, the named
+ 	 inst vars precede the indexed ones.  In non-object indexed objects (objects that contain
+ 	 bits, not object references) this primitive answers the raw integral value at each slot. 
+ 	 e.g. for Strings it answers the character code, not the Character object at each slot."
+ 
+ 	"Override to deal with potential code compaction on accessing context pcs"
+ 	| index rcvr fmt numSlots |
+ 	self assert: ((objectMemory isCompiledMethod: newMethod)
+ 				and: [(self primitiveIndexOf: newMethod) > 0]).
+ 
+ 	index := self stackTop.
+ 	rcvr := self stackValue: 1.
+ 	(objectMemory isIntegerObject: index) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	(objectMemory isImmediate: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadReceiver].
+ 	fmt := objectMemory formatOf: rcvr.
+ 	index := (objectMemory integerValueOf: index) - 1.
+ 
+ 	fmt <= objectMemory lastPointerFormat ifTrue:
+ 		[numSlots := objectMemory numSlotsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[| value numLiveSlots |
+ 			 (objectMemory isContextNonImm: rcvr)
+ 				ifTrue:
+ 					[self externalWriteBackHeadFramePointers.
+ 					 numLiveSlots := (self stackPointerForMaybeMarriedContext: rcvr) + CtxtTempFrameStart.
+ 					 (self asUnsigned: index) < numLiveSlots
+ 						ifTrue:
+ 							[| methodHeader |
+ 							 "Note newMethod's header to check for potential code compaction
+ 							  in mapping the context's pc from machine code to bytecode."
+ 							 index = InstructionPointerIndex ifTrue:
+ 								[methodHeader := objectMemory methodHeaderOf: newMethod].
+ 							 value := self externalInstVar: index ofContext: rcvr.
+ 							"If the header has changed in any way then it is most likely that machine code
+ 							 has been moved or reclaimed for this method and so normal return is impossible."
+ 							 (index = InstructionPointerIndex
+ 							  and: [methodHeader ~= (objectMemory methodHeaderOf: newMethod)]) ifTrue:
+ 									[self pop: argumentCount + 1.
+ 									 self convertToInterpreterFrame: 0.
+ 									 self push: value.
+ 									 cogit ceInvokeInterpret
+ 									 "NOTREACHED"]]
+ 						ifFalse: [value := objectMemory nilObject]]
+ 				ifFalse:
+ 					[value := objectMemory fetchPointer: index ofObject: rcvr].
+ 			 self pop: argumentCount + 1 thenPush: value.
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	fmt >= objectMemory firstByteFormat ifTrue:
+ 		[fmt >= objectMemory firstCompiledMethodFormat ifTrue:
+ 			[^self primitiveFailFor: PrimErrUnsupported].
+ 		 numSlots := objectMemory numBytesOfBytes: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1 thenPushInteger: (objectMemory fetchByte: index ofObject: rcvr).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [fmt >= objectMemory firstShortFormat]) ifTrue:
+ 		[numSlots := objectMemory num16BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1 thenPushInteger: (objectMemory fetchUnsignedShort16: index ofObject: rcvr).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	fmt = objectMemory sixtyFourBitIndexableFormat ifTrue:
+ 		[numSlots := objectMemory num64BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1
+ 				thenPush: (self positive64BitIntegerFor: (objectMemory fetchLong64: index ofObject: rcvr)).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	fmt >= objectMemory firstLongFormat ifTrue:
+ 		[numSlots := objectMemory num32BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1
+ 				thenPush: (self positive32BitIntegerFor: (objectMemory fetchLong32: index ofObject: rcvr)).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	^self primitiveFailFor: PrimErrBadReceiver!

Item was changed:
  ----- Method: CogVMSimulator class>>initialize (in category 'class initialization') -----
  initialize
  	"These are primitives that alter the state of the stack.  They are here simply for assert checking.
  	 After invocation the Cogit should not check for the expected stack delta when these primitives
  	 succeed, because the stack will usually have been modified."
  	StackAlteringPrimitives := #(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
+ 									primitiveClone primitiveInstVarAt primitiveSlotAt "because these can cause code compactions..."
  									primitiveEnterCriticalSection primitiveExitCriticalSection
  									primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch
  									primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  									primitiveExecuteMethodArgsArray primitiveExecuteMethod
  									primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  									primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs) asIdentitySet!

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
(excessive size, no diff calculated)

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

Item was added:
+ ----- Method: StackInterpreter>>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.  If so, they *cannot*
+ 	 return through the potentially moved method and so continue in the interpreter."
+ 	<inline: true>
+ 	self cCode: [] inSmalltalk: [#primitiveClone primitiveInstVarAt primitiveSlotAt]. "For senders..."
+ 	^primIndex = PrimNumberInstVarAt
+ 	or: [primIndex = PrimNumberShallowCopy
+ 	or: [primIndex = PrimNumberSlotAt]]!



More information about the Vm-dev mailing list