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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 16 19:58:50 UTC 2014


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

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

Name: VMMaker.oscog-eem.823
Author: eem
Time: 16 July 2014, 12:55:42.046 pm
UUID: 2d337398-d2dd-4715-9476-9a463c29efad
Ancestors: VMMaker.oscog-eem.822

Reimplement the backward count in interpreted methods,
storing the count in IFrameFlags, hence eliminating the
requirement that the jump happens consecutively N times in
just that method with no backward jumps in any other method.
The Chameneos benchmark has this pattern and so two
mehtods don't get jitted.
This eliminates lastBackwardJumpMethod & backwardJumpCount.

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

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
+ 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod reenterInterpreter deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod processHasThreadId flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile noThreadingOfGUIThread'
- 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod lastBackwardJumpMethod backwardJumpCount reenterInterpreter deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod processHasThreadId flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile noThreadingOfGUIThread'
  	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield CogitClass HasBeenReturnedFromMCPC MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimTraceLogSize ReturnToInterpreter RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
  !CoInterpreter commentStamp: '<historical>' 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.!

Item was changed:
  ----- Method: CoInterpreter class>>initializeFrameIndices (in category 'initialization') -----
  initializeFrameIndices
  	"Format of a stack frame.  Word-sized indices relative to the frame pointer.
  	 Terminology
  		Frames are either single (have no context) or married (have a context).
  		Contexts are either single (exist on the heap), married (have a context) or widowed (had a frame that has exited).
  	 Stacks grow down:
  
  			receiver for method activations/closure for block activations
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (initialized to nil)
  			frame flags (interpreter only)
  			saved method ip (initialized to 0; interpreter only)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  
  	In an interpreter frame
  		frame flags holds
+ 			the backward jump count (see ifBackwardsCheckForEvents)
  			the number of arguments (since argument temporaries are above the frame)
  			the flag for a block activation
  			and the flag indicating if the context field is valid (whether the frame is married).
  		saved method ip holds the saved method ip when the callee frame is a machine code frame.
  		This is because the saved method ip is actually the ceReturnToInterpreterTrampoline address.
  	In a machine code frame
  		the flag indicating if the context is valid is the least significant bit of the method pointer
  		the flag for a block activation is the next most significant bit of the method pointer
  
  	Interpreter frames are distinguished from method frames by the method field which will
  	be a pointer into the heap for an interpreter frame and a pointer into the method zone for
  	a machine code frame.
  
  	The first frame in a stack page is the baseFrame and is marked as such by a saved fp being its stackPage,
  	in which case the first word on the stack is the caller context (possibly hybrid) beneath the base frame."
  
  	| fxCallerSavedIP fxSavedFP fxMethod fxIFrameFlags fxThisContext fxIFReceiver fxMFReceiver fxIFSavedIP |
  	fxCallerSavedIP := 1.
  	fxSavedFP := 0.
  	fxMethod := -1.
  	fxThisContext := -2.
  	fxIFrameFlags := -3.	"Can find numArgs, needed for fast temp access. args are above fxCallerSavedIP.
  							 Can find ``is block'' bit
  							 Can find ``has context'' bit"
  	fxIFSavedIP := -4.
  	fxIFReceiver := -5.
  	fxMFReceiver := -3.
  
  	"For debugging nil out values that differ in the StackInterpreter."
  	FrameSlots := #undeclared.
  	IFrameSlots := fxCallerSavedIP - fxIFReceiver + 1.
  	MFrameSlots := fxCallerSavedIP - fxMFReceiver + 1.
  
  	FoxCallerSavedIP := fxCallerSavedIP * BytesPerWord.
  	"In Cog a base frame's caller context is stored on the first word of the stack page."
  	FoxCallerContext := #undeclared.
  	FoxSavedFP := fxSavedFP * BytesPerWord.
  	FoxMethod := fxMethod * BytesPerWord.
  	FoxThisContext := fxThisContext * BytesPerWord.
  	FoxFrameFlags := #undeclared.
  	FoxIFrameFlags := fxIFrameFlags * BytesPerWord.
  	FoxIFSavedIP := fxIFSavedIP * BytesPerWord.
  	FoxReceiver := #undeclared.
  	FoxIFReceiver := fxIFReceiver * BytesPerWord.
  	FoxMFReceiver := fxMFReceiver * BytesPerWord.
  
  	"N.B.  There is room for one more flag given the current 8 byte alignment of methods (which
  	 is at least needed to distinguish the checked and uncecked entry points by their alignment."
  	MFMethodFlagHasContextFlag := 1.
  	MFMethodFlagIsBlockFlag := 2.
  	MFMethodFlagFrameIsMarkedFlag := 4. "for pathTo:using:followWeak:"
  	MFMethodFlagsMask := MFMethodFlagHasContextFlag + MFMethodFlagIsBlockFlag + MFMethodFlagFrameIsMarkedFlag.
  	MFMethodMask := (MFMethodFlagsMask + 1) negated!

Item was changed:
  ----- Method: CoInterpreter>>ifBackwardsCheckForEvents: (in category 'jump bytecodes') -----
  ifBackwardsCheckForEvents: offset
  	"Backward jump means we're in a loop.
  		- check for possible interrupts.
  		- check for long-running loops and JIT if appropriate."
+ 	| switched backwardJumpCountByte |
- 	| switched |
  	<inline: true>
  	offset < 0 ifTrue:
  		[localSP < stackLimit ifTrue:
  			[self externalizeIPandSP.
  			 switched := self checkForEventsMayContextSwitch: true.
  			 self returnToExecutive: true postContextSwitch: switched.
  			 self browserPluginReturnIfNeeded.
  			 self internalizeIPandSP].
+ 		 "We use the least significant byte of the flags word (which is marked as an immediate) and subtract two each time
+ 		  to avoid disturbing the least significant tag bit.  Since the byte is initialized to 1 (on frame build), on first decrement
+ 		  it will become -1.  We trip when it becomes 1 again."
+ 		 backwardJumpCountByte := stackPages byteAt: localFP + (VMBIGENDIAN ifTrue: [FoxIFrameFlags + BytesPerWord - 1] ifFalse: [FoxIFrameFlags]).
+ 		 (backwardJumpCountByte := backwardJumpCountByte - 2) <= 1 ifTrue:
+ 			[backwardJumpCountByte = -1
+ 				ifTrue: "initialize the count"
+ 					[self assert: minBackwardJumpCountForCompile <= 128.
+ 					 backwardJumpCountByte := minBackwardJumpCountForCompile - 1 << 1 + 1]
+ 				ifFalse:
- 		method = lastBackwardJumpMethod
- 			ifTrue:
- 				[(backwardJumpCount := backwardJumpCount - 1) <= 0 ifTrue:
  					[(self methodWithHeaderShouldBeCogged: (self headerOf: method))
  						ifTrue:
  							[self externalizeFPandSP.
  							 self attemptToSwitchToMachineCode: (self oopForPointer: localIP) - offset - method - BaseHeaderSize - 1]
+ 						ifFalse: "avoid asking for as long as possible"
+ 							[backwardJumpCountByte := 16rFF]]].
+ 		 stackPages
+ 			byteAt: localFP + (VMBIGENDIAN ifTrue: [FoxIFrameFlags + BytesPerWord - 1] ifFalse: [FoxIFrameFlags])
+ 			put: backwardJumpCountByte]!
- 						ifFalse: "don't ask if one should compile a second time..."
- 							[backwardJumpCount := 1 << (BytesPerWord * 8 - 2)]]]
- 			ifFalse:
- 				[lastBackwardJumpMethod := method.
- 				backwardJumpCount := minBackwardJumpCountForCompile]]!

Item was removed:
- ----- Method: CoInterpreter>>initialize (in category 'initialization') -----
- initialize
- 	super initialize.
- 	"Assign to these two to avoid them being inlined into #interpret"
- 	lastBackwardJumpMethod := backwardJumpCount := 0!

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 assert: ((coInterpreter methodHasCogMethod: aMethodObj) not
  				or: [(self noAssertMethodClassAssociationOf: aMethodObj) = objectMemory nilObject]).
  	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop).
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	self cppIf: 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].
  	extA := extB := 0.
+ 	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
- 	objectMemory ensureNoForwardedLiteralsIn: aMethodObj.
  	methodObj := 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!



More information about the Vm-dev mailing list