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

commits at source.squeak.org commits at source.squeak.org
Sat May 16 01:05:36 UTC 2015


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

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

Name: VMMaker.oscog-eem.1307
Author: eem
Time: 15 May 2015, 5:58:56.595 pm
UUID: 4406a119-cdb6-40b3-a2ec-c1989e044870
Ancestors: VMMaker.oscog-eem.1306

Revamp icache flushing in the Cogit for ARM.
Move icache flush for generated methods/pics to
the fillIn*Header: routines.  Make sure the cache is
flushed in generateCaptureCStackPointers:.
Flush the entire PIC when extending it (dubious).

Extend the fastPrimTrace scheme to trace stack overflow,
prim failure and prim retry to help debug the
phantom stack frame bug in Cog Spur.

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

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'
+ 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimTraceLogSize ReturnToInterpreter 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 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>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	COGVM := true.
  
  	MinBackwardJumpCountForCompile := 40.
  
  	MaxNumArgs := 15.
  	PrimCallNeedsNewMethod := 1.
  	PrimCallNeedsPrimitiveFunction := 2.
  	PrimCallMayCallBack := 4.
  	PrimCallCollectsProfileSamples := 8.
  	CheckAllocationFillerAfterPrimCall := 16.
  	PrimCallDoNotJIT := 32.
  
  	ReturnToInterpreter := 1. "setjmp/longjmp code."
  
  	PrimTraceLogSize := 256. "Room for 256 selectors.  Must be 256 because we use a byte to hold the index"
  	TraceBufferSize := 256 * 3. "Room for 256 events"
  	TraceContextSwitch := self objectMemoryClass basicNew integerObjectOf: 1.
  	TraceBlockActivation := self objectMemoryClass basicNew integerObjectOf: 2.
  	TraceBlockCreation := self objectMemoryClass basicNew integerObjectOf: 3.
  	TraceIncrementalGC := self objectMemoryClass basicNew integerObjectOf: 4.
  	TraceFullGC := self objectMemoryClass basicNew integerObjectOf: 5.
  	TraceCodeCompaction := self objectMemoryClass basicNew integerObjectOf: 6.
  	TraceOwnVM := self objectMemoryClass basicNew integerObjectOf: 7.
  	TraceDisownVM := self objectMemoryClass basicNew integerObjectOf: 8.
  	TraceThreadSwitch := self objectMemoryClass basicNew integerObjectOf: 9.
  	TracePreemptDisowningThread := self objectMemoryClass basicNew integerObjectOf: 10.
  	TraceVMCallback := self objectMemoryClass basicNew integerObjectOf: 11.
  	TraceVMCallbackReturn := self objectMemoryClass basicNew integerObjectOf: 12.
  	TraceStackOverflow := self objectMemoryClass basicNew integerObjectOf: 13.
+ 	TracePrimitiveFailure := self objectMemoryClass basicNew integerObjectOf: 14.
+ 	TracePrimitiveRetry := self objectMemoryClass basicNew integerObjectOf: 15.
  
  	TraceIsFromMachineCode := 1.
  	TraceIsFromInterpreter := 2.
  	CSCallbackEnter := 3.
  	CSCallbackLeave := 4.
  	CSEnterCriticalSection := 5.
  	CSExitCriticalSection := 6.
  	CSResume := 7.
  	CSSignal := 8.
  	CSSuspend := 9.
  	CSWait := 10.
  	CSYield := 11.
  	CSCheckEvents := 12.
  	CSThreadSchedulingLoop := 13.
  	CSOwnVM := 14.
  	CSThreadBind := 15.
  	CSSwitchIfNeccessary := 16.
  
  	TraceSources := CArrayAccessor on: #('?' 'm' 'i' 'callbackEnter' 'callbackLeave' 'enterCritical' 'exitCritical' 'resume' 'signal'  'suspend' 'wait' 'yield' 'eventcheck' 'threadsched' 'ownVM' 'bindToThread' 'switchIfNecessary').
  
  	"this is simulation only"
  	RumpCStackSize := 4096!

Item was added:
+ ----- Method: CoInterpreter>>checkForAndFollowForwardedPrimitiveState (in category 'primitive support') -----
+ checkForAndFollowForwardedPrimitiveState
+ 	"Override to log"
+ 	<option: #SpurObjectMemory>
+ 	| found |
+ 	cogit recordPrimTrace ifTrue:
+ 		[self fastLogPrim: TracePrimitiveFailure].
+ 	found := super checkForAndFollowForwardedPrimitiveState.
+ 	(found and: [cogit recordPrimTrace]) ifTrue:
+ 		[self fastLogPrim: TracePrimitiveRetry].
+ 	^found!

Item was changed:
  ----- Method: CoInterpreter>>fastLogPrim: (in category 'debug support') -----
+ fastLogPrim: aSelectorOrImmediate
- fastLogPrim: aSelector
  	"Fast tracing of named primitives.  primTraceLogIndex is a byte variable.
+ 	 aSelectorOrImmediate is a selector oop or one of TraceCodeCompaction et al.
  	 primTraceLog has 256 entries.  In C the + 1 below is hence implicitly modulo 256."
  	<inline: true>
+ 	primTraceLog at: primTraceLogIndex put: aSelectorOrImmediate.
- 	primTraceLog at: primTraceLogIndex put: aSelector.
  	self primTraceLogIndex: primTraceLogIndex + 1!

Item was changed:
  ----- Method: CoInterpreter>>maybeTraceStackOverflow (in category 'debug support') -----
  maybeTraceStackOverflow
  	cogit recordOverflowTrace ifTrue:
  		[self recordTrace: TraceStackOverflow
  			thing: TraceStackOverflow
  			source: ((self isMachineCodeFrame: framePointer)
  						ifTrue: [TraceIsFromMachineCode]
+ 						ifFalse: [TraceIsFromInterpreter])].
+ 	cogit recordPrimTrace ifTrue:
+ 		[self fastLogPrim: TraceStackOverflow]!
- 						ifFalse: [TraceIsFromInterpreter])]!

Item was changed:
  ----- Method: CoInterpreter>>printPrimLogEntryAt: (in category 'debug support') -----
  printPrimLogEntryAt: i
  	<inline: false>
  	| intOrSelector |
  	intOrSelector := primTraceLog at: i.
  	(objectMemory isImmediate: intOrSelector)
  		ifTrue:
  			[intOrSelector = TraceIncrementalGC ifTrue:
  				[self print: '**IncrementalGC**'. ^nil].
  			 intOrSelector = TraceFullGC ifTrue:
  				[self print: '**FullGC**'. ^nil].
  			 intOrSelector = TraceCodeCompaction ifTrue:
  				[self print: '**CompactCode**'. ^nil].
+ 			 intOrSelector = TraceStackOverflow ifTrue:
+ 				[self print: '**StackOverflow**'. ^nil].
+ 			 intOrSelector = TracePrimitiveFailure ifTrue:
+ 				[self print: '**PrimitiveFailure**'. ^nil].
+ 			 intOrSelector = TracePrimitiveRetry ifTrue:
+ 				[self print: '**PrimitiveRetry**'. ^nil].
  			 self print: '???']
  		ifFalse:
  			[intOrSelector = 0
  				ifTrue: [self printNum: i; print: '!!!!!!']
  				ifFalse: [objectMemory safePrintStringOf: intOrSelector]]!

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  	"Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  	 its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  	 dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  	 having the MNU case for cache flushing."
   	<var: #cPIC type: #'CogMethod *'>
  	| operand target address size end |
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	coInterpreter
  		compilationBreak: cPIC selector
  		point: (objectMemory numBytesOf: cPIC selector)
  		isMNUCase: isMNUCase.
  	self allocateOpcodes: 5 bytecodes: 0.
  	self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  	"Caller patches to open pic if caseNMethod is young."
  	self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  	(isMNUCase not
  	 and: [coInterpreter methodHasCogMethod: caseNMethod])
  		ifTrue:
  			[operand := 0.
  			 target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  		ifFalse:
  			[isMNUCase ifTrue:
  				[cPIC cpicHasMNUCase: true].
  			 operand := caseNMethod.
  			 target := cPIC asInteger
  					+ (isMNUCase
  						ifTrue: [self sizeof: CogMethod]
  						ifFalse: [self interpretOffset - backEnd callInstructionByteSize])].
  	self CmpCw: caseNTag R: TempReg.
  	self MoveCw: operand R: SendNumArgsReg.
  	self JumpLongZero: target.
  	self MoveCw: cPIC asInteger R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: cPIC cmNumArgs).
  
  	self computeMaximumSizes.
  	address := self addressOfEndOfCase: cPIC cPICNumCases - 1 inCPIC: cPIC.
  	size := self generateInstructionsAt: address.
  	end := self outputInstructionsAt: address.
+ 	processor flushICacheFrom: cPIC asInteger to: cPIC asInteger + closedPICSize.
- 	processor flushICacheFrom: address to: cPIC asInteger + closedPICSize.
  	cPIC cPICNumCases: cPIC cPICNumCases + 1.
  	^0!

Item was changed:
  ----- Method: Cogit>>fillInCPICHeader:size:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic size: size numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	self assert: (objectMemory isYoung: selector) not.
  	pic cmType: CMClosedPIC.
  	pic objectHeader: 0.
  	pic blockSize: size.
  	pic methodObject: 0.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmRefersToYoung: false.
  	pic cmUsageCount: self initialClosedPICUsageCount.
  	pic cpicHasMNUCase: hasMNUCase.
  	pic cPICNumCases: numCases.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMClosedPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: pic cPICNumCases = numCases.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: size = (methodZone roundUpLength: size).
+ 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + size.
  	^pic!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #method type: #'CogMethod *'>
  	<var: #originalMethod type: #'CogMethod *'>
  	| methodHeader originalMethod |
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	methodHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: methodHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			methodHeader := originalMethod methodHeader.
  			self cppIf: NewspeakVM ifTrue:
  				[methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: method asInteger.
  			self cppIf: NewspeakVM ifTrue:
  				[method nextMethodOrIRCs: theIRCs]].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - method asInteger]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - method asInteger <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - method asInteger]
  								ifFalse: [0]).
  	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
+ 	processor flushICacheFrom: method asUnsignedInteger to: method asUnsignedInteger + size.
  	^method!

Item was changed:
  ----- Method: Cogit>>fillInOPICHeader:size:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic size: size numArgs: numArgs selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	pic cmType: CMOpenPIC.
  	pic objectHeader: 0.
  	pic blockSize: size.
  	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
  	methodZone addToOpenPICList: pic.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
  		[methodZone addToYoungReferrers: pic].
  	pic cmUsageCount: self initialOpenPICUsageCount.
  	pic cpicHasMNUCase: false.
  	pic cPICNumCases: 0.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMOpenPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: size = (methodZone roundUpLength: size).
+ 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + size.
  	^pic!

Item was changed:
  ----- Method: Cogit>>generateCaptureCStackPointers: (in category 'initialization') -----
  generateCaptureCStackPointers: captureFramePointer
  	"Generate the routine that writes the current values of the C frame and stack pointers into
  	 variables.  These are used to establish the C stack in trampolines back into the C run-time.
  
  	 This is a presumptuous quick hack for x86.  It is presumptuous for two reasons.  Firstly
  	 the system's frame and stack pointers may differ from those we use in generated code,
  	 e.g. on register-rich RISCs.  Secondly the ABI may not support a simple frameless call
  	 as written here (for example 128-bit stack alignment on Mac OS X)."
  	| startAddress |
  	<inline: false>
  	self allocateOpcodes: 32 bytecodes: 0.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	startAddress := methodZoneBase.
  	captureFramePointer ifTrue:
  		[self MoveR: FPReg Aw: self cFramePointerAddress].
  	"Capture the stack pointer prior to the call."
  	backEnd leafCallStackPointerDelta = 0
  		ifTrue: [self MoveR: SPReg Aw: self cStackPointerAddress]
  		ifFalse: [self MoveR: SPReg R: TempReg.
  				self AddCq: backEnd leafCallStackPointerDelta R: TempReg.
  				self MoveR: TempReg Aw: self cStackPointerAddress].
  	self RetN: 0.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	processor flushICacheFrom: startAddress to: methodZoneBase.
  	self recordGeneratedRunTime: 'ceCaptureCStackPointers' address: startAddress.
  	ceCaptureCStackPointers := self cCoerceSimple: startAddress to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	<returnTypeC: #'CogMethod *'>
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: headerSize negated.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: nil start: methodLabel address + cmNoCheckEntryOffset.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	totalSize > MaxMethodSize ifTrue:
  		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithNopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: selector.
  	postCompileHook notNil ifTrue:
  		[self perform: postCompileHook with: method with: primInvokeLabel.
  		 postCompileHook := nil].
- 	processor flushICacheFrom: startAddress to: startAddress + headerSize + codeSize.
  	^method!



More information about the Vm-dev mailing list