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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 27 19:46:43 UTC 2016


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

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

Name: VMMaker.oscog-eem.1849
Author: eem
Time: 27 April 2016, 12:44:35.473999 pm
UUID: d65892b1-b636-442a-affd-36ef8f9abcd1
Ancestors: VMMaker.oscog-eem.1848

Fix a bad bug in primitiveVoidVMStateForMethod. One might think that the heap scan is unnecessary if the method does not have a cog method.  But it could be the case that the code zone has recently been reclaimed and so not having a cog method is no indication that it didn't have a cog method some time in the recent past, and that there are indeed still contexts with machine code pcs out there.  The only steps that can be avoided is divorcing frames in the stack zone, and scanning to unlink and free if there isn't a cog method.

Refactor flushExternalPrimitiveOf: and callers to eliminate duplication; moving the primitive number test into flushExternalPrimitiveOf:.

Side-step inlining for bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: to reduce duplication in Spur's allObjectsDo: (which unrolls its argument three times).

Extract one phrase from cog:selector: for readability.

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

Item was changed:
  ----- Method: CoInterpreter>>ensureAllContextsWithMethodHaveBytecodePCs: (in category 'frame access') -----
  ensureAllContextsWithMethodHaveBytecodePCs: methodObj
  	"Map all native pcs to bytecoded pcs in all contexts on methodObj.
  	 Used to implement primitiveVoidVMStateForMethod."
  	objectMemory allObjectsDo:
  		[:oop|
  		 ((objectMemory isContextNonImm: oop)
  		  and: [(objectMemory fetchPointer: MethodIndex ofObject: oop) = methodObj]) ifTrue:
+ 			[self widowOrForceToBytecodePC: oop]]!
- 			[(self isMarriedOrWidowedContext: oop)
- 				ifTrue:
- 					"Since any machine-code frame activations of the method have been divorced
- 					 there should only be interpreted activations of marriecd contexts."
- 					[(self isWidowedContext: oop) ifFalse:
- 						[self deny: (self isMachineCodeFrame: (self frameOfMarriedContext: oop))]]
- 				ifFalse:
- 					[self ensureContextHasBytecodePC: oop]]]!

Item was changed:
  ----- Method: CoInterpreter>>flushExternalPrimitiveOf: (in category 'plugin primitive support') -----
  flushExternalPrimitiveOf: methodObj
  	"methodObj is a CompiledMethod containing an external primitive.
  	 Flush the function address and session ID of the CM.  Override
  	 to also flush the machine code call if one exists."
  	<api>
+ 	| primIdx |
+ 	primIdx := super flushExternalPrimitiveOf: methodObj.
+ 	(primIdx = PrimitiveExternalCallIndex
+ 	 and: [self methodHasCogMethod: methodObj]) ifTrue:
- 	super flushExternalPrimitiveOf: methodObj.
- 	(self methodHasCogMethod: methodObj) ifTrue:
  		[cogit
  			rewritePrimInvocationIn: (self cogMethodOf: methodObj)
  			to: #primitiveExternalCall]!

Item was added:
+ ----- Method: CoInterpreter>>widowOrForceToBytecodePC: (in category 'frame access') -----
+ widowOrForceToBytecodePC: ctxt
+ 	"Either widow the context or map its pc to a bytecode one.
+ 	 Used to implement primitiveVoidVMStateForMethod."
+ 	<inline: #never> "for debugging & saving space"
+ 	(self isMarriedOrWidowedContext: ctxt)
+ 		ifTrue:
+ 			"Since any machine-code frame activations of the method have been divorced
+ 			 there should only be interpreted activations of marriecd contexts."
+ 			[(self isWidowedContext: ctxt) ifFalse:
+ 				[self deny: (self isMachineCodeFrame: (self frameOfMarriedContext: ctxt))]]
+ 		ifFalse:
+ 			[self ensureContextHasBytecodePC: ctxt]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveVoidVMStateForMethod (in category 'system control primitives') -----
  primitiveVoidVMStateForMethod
  	"The receiver is a compiledMethod.  Clear all VM state associated with the method,
  	 including any machine code, or machine code pcs in context objects."
+ 	| activeContext methodObj hasCogMethod theFrame thePage |
  	<var: #theFrame type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	super primitiveFlushCacheByMethod.
+ 	"One might think (as this author did) that the heap scan is unnecessary if the method does not
+ 	 have a cog method.  But it could be the case that the code zone has recently been reclaimed
+ 	 and so not having a cog method is no indication that it didn't have a cog method some time in
+ 	 the recent past, and that there are indeed still contexts with machine code pcs out there.  The
+ 	 only steps that can be avoided is divorcing frames in the stack zone, and scanning to unlink and
+ 	 free if there isn't a cog method."
+ 	methodObj := self stackTop.
+ 	self push: instructionPointer.
+ 	self externalWriteBackHeadFramePointers.
+ 	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
+ 	(hasCogMethod := self methodHasCogMethod: methodObj) ifTrue:
+ 		[self divorceMachineCodeFramesWithMethod: methodObj].
+ 	self ensureAllContextsWithMethodHaveBytecodePCs: methodObj.
+ 	hasCogMethod ifTrue:
+ 		[cogit unlinkSendsTo: methodObj andFreeIf: true].
+ 	(self isStillMarriedContext: activeContext)
+ 		ifTrue:
+ 			[theFrame := self frameOfMarriedContext: activeContext.
+ 			 thePage := stackPages stackPageFor: theFrame.
+ 			 self assert: thePage headFP = theFrame.
+ 			 self setStackPageAndLimit: thePage.
+ 			 stackPointer := thePage headSP.
+ 			 framePointer := thePage headFP.
+ 			 instructionPointer := self popStack.
+ 			 self assert: methodObj = self stackTop]
+ 		ifFalse:
+ 			[self zeroStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
+ 			 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
+ 			 self popStack. "pop bogus machine-code instructionPointer"
+ 			 self assert: methodObj = self stackTop.
+ 			 self siglong: reenterInterpreter jmp: ReturnToInterpreter]!
- 	(self methodHasCogMethod: self stackTop) ifTrue:
- 		[| activeContext methodObj theFrame thePage |
- 		methodObj := self stackTop.
- 		self push: instructionPointer.
- 		self externalWriteBackHeadFramePointers.
- 		activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
- 		self divorceMachineCodeFramesWithMethod: methodObj.
- 		self ensureAllContextsWithMethodHaveBytecodePCs: methodObj.
- 		cogit unlinkSendsTo: methodObj andFreeIf: true.
- 		(self isStillMarriedContext: activeContext)
- 			ifTrue:
- 				[theFrame := self frameOfMarriedContext: activeContext.
- 				 thePage := stackPages stackPageFor: theFrame.
- 				 self assert: thePage headFP = theFrame.
- 				 self setStackPageAndLimit: thePage.
- 				 stackPointer := thePage headSP.
- 				 framePointer := thePage headFP.
- 				 instructionPointer := self popStack.
- 				 self assert: methodObj = self stackTop]
- 			ifFalse:
- 				[self zeroStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
- 				 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
- 				 self popStack. "pop bogus machine-code instructionPointer"
- 				 self assert: methodObj = self stackTop.
- 				 self siglong: reenterInterpreter jmp: ReturnToInterpreter]]
- !

Item was changed:
  ----- Method: Cogit>>cog:selector: (in category 'jit - api') -----
  cog: aMethodObj selector: aSelectorOop
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	(self exclude: aMethodObj selector: aSelectorOop) ifTrue:
+ 		[^nil].
- 	self cCode: [] inSmalltalk: "for debugging, allow excluding methods based on selector or methodClass"
- 		[self class initializationOptions
- 			at: #DoNotJIT
- 			ifPresent:
- 				[:excluded| | methodClass selector |
- 				methodClass := coInterpreter nameOfClass: (coInterpreter methodClassOf: aMethodObj).
- 				selector := coInterpreter stringOf: aSelectorOop.
- 				(excluded anySatisfy: [:exclude| selector = exclude or: [methodClass = exclude]]) ifTrue:
- 					[coInterpreter transcript nextPutAll: 'EXCLUDING '; nextPutAll: methodClass; nextPutAll: '>>#'; nextPutAll: selector; cr; flush.
- 					 ^nil]]].
  	"In Newspeak we support anonymous accessors and hence tolerate the same
  	 method being cogged multiple times.  But only if the method class association is nil."
  	NewspeakVM
  		ifTrue:
  			[(coInterpreter methodHasCogMethod: aMethodObj) ifTrue:
  				[cogMethod := coInterpreter cogMethodOf: aMethodObj.
  				 self deny: cogMethod selector = aSelectorOop.
  				 cogMethod selector = aSelectorOop ifTrue:
  					[^cogMethod].
  				 (coInterpreter methodClassAssociationOf: aMethodObj) ~= objectMemory nilObject ifTrue:
+ 					[self cCode: 'extern void *firstIndexableField(sqInt)'. "Slang, au natural"
+ 					 self warnMultiple: cogMethod selectors: aSelectorOop.
- 					[self warnMultiple: cogMethod selectors: aSelectorOop.
  					^nil]]]
  		ifFalse: [self deny: (coInterpreter methodHasCogMethod: aMethodObj)].
  	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop)
  		isMNUCase: false.
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	NewspeakVM ifTrue:
  		[cogMethod := methodZone findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop.
  		 cogMethod ifNotNil:
  			[(coInterpreter methodHasCogMethod: aMethodObj) not ifTrue:
  				[self assert: (coInterpreter rawHeaderOf: aMethodObj) = cogMethod methodHeader.
  				 cogMethod methodObject: aMethodObj.
  				 coInterpreter rawHeaderOf: aMethodObj put: cogMethod asInteger].
  			^cogMethod]].
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	methodObj := aMethodObj.
  	methodHeader := objectMemory methodHeaderOf: aMethodObj.
  	cogMethod := self compileCogMethod: aSelectorOop.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		 self maybeFreeCounters.
  		 "Right now no errors should be reported, so nothing more to do."
  		 "self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was added:
+ ----- Method: Cogit>>exclude:selector: (in category 'simulation only') -----
+ exclude: aMethodObj selector: aSelectorOop
+ 	"For debugging, allow excluding methods based on selector or methodClass.  Answer if the mehtod should be excluded."
+ 	<inline: true>
+ 	^self
+ 		cCode: [false]
+ 		inSmalltalk:
+ 			[self class initializationOptions
+ 				at: #DoNotJIT
+ 				ifPresent:
+ 					[:excluded| | methodClass selector |
+ 					methodClass := coInterpreter nameOfClass: (coInterpreter methodClassOf: aMethodObj).
+ 					selector := coInterpreter stringOf: aSelectorOop.
+ 					(excluded anySatisfy: [:exclude| selector = exclude or: [methodClass = exclude]]) ifTrue:
+ 						[coInterpreter transcript nextPutAll: 'EXCLUDING '; nextPutAll: methodClass; nextPutAll: '>>#'; nextPutAll: selector; cr; flush.
+ 						 ^true]].
+ 			 ^false]!

Item was changed:
  ----- Method: Cogit>>warnMultiple:selectors: (in category 'debug printing') -----
  warnMultiple: cogMethod selectors: aSelectorOop
  	<inline: true>
+ 	<var: 'cogMethod' type: #'CogMethod *'>
- 	self cCode: 'extern void *firstIndexableField(sqInt)'.
  	self cCode:
  			[self fp: #stderr
  				r: 'Warning, attempt to use method with selector %.*s and selector %.*s\n'
  				i: (self cCoerceSimple: (objectMemory numBytesOf: cogMethod selector) to: #int)
  				n: (self cCoerceSimple: (objectMemory firstIndexableField: cogMethod selector) to: #'char *')
  				t: (objectMemory numBytesOf: aSelectorOop)
  				f: (self cCoerceSimple: (objectMemory firstIndexableField: aSelectorOop) to: #'char *')]
  		inSmalltalk:
  			[self warn: 'Warning, attempt to use method with selector ',
  						(coInterpreter stringOf: cogMethod selector),
  						' and selector ',
  						(coInterpreter stringOf: aSelectorOop)]!

Item was changed:
  ----- Method: NewObjectMemory>>printActivationsOf: (in category 'debug printing') -----
  printActivationsOf: aMethodObj
  	"Scan the heap printing the oops of any and all contexts that refer to anOop"
  	| oop |
  	<api>
  	oop := self firstAccessibleObject.
  	[oop = nil] whileFalse:
  		[((self isContextNonImm: oop)
  		  and: [aMethodObj = (self fetchPointer: MethodIndex ofObject: oop)]) ifTrue:
  			[coInterpreter
+ 				printHex: oop; space; printOopShort: oop; print: ' pc ';
- 				printHex: oop; printOopShort: oop; print: ' pc ';
  				printHex: (self fetchPointer: InstructionPointerIndex ofObject: oop); cr].
  		 oop := self accessibleObjectAfter: oop]!

Item was added:
+ ----- Method: ObjectMemory>>isCompiledMethodFormat: (in category 'interpreter access') -----
+ isCompiledMethodFormat: format
+ 	^format >= self firstCompiledMethodFormat!

Item was changed:
  ----- Method: ObjectMemory>>printActivationsOf: (in category 'debug printing') -----
  printActivationsOf: aMethodObj
  	"Scan the heap printing the oops of any and all contexts that refer to anOop"
  	| oop |
  	<api>
  	oop := self firstAccessibleObject.
  	[oop = nil] whileFalse:
  		[((self isContextNonImm: oop)
  		  and: [aMethodObj = (self fetchPointer: MethodIndex ofObject: oop)]) ifTrue:
  			[self interpreter
+ 				printHex: oop; space; printOopShort: oop; print: ' pc ';
- 				printHex: oop; printOopShort: oop; print: ' pc ';
  				printHex: (self fetchPointer: InstructionPointerIndex ofObject: oop); cr].
  		 oop := self accessibleObjectAfter: oop]!

Item was changed:
  ----- Method: SpurMemoryManager>>printActivationsOf: (in category 'debug printing') -----
  printActivationsOf: aMethodObj
  	"Scan the heap printing the oops of any and all contexts that refer to anOop"
  	<api>
  	self allObjectsDo:
  		[:obj| 
  		 ((self isContextNonImm: obj)
  		  and: [aMethodObj = (self fetchPointer: MethodIndex ofObject: obj)]) ifTrue:
  			[coInterpreter
+ 				printHex: obj; space; printOopShort: obj; print: ' pc ';
- 				printHex: obj; printOopShort: obj; print: ' pc ';
  				printHex: (self fetchPointer: InstructionPointerIndex ofObject: obj); cr]]!

Item was changed:
  ----- Method: StackInterpreter>>bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: (in category 'frame access') -----
  bereaveAllMarriedContextsForSnapshotFlushingExternalPrimitivesIf: flushExtPrims
  	"Enumerate all contexts and convert married contexts to widowed contexts so
  	 that the snapshot contains only single contexts.  This allows the test for being
  	 married to avoid checking for a context's frame pointer being in bounds.  If
  	 flushExtPrims is true, flush references to external primitives in methods."
  	objectMemory allObjectsDo:
  		[:obj| | fmt |
  		fmt := objectMemory formatOf: obj.
  		(fmt = objectMemory indexablePointersFormat
  		  and: [objectMemory isContextNonImm: obj]) ifTrue:
+ 			[self makeContextSnapshotSafe: obj].
- 			[(self isMarriedOrWidowedContext: obj)
- 				ifTrue: "The stack pages have already been discarded.  Any remaining married contexts are actually widows."
- 					[self markContextAsDead: obj]
- 				ifFalse:
- 					[self ensureContextHasBytecodePC: obj].
- 			 "Fill slots beyond top of stack with nil"
- 			 (self fetchStackPointerOf: obj) + CtxtTempFrameStart
- 				to: (objectMemory numSlotsOf: obj) - 1
- 				do: [:i |
- 					objectMemory
- 						storePointerUnchecked: i
- 						ofObject: obj
- 						withValue: objectMemory nilObject]].
  		 "Clean out external functions from compiled methods"
  		 (flushExtPrims
+ 		  and: [objectMemory isCompiledMethodFormat: fmt]) ifTrue:
+ 			[self flushExternalPrimitiveOf: obj]]!
- 		  and: [fmt >= objectMemory firstCompiledMethodFormat]) ifTrue:
- 			["Its primitiveExternalCall"
- 			 (self primitiveIndexOf: obj) = PrimitiveExternalCallIndex ifTrue:
- 				[self flushExternalPrimitiveOf: obj]]]!

Item was changed:
  ----- Method: StackInterpreter>>flushExternalPrimitiveOf: (in category 'plugin primitive support') -----
  flushExternalPrimitiveOf: methodObj
+ 	"methodObj is a CompiledMethod. If it contains an external primitive,
+ 	 flush the function address and session ID of the CM.  Answer the prim
+ 	 index for the benefit of subclass overrides."
+ 	<inline: false>
+ 	| header primIdx lit |
+ 	header := objectMemory methodHeaderOf: methodObj.
+ 	primIdx := self primitiveIndexOfMethod: methodObj header: header.
+ 	(primIdx = PrimitiveExternalCallIndex
+ 	 and: [(objectMemory literalCountOfMethodHeader: header) > 0]) ifTrue: "If not, something's broken"
+ 		[lit := self literal: 0 ofMethod: methodObj.
+ 		((objectMemory isArray: lit) and: [(objectMemory numSlotsOf: lit) = 4]) ifTrue: "If not, something's broken"
+ 			[objectMemory
+ 				storePointerUnchecked: 2 ofObject: lit withValue: ConstZero;
+ 				storePointerUnchecked: 3 ofObject: lit withValue: ConstZero]].
+ 	^primIdx!
- 	"methodObj is a CompiledMethod containing an external primitive. Flush the function address and session ID of the CM"
- 	| lit |
- 	(objectMemory literalCountOf: methodObj) > 0 ifFalse:
- 		[^nil]. "Something's broken"
- 	lit := self literal: 0 ofMethod: methodObj.
- 	((objectMemory isArray: lit) and:[(objectMemory lengthOf: lit) = 4]) ifFalse:
- 		[^nil]. "Something's broken"
- 	"ConstZero is a known SmallInt so no root check needed"
- 	objectMemory storePointerUnchecked: 2 ofObject: lit withValue: ConstZero.
- 	objectMemory storePointerUnchecked: 3 ofObject: lit withValue: ConstZero!

Item was changed:
  ----- Method: StackInterpreter>>flushExternalPrimitives (in category 'plugin primitive support') -----
  flushExternalPrimitives
  	"Flush the references to external functions from plugin primitives.
  	 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."
  	objectMemory allObjectsDo:
+ 		[:oop|
+ 		(objectMemory isCompiledMethod: oop) ifTrue: "This is a compiled method"
+ 			[self flushExternalPrimitiveOf: oop]].
- 		[:oop| | primIdx |
- 		(objectMemory isFreeObject: oop) ifFalse:
- 			[(objectMemory isCompiledMethod: oop) ifTrue: "This is a compiled method"
- 				[primIdx := self primitiveIndexOf: oop.
- 				 primIdx = PrimitiveExternalCallIndex ifTrue: "It's primitiveExternalCall"
- 					[self flushExternalPrimitiveOf: oop]]]].
  	self flushMethodCache.
  	self flushExternalPrimitiveTable!

Item was added:
+ ----- Method: StackInterpreter>>makeContextSnapshotSafe: (in category 'frame access') -----
+ makeContextSnapshotSafe: ctxt
+ 	"Convert married contexts to widowed contexts, and in the CoInterpreter,
+ 	 map any machine code pcs to bytecode pcs, and then nil all slots beyond
+ 	 top of stack, so that the context can be resumed on any VM."
+ 	<inline: false>
+ 	self assert: (objectMemory isContext: ctxt).
+ 	"The stack pages have already been discarded.  Any remaining married contexts are actually widows."
+ 	(self isMarriedOrWidowedContext: ctxt)
+ 		ifTrue: [self markContextAsDead: ctxt]
+ 		ifFalse: [self ensureContextHasBytecodePC: ctxt].
+ 	 "Fill slots beyond top of stack with nil"
+ 	 (self fetchStackPointerOf: ctxt) + CtxtTempFrameStart
+ 		to: (objectMemory numSlotsOf: ctxt) - 1
+ 		do: [:i |
+ 			 objectMemory
+ 				storePointerUnchecked: i
+ 				ofObject: ctxt
+ 				withValue: objectMemory nilObject]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveFlushCacheByMethod (in category 'system control primitives') -----
  primitiveFlushCacheByMethod
  	"The receiver is a compiledMethod.  Clear all entries in the method lookup cache that refer to this method, presumably because it has been redefined, overridden or removed."
+ 	| probe oldMethod |
- 	| probe oldMethod primIdx |
  	oldMethod := self stackTop.
  	probe := 0.
  	1 to: MethodCacheEntries do:
  		[:i |
  		(methodCache at: probe + MethodCacheMethod) = oldMethod ifTrue:
  			[methodCache at: probe + MethodCacheSelector put: 0].
  		probe := probe + MethodCacheEntrySize].
+ 	self flushExternalPrimitiveOf: oldMethod.
- 	primIdx := self primitiveIndexOf: oldMethod.
- 	primIdx = PrimitiveExternalCallIndex ifTrue:
- 		["It's primitiveExternalCall"
- 		self flushExternalPrimitiveOf: oldMethod].
  	self flushAtCache!



More information about the Vm-dev mailing list