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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 1 15:42:32 UTC 2016


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

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

Name: VMMaker.oscog-eem.1930
Author: eem
Time: 1 September 2016, 5:40:11.487941 pm
UUID: e01f4bfc-2f0a-40e1-9491-d744cde15034
Ancestors: VMMaker.oscog-cb.1929

Implement compacting CPICs on method zone reclamation rather than freeing CPICs that have one or more freed entries.  This for more stable analysis in the Sista VM.
Make MaxCPICCases a constant (class var) rather thnan a variable.

=============== Diff against VMMaker.oscog-cb.1929 ===============

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB tempOop numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel debugBytecodePointers debugOpcodeIndices disassemblingMethod'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NeedsFixupFlag NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB tempOop numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel maxCPICCases debugBytecodePointers debugOpcodeIndices disassemblingMethod'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NeedsFixupFlag NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass'
  	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 4/6/2015 15:56' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := initializationOptions at: #Debug ifAbsent: [false].
  	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration ifNil:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
  	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [self objectMemoryClass defaultISA]) caseOf: {
  							[#X64] 		->	[BochsX64Alien].
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien].
  							[#MIPSEL]	->	[MIPSELSimulator] }.
  	CogCompilerClass := self activeCompilerClass.
  	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) reverseDo:
  		[:compilerClass| compilerClass initialize; initializeAbstractRegisters].
  	self objectMemoryClass objectRepresentationClass initializeMiscConstants.
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
+ 	"6 is a fine number for the max number of PCI entries.  8 is too large."
+ 	MaxCPICCases := 6.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was changed:
  ----- Method: Cogit>>addressOfEndOfCase:inCPIC: (in category 'in-line cacheing') -----
  addressOfEndOfCase: n inCPIC: cPIC 
  	"calculate the end of the n'th case statement - which is complicated because we have case 1 right at the top of our CPIC and then build up from the last one. Yes I know this sounds strange, but trust me - I'm an Engineer, we do things backwards all the emit"
  
  	<var: #cPIC type: #'CogMethod *'>
+ 	self assert: (n >= 1and: [n <= MaxCPICCases]).
- 	self assert: (n >= 1and: [n <= maxCPICCases]).
  	^n = 1
  		ifTrue: [cPIC asInteger + firstCPICCaseOffset]
+ 		ifFalse: [cPIC asInteger + firstCPICCaseOffset + (MaxCPICCases + 1 - n * cPICCaseSize)]!
- 		ifFalse: [cPIC asInteger + firstCPICCaseOffset + (maxCPICCases + 1 - n * cPICCaseSize)]!

Item was changed:
  ----- Method: Cogit>>cPIC:HasTarget: (in category 'in-line cacheing') -----
  cPIC: cPIC HasTarget: targetMethod
  	"Are any of the jumps from this CPIC to targetMethod?"
  	<var: #cPIC type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| pc target |
  	target := targetMethod asUnsignedInteger + cmNoCheckEntryOffset.
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	"Since this is a fast test doing simple compares we don't need to care that some
  	cases have nonsense addresses in there. Just zip on through."
  	"First jump is unconditional; subsequent ones are conditional"
  	target = (backEnd jumpLongTargetBeforeFollowingAddress: pc) ifTrue:
  		[^true].
+ 	2 to: MaxCPICCases do:
- 	2 to: maxCPICCases do:
  		[:i|
  		pc := pc + cPICCaseSize.
  		target = (backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc) ifTrue:
  			[^true]].
  	^false!

Item was added:
+ ----- Method: Cogit>>cPICCompactAndIsNowEmpty: (in category 'in-line cacheing') -----
+ cPICCompactAndIsNowEmpty: cPIC
+ 	"Scan the CPIC for target methods that have been freed and eliminate them.
+ 	 Since the first entry cannot be eliminated, answer that the PIC should be
+ 	 freed if the first entry is to a free target.  Answer if the PIC is now empty or should be freed."
+ 	<var: #cPIC type: #'CogMethod *'>
+ 	| pc entryPoint targetMethod targets tags methods used |
+ 	<var: #targetMethod	type: #'CogMethod *'>
+ 	<var: #tags			declareC: 'int tags[MaxCPICCases]'>
+ 	<var: #targets			declareC: 'sqInt targets[MaxCPICCases]'>
+ 	<var: #methods		declareC: 'sqInt methods[MaxCPICCases]'>
+ 	self cCode: [] inSmalltalk:
+ 		[tags := CArrayAccessor on: (Array new: MaxCPICCases).
+ 		 targets := CArrayAccessor on: (Array new: MaxCPICCases).
+ 		 methods := CArrayAccessor on: (Array new: MaxCPICCases)].
+ 	used := 0.
+ 	1 to: cPIC cPICNumCases do:
+ 		[:i| | valid |
+ 		 pc := self addressOfEndOfCase: i inCPIC: cPIC.
+ 		 entryPoint := i = 1
+ 						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
+ 						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
+ 		 valid := true.
+ 		 "Collect all target triples except for triples whose entry-point is a freed method"
+ 		 (cPIC containsAddress: entryPoint) ifFalse:
+ 			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 			 self assert: (targetMethod cmType = CMMethod or: [targetMethod cmType = CMFree]).
+ 			 targetMethod cmType = CMFree ifTrue:
+ 				[i = 1 ifTrue: [^true]. "cannot filter out the first entry cuz classTag is at pont of send."
+ 				 valid := false]].
+ 		 valid ifTrue:
+ 			[tags at: used put: (i > 1 ifTrue: [backEnd literal32BeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize]).
+ 			 targets at: used put: entryPoint.
+ 			 methods at: used put: (backEnd literalBeforeFollowingAddress: pc - (i = 1
+ 																				ifTrue: [backEnd jumpLongByteSize]
+ 																				ifFalse: [backEnd jumpLongConditionalByteSize + backEnd cmpC32RTempByteSize])).
+ 			 used := used + 1]].
+ 	used = cPIC cPICNumCases ifTrue:
+ 		[^false].
+ 	used = 0 ifTrue:
+ 		[^true].
+ 	cPIC cPICNumCases: used.
+ 	used = 1 ifTrue:
+ 		[pc := self addressOfEndOfCase: 2 inCPIC: cPIC.
+ 		 self rewriteCPIC: cPIC caseJumpTo: pc.
+ 		 ^false].
+ 	"the first entry cannot change..."
+ 	1 to: used - 1 do:
+ 		[:i|
+ 		 pc := self addressOfEndOfCase: i + 1 inCPIC: cPIC.
+ 		 self rewriteCPICCaseAt: pc tag: (tags at: i) objRef: (methods at: i) target: (targets at: i)].
+ 
+ 	"finally, rewrite the jump 3 instr  before firstCPICCaseOffset to jump to the beginning of this new case"
+ 	self rewriteCPIC: cPIC caseJumpTo: pc - cPICCaseSize.
+ 	^false!

Item was changed:
  ----- Method: Cogit>>ceCPICMiss:receiver: (in category 'in-line cacheing') -----
  ceCPICMiss: cPIC receiver: receiver
  	"Code entry closed PIC miss.  A send has fallen
  	 through a closed (finite) polymorphic inline cache.
  	 Either extend it or patch the send site to an open PIC.
  	 The stack looks like:
  			receiver
  			args
  	  sp=>	sender return address"
  	<var: #cPIC type: #'CogMethod *'>
  	<api>
  	| outerReturn newTargetMethodOrNil errorSelectorOrNil cacheTag result |
  	self cCode: ''
  		inSmalltalk:
  			[cPIC isInteger ifTrue:
  				[^self ceCPICMiss: (self cogMethodSurrogateAt: cPIC) receiver: receiver]].
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	outerReturn := coInterpreter stackTop.
  	self deny: (backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue. 
+ 	cPIC cPICNumCases < MaxCPICCases
- 	cPIC cPICNumCases < maxCPICCases
  		ifTrue:
  			[self lookup: cPIC selector
  				for: receiver
  				methodAndErrorSelectorInto:
  					[:method :errsel|
  					newTargetMethodOrNil := method.
  					errorSelectorOrNil := errsel]]
  		ifFalse: [newTargetMethodOrNil := errorSelectorOrNil := nil].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
+ 	(cPIC cPICNumCases >= MaxCPICCases
- 	(cPIC cPICNumCases >= maxCPICCases
  	 or: [(errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: cPIC selector
  					numArgs: cPIC cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	"Now extend the PIC with the new case."
  	self cogExtendPIC: cPIC
  		CaseNMethod: newTargetMethodOrNil
  		tag: cacheTag
  		isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  	"Jump back into the pic at its entry in case this is an MNU."
  	coInterpreter
  		executeCogPIC: cPIC
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>cogMethodDoesntLookKosher: (in category 'debugging') -----
  cogMethodDoesntLookKosher: cogMethod
  	"Check that the header fields onf a non-free method are consistent with
  	 the type. Answer 0 if it is ok, otherwise answer a code for the error."
  	<api>
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	((cogMethod blockSize bitAnd: objectMemory wordSize - 1) ~= 0
  	 or: [cogMethod blockSize < (self sizeof: CogMethod)
  	 or: [cogMethod blockSize >= 32768]]) ifTrue:
  		[^1].
  
  	cogMethod cmType = CMFree ifTrue: [^2].
  
  	cogMethod cmType = CMMethod ifTrue:
  		[(objectMemory isIntegerObject: cogMethod methodHeader) ifFalse:
  			[^11].
  		 (objectRepresentation couldBeObject: cogMethod methodObject) ifFalse:
  			[^12].
  		 (cogMethod stackCheckOffset > 0
  		 and: [cogMethod stackCheckOffset < cmNoCheckEntryOffset]) ifTrue:
  			[^13].
  		 ^0].
  
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[cogMethod blockSize ~= openPICSize ifTrue:
  			[^21].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^22].
  		
  		 "Check the nextOpenPIC link unless we're compacting"
  		 cogMethod objectHeader >= 0 ifTrue:
  			[(cogMethod methodObject ~= 0
  			 and: [cogMethod methodObject < methodZoneBase
  				   or: [cogMethod methodObject > (methodZone freeStart - openPICSize)
  				   or: [(cogMethod methodObject bitAnd: objectMemory wordSize - 1) ~= 0
  				   or: [(self cCoerceSimple: cogMethod methodObject
  							to: #'CogMethod *') cmType ~= CMOpenPIC]]]]) ifTrue:
  				[^23]].
  		 cogMethod stackCheckOffset ~= 0 ifTrue:
  			[^24].
  		 ^0].
  
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[cogMethod blockSize ~= closedPICSize ifTrue:
  			[^31].
+ 		 (cogMethod cPICNumCases between: 1 and: MaxCPICCases) ifFalse:
- 		 (cogMethod cPICNumCases between: 1 and: maxCPICCases) ifFalse:
  			[^32].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^33].
  		 cogMethod methodObject ~= 0 ifTrue:
  			[^34].
  		 ^0].
  
  	^9!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assert: self noCogMethodsMaximallyMarked.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
+ 	self compactPICsWithFreedTargets.
- 	self freePICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  	methodZone relocateMethodsPreCompaction.
  	methodZone compactCompiledCode.
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
  	backEnd stopsFrom: methodZone freeStart to: methodZone youngReferrers - 1.
  	processor
  		flushICacheFrom: methodZoneBase asUnsignedInteger
  		to: methodZone youngReferrers asUnsignedInteger!

Item was added:
+ ----- Method: Cogit>>compactPICsWithFreedTargets (in category 'compaction') -----
+ compactPICsWithFreedTargets
+ 	| cogMethod count |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
+ 	count := 0.
+ 	[cogMethod < methodZone limitZony] whileTrue:
+ 		[(cogMethod cmType = CMClosedPIC
+ 		  and: [self cPICCompactAndIsNowEmpty: cogMethod]) ifTrue:
+ 			[cogMethod cmType: CMFree].
+ 		 cogMethod := methodZone methodAfter: cogMethod.
+ 		 count := count + 1].
+ 	self assert: count = methodZone numMethods!

Item was changed:
  ----- Method: Cogit>>compileClosedPICPrototype (in category 'in-line cacheing') -----
  compileClosedPICPrototype
  	"Compile the abstract instructions for a full closed PIC, used to generate the chunk of code
  	 which is copied to form each closed PIC.  A Closed Polymorphic Inline Cache is a small jump
  	 table used to optimize sends with a limited degree of polymorphism (currently up to 6 cases).
  	 We call it closed because it deals only with a finite number of cases, as opposed to an Open PIC.
  	 When a monomorphic linked send (a send with a single case, linking direct to the checked entry
  	 point of a CogMethod) fails a class check, the Cogit attempts to create a two-entry PIC that will
  	 handle jumping to the original target for the original class and the relevant target for the new
  	 class.  This jump table will be extended on subsequent failures up to a limit (6).
  
  	 We avoid extending CPICs to Open PICs by linking the send site to an Open PIC if one already
  	 exists with the send's selector, a good policy since measurements show that sends of mega-
  	 morphic selectors usually become megamorphic at all send sites.  Hence the Open PIC list.
  
  	 A CPIC also optimizes MNUs and interpret-only methods.  Each case can load SendNumArgs with
  	 the oop of a method, or will load SendNumArgs with 0 if not.  MNUs are optimized by jumping to
  	 the mnuAbort in the CPIC, which calls code that creates the Message, thereby avoiding looking up
  	 the original message which will not be found, and either looks up doesNotUnderstand: or directly
  	 activates the method loaded into SendNumArgs, hence avoiding looking up doesNotUnderstand:.
  	 Interpret-only methods are handled by jumping to the picInterpretAbort, which enters the
  	 interpreter activating the method loaded in SendNumArgs.
  
  	 CPICs look like the following, where rClass is set at the original send site for the 1st case, and #Foo
  	 is some constant, either an oop, a class tag or an instruction address.
  
  		rTemp := (rRecever bitAnd: TagMask) = 0 ifTrue: [rReceiver class] ifFalse: [rRecever bitAnd: TagMask].
  		rTemp = rClass ifFalse:
  			[self goto: #Label].
  		rSendNumArgs := #MethodForCase1Or0.
  		self goto: #TargetForCase1.
  	 #Label
  		rTemp = #ClassTagForCase6 ifTrue:
  			[rSendNumArgs := #MethodForCase6Or0.
  			 self goto: #TargetForCase6].
  		...cases 5, 4 & 3
  		rTemp = #ClassTagForCase2 ifTrue:
  			[rSendNumArgs := #MethodForCase2Or0.
  			 self goto: #TargetForCase2].
  		self goto: #CPICMissTrampoline
  		literals (if out-of-line literals)
  
  	 where we short-cut as many cases as needed by making the self goto: #Label skip as many cases
  	 as needed."
  	<inline: true>
  	| numArgs jumpNext |
  	<var: #jumpNext type: #'AbstractInstruction *'>
  	self compilePICAbort: (numArgs := 0). "Will get rewritten to appropriate arity when configuring."
  	jumpNext := self compileCPICEntry.
  	"At the end of the entry code we need to jump to the first case code, which is actually the last chunk.
  	 On each entension we must update this jump to move back one case."
  	"16r5EAF00D is the method oop, or 0, for the 1st case."
  	self MoveUniqueCw: 16r5EAF00D R: SendNumArgsReg.
  	self JumpLong: self cPICPrototypeCaseOffset + 16rCA5E10.
  	endCPICCase0 := self Label.
+ 	1 to: MaxCPICCases - 1 do:
- 	1 to: maxCPICCases - 1 do:
  		[:h|
+ 		h = (MaxCPICCases - 1) ifTrue:
- 		h = (maxCPICCases - 1) ifTrue:
  			[jumpNext jmpTarget: self Label]. "this is where we jump to for the first case"
  		"16rBADA550+h is the method oop, or 0, for the Nth case."
  		self MoveUniqueCw: 16rBADA550 + h R: SendNumArgsReg.
  		"16rBABE1F15+h is the class tag for the Nth case"
  		self CmpC32: 16rBABE1F15+h R: TempReg.
  		self JumpLongZero: self cPICPrototypeCaseOffset + 16rCA5E10 + (h * 16).
  		h = 1 ifTrue:
  			[endCPICCase1 := self Label]].
  	self MoveCw: methodLabel address R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: numArgs).	"Will get rewritten to appropriate arity when configuring."
  	cPICEndOfCodeLabel := self Label.
  	literalsManager dumpLiterals: false.
  	^0!

Item was changed:
  ----- Method: Cogit>>disassembleMethod:on: (in category 'disassembly') -----
  disassembleMethod: surrogateOrAddress on: aStream
  	<doNotGenerate>
  	| cogMethod mapEntries codeRanges |
  	cogMethod := surrogateOrAddress isInteger
  								ifTrue: [self cogMethodSurrogateAt: surrogateOrAddress]
  								ifFalse: [surrogateOrAddress].
  	cogMethod cmType = CMBlock ifTrue:
  		[^self disassembleMethod: cogMethod cmHomeMethod on: aStream].
  	(disassemblingMethod isNil
  	 and: [self class initializationOptions at: #relativeAddressDisassembly ifAbsent: [false]]) ifTrue:
  		[^[disassemblingMethod := cogMethod.
  		    self disassembleMethod: surrogateOrAddress on: aStream] ensure:
  			[disassemblingMethod := nil]].
  	self printMethodHeader: cogMethod on: aStream.
  
  	mapEntries := Dictionary new.
  	(cogMethod cmType = CMMethod and: [cogMethod cmIsFullBlock]) ifFalse:
  		[mapEntries at: cogMethod asInteger + cmEntryOffset put: 'entry'].
  	
  	cogMethod cmType = CMMethod ifTrue:
  		[cogMethod cmIsFullBlock
  			ifTrue: [mapEntries at: cogMethod asInteger + cbNoSwitchEntryOffset put: 'noSwitchEntry']
  			ifFalse: [mapEntries at: cogMethod asInteger + cmNoCheckEntryOffset put: 'noCheckEntry']].
  
  	cogMethod cmType = CMClosedPIC
  		ifTrue:
  			[mapEntries at: cogMethod asInteger + firstCPICCaseOffset put: 'ClosedPICCase0'.
+ 			 1 to: MaxCPICCases - 1 do:
- 			 1 to: maxCPICCases - 1 do:
  				[:i|
  				mapEntries
  					at: cogMethod asInteger + firstCPICCaseOffset + (i * cPICCaseSize)
  					put: 'ClosedPICCase', i printString]]
  		ifFalse:
  			[self mapFor: cogMethod
  				performUntil: #collectMapEntry:address:into:
  				arg: mapEntries].
  
  	NewspeakVM ifTrue:
  		[objectRepresentation canPinObjects ifFalse:
  			[mapEntries keys do:
  				[:a|
  				(mapEntries at: a) = #IsNSSendCall ifTrue:
  					[mapEntries
  						at: a + backEnd jumpShortByteSize
  							put: {'Class'. #disassembleCachedOop:. (objectMemory wordSize)};
  						at: a + backEnd jumpShortByteSize + objectMemory bytesPerOop
  							put: {'ImplicitReceiver'. #disassembleCachedOop:. (objectMemory wordSize)}]]]].
  
  	"This would all be far more elegant and simple if we used blocks.
  	 But there are no blocks in C and the basic enumerators here need
  	 to be used in the real VM.  Apologies."
  	(codeRanges := self codeRangesFor: cogMethod) do:
  		[:range|
  		(cogMethod cmType = CMMethod) ifTrue:
  			[mapEntries keysAndValuesDo:
  				[:mcpc :label| | bcpc selectorOrNone |
  				((range includes: mcpc)
  				 and: [(AnnotationsWithBytecodePCs includes: label)
  				 and: [range cogMethod stackCheckOffset > 0]]) ifTrue:
  					[bcpc := self bytecodePCFor: mcpc startBcpc: range startpc in: range cogMethod.
  					 bcpc ~= 0 ifTrue:
  						[label = #IsSendCall
  							ifTrue:
  								[selectorOrNone := (self selectorForSendAt: mcpc annotation: IsSendCall in: cogMethod methodObject).
  								 (selectorOrNone isInteger and: [objectMemory addressCouldBeOop: selectorOrNone]) ifTrue:
  									[selectorOrNone := objectMemory stringOf: selectorOrNone].
  								selectorOrNone := ' ', selectorOrNone]
  							ifFalse: [selectorOrNone := ''].
  						 mapEntries
  							at: mcpc
  							put: label, selectorOrNone, ' bc ', bcpc printString, '/', (bcpc + 1) printString]]]].
  		(cogMethod blockEntryOffset ~= 0
  		 and: [range first = (cogMethod blockEntryOffset + cogMethod asInteger)])
  			ifTrue:
  				[aStream nextPutAll: 'blockEntry:'; cr.
  				 self blockDispatchFor: cogMethod
  					perform: #disassemble:from:to:arg:
  					arg: aStream]
  			ifFalse:
  				[range first > (cogMethod address + cmNoCheckEntryOffset) ifTrue:
  					[self printMethodHeader: range cogMethod
  						on: aStream].
  				self disassembleFrom: range first to: range last labels: mapEntries on: aStream]].
  	aStream nextPutAll: 'startpc: '; print: codeRanges first startpc; cr.
  	(cogMethod cmType = CMMethod
  	 or: [cogMethod cmType = CMOpenPIC]) ifTrue:
  		[[self mapFor: cogMethod
  			performUntil: #printMapEntry:mcpc:args:
  			arg: { aStream. codeRanges. cogMethod }]
  			on: AssertionFailure
  			do: [:ex|
  				ex primitiveChangeClassTo: ResumableVMError basicNew. ":) :) :)"
  				ex resume: nil]].
  	^cogMethod!

Item was changed:
  ----- Method: Cogit>>expectedClosedPICPrototype: (in category 'in-line cacheing') -----
  expectedClosedPICPrototype: cPIC
  	"Use asserts to check if the ClosedPICPrototype is as expected from compileClosedPICPrototype,
  	 and can be updated as required via rewriteCPICCaseAt:tag:objRef:target:.  If all asserts pass, answer
  	 0, otherwise answer a bit mask identifying all the errors."
  	"self disassembleFrom: methodZoneBase + (self sizeof: CogMethod) to: methodZoneBase + closedPICSize"
  	<var: #cPIC type: #'CogMethod *'>
  	| pc errors object classTag entryPoint |
  	errors := 0.
  	pc := cPIC asUnsignedInteger + firstCPICCaseOffset.
  	"First jump is unconditional; subsequent ones are conditional"
  	object := backEnd literalBeforeFollowingAddress: pc - backEnd jumpLongByteSize.
  	(self asserta: object = 16r5EAF00D) ifFalse:
  		[errors := 1].
  
  	entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
  	(self asserta: entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10)) ifFalse:
  		[errors := errors + 2].
  
+ 	1 to: MaxCPICCases - 1 do:
- 	1 to: maxCPICCases - 1 do:
  		[:i | | methodObjPC classTagPC |
  		pc := pc + cPICCaseSize.
  
  		"verify information in case is as expected."
  		methodObjPC := pc - backEnd jumpLongConditionalByteSize - backEnd cmpC32RTempByteSize.
  		object := backEnd literalBeforeFollowingAddress: methodObjPC.
  		(self asserta: object = (16rBADA550 + i)) ifFalse:
  			[errors := errors bitOr: 4].
  
  		classTagPC := pc - backEnd jumpLongConditionalByteSize.
  		classTag := backEnd literal32BeforeFollowingAddress: classTagPC.
  		(self asserta: classTag = (16rBABE1F15 + i)) ifFalse:
  			[errors := errors bitOr: 8].
  
  		entryPoint := backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc.
  		(self asserta: entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10 + (i * 16))) ifFalse:
  			[errors := errors bitOr: 16].
  
  		"change case via rewriteCPICCaseAt:tag:objRef:target:"
  		self rewriteCPICCaseAt: pc
  			tag: (classTag bitXor: 16r5A5A5A5A)
  			objRef: (object bitXor: 16rA5A5A5A5)
  			target: (entryPoint bitXor: 16r55AA50). "don't xor least 4 bits to leave instruction alignment undisturbed"
  
  		"verify information in case is as expected post update."
  		object := backEnd literalBeforeFollowingAddress: methodObjPC.
  		(self asserta: object = (16rBADA550 + i bitXor: 16rA5A5A5A5)) ifFalse:
  			[errors := errors bitOr: 32].
  		classTag := backEnd literal32BeforeFollowingAddress: classTagPC.
  		(self asserta: classTag = (16rBABE1F15 + i bitXor: 16r5A5A5A5A)) ifFalse:
  			[errors := errors bitOr: 64].
  		entryPoint := backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc.
  		(self asserta: entryPoint = ((self cPICPrototypeCaseOffset + 16rCA5E10 + (i * 16)) bitXor: 16r55AA50)) ifFalse:
  			[errors := errors bitOr: 128].
  
  		"finally restore case to the original state"
  		self rewriteCPICCaseAt: pc
  			tag: (classTag bitXor: 16r5A5A5A5A)
  			objRef: (object bitXor: 16rA5A5A5A5)
  			target: (entryPoint bitXor: 16r55AA50)].
  
  	entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc + cPICEndSize - literalsManager endSizeOffset.
  	(self asserta: entryPoint = (self cPICMissTrampolineFor: 0)) ifFalse:
  		[errors := errors + 256].
  	
  	^errors!

Item was changed:
  ----- Method: Cogit>>generateClosedPICPrototype (in category 'initialization') -----
  generateClosedPICPrototype
  	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
  	| cPIC endAddress |
  	<var: 'cPIC' type: #'CogMethod *'>
- 	maxCPICCases := 6.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
+ 	self allocateOpcodes: MaxCPICCases * 9 bytecodes: 0.
- 	self allocateOpcodes: maxCPICCases * 9 bytecodes: 0.
  	methodLabel address: methodZoneBase; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileClosedPICPrototype.
  	self computeMaximumSizes.
  	cPIC := (self cCoerceSimple: methodZoneBase to: #'CogMethod *').
  	closedPICSize := (self sizeof: CogMethod) + (self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod)).
  	endAddress := self outputInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	self assert: methodZoneBase + closedPICSize = endAddress.
  	firstCPICCaseOffset := endCPICCase0 address - methodZoneBase.
  	cPICEndOfCodeOffset := cPICEndOfCodeLabel address - methodZoneBase.
  	cPICCaseSize := endCPICCase1 address - endCPICCase0 address.
+ 	cPICEndSize := closedPICSize - (MaxCPICCases - 1 * cPICCaseSize + firstCPICCaseOffset).
- 	cPICEndSize := closedPICSize - (maxCPICCases - 1 * cPICCaseSize + firstCPICCaseOffset).
  	closedPICSize := methodZone roundUpLength: closedPICSize.
  	self assert: picInterpretAbort address = (methodLabel address + self picInterpretAbortOffset).
  	self assert: (self expectedClosedPICPrototype: cPIC) = 0.
  	
  	"tpr this is a little tiresome but after any assert checking we need to 0 out the case0 objRef rather than leaving 16r5EAF00D lying around"
  
  	backEnd storeLiteral: 0 beforeFollowingAddress: endCPICCase0 address - backEnd jumpLongByteSize.
  	
  	"update the methodZoneBase so we keep the prototype aruond for later use"
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	cPICPrototype := cPIC.
  	"self cCode: ''
  		inSmalltalk:
  			[self disassembleFrom: cPIC + (self sizeof: CogMethod) to: cPIC + closedPICSize - 1.
  			 self halt]"!



More information about the Vm-dev mailing list