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

commits at source.squeak.org commits at source.squeak.org
Sat Feb 10 02:02:17 UTC 2018


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

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

Name: VMMaker.oscog-eem.2333
Author: eem
Time: 9 February 2018, 6:01:54.490829 pm
UUID: c1d6776d-bdb0-415a-8e2b-8251cde78de0
Ancestors: VMMaker.oscog-eem.2332

RegisterAllocatingCogit:
Fix mistakes in reconcileWith:spillOffset:onSpillOrUnspill: when merging with a volatile entry that has a register.  The current entry must morph into an SSRegister, /not/ an SSSpill, and it must answer that it has merged a register.  mergeCurrentSimStackWith: must deassign the target's reguster, /not/ current's.  And it must actually update current's spill status on (un)spill.

Fix slip in genForwardersInlinedIdenticalOrNotIf:.

Fix new case in simStackMergeCompatibleWith:.

With these changes the bootstrap gets beyond saving the image, > 18000 jitted methods, before hitting an assert fail due to a bad reguster assignment for simSelf in TransformMorph>>invalidRect:from:.  Progress!

Simulator:
Have the break selector dialog allow setting an MNU break selector.

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

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>reconcileWith:spillOffset:onSpillOrUnspill: (in category 'compile abstract instructions') -----
  reconcileWith: targetEntry spillOffset: spillOffset onSpillOrUnspill: spillOrUnspillBlock
  	"Make the state of a targetEntry, a stack entry following a non-inlined special selector
  	 send, the same as the corresponding entry (the receiver) along the inlined path.
  	 spillOffset is zero for non-spill locations (self & temps), and the offset of the spill for
  	 volatile stack entries. spillOrUnspillBlock is a block evaluated with the target's
  	 registerOrNone if the receiver and target have different spilledness.
  	 Answer if the reconciliation merged a register; merged registers must be deassigned."
  	<var: #targetEntry type: #'SimStackEntry *'>
  	<inline: true>
  	| targetReg mergedRegister |
  	spilled = targetEntry spilled ifTrue:
  		[self assert: ((self isSameEntryAs: targetEntry)
  					 or: [(targetEntry spilled not and: [targetEntry registerOrNone ~= NoReg])
  					 or: [spilled and: [type = SSConstant and: [offset = targetEntry offset]]]]).
  		 (targetReg := targetEntry registerOrNone) = NoReg ifTrue:
  			[liveRegister := NoReg.
  			 ^false].
  		 mergedRegister := false.
  		 type caseOf: {
  			[SSBaseOffset]	-> [liveRegister ~= targetReg ifTrue:
  									[cogit MoveMw: offset r: register R: targetReg.
  									 mergedRegister := true].
  								targetEntry type caseOf: {
  									[SSBaseOffset]	-> [liveRegister := targetReg.
  														(self isSameEntryAs: targetEntry) ifFalse:
  															[type := SSSpill.
  															 offset := spillOffset]].
  									[SSSpill]		-> [liveRegister := targetReg. type := SSSpill.
  														offset := spillOffset].
  									[SSConstant]	-> [liveRegister := targetReg. type := SSSpill.
  														offset := spillOffset].
  									[SSRegister]	-> [register := targetReg. type := SSRegister] }].
  			[SSSpill]		-> [cogit MoveMw: offset r: register R: targetReg.
  								liveRegister := targetReg.
  								mergedRegister := true].
  			[SSConstant]	-> [liveRegister = NoReg
  									ifTrue: [cogit genMoveConstant: constant R: targetReg]
  									ifFalse: [cogit MoveR: liveRegister R: targetReg].
  								type := SSRegister. register := targetReg. liveRegister := NoReg.
  								mergedRegister := true].
  			[SSRegister]	-> [targetReg ~= register ifTrue:
  									[cogit MoveR: register R: targetReg.
  									 register := targetReg.
  									 mergedRegister := true]] }.
  		 ^mergedRegister].
  	targetReg := targetEntry registerOrNone.
  	spillOrUnspillBlock value: targetReg.
  	(type = SSConstant
  	 and: [targetEntry type ~= SSConstant or: [targetEntry constant ~= constant]]) ifTrue:
  		[type := SSSpill. offset := spillOffset. register := FPReg].
+ 	(spilled not and: [type = SSSpill]) ifTrue:
+ 		[self assert: targetReg ~= NoReg. type := SSRegister. register := targetReg].
  	liveRegister ~= targetReg ifTrue:
+ 		[liveRegister := NoReg.
+ 		 ^true].
- 		[liveRegister := NoReg].
  	^false!

Item was changed:
  ----- Method: CogVMSimulator>>codeGeneratorToComputeAccessorDepth (in category 'primitive support') -----
  codeGeneratorToComputeAccessorDepth
+ 	^(VMMaker new
- 	^VMMaker new
  		buildCodeGeneratorForInterpreter: CoInterpreterPrimitives
  		includeAPIMethods: false
+ 		initializeClasses: false)
+ 			logger: self transcript;
+ 			yourself!
- 		initializeClasses: false!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulationWindow;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'print mc/cog head frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  		add: 'short print ext head frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int head frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'short print mc/cog head frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  		add: 'long print ext head frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int head frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'long print mc/cog head frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
  		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor pc.
  											self externalWriteBackHeadFramePointers];
  		addLine;
  		add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: cogit getCStackPointer];
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action:
  			[cogit disassembleCodeAt: (((cogit codeEntryFor: cogit processor pc) isNil
  										  and: [(cogit methodZone methodFor: cogit processor pc) = 0])
  											ifTrue: [instructionPointer]
  											ifFalse: [cogit processor pc])];
  		add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  		add: 'symbolic method...' action: [(self promptHex: 'method bytecodes') ifNotNil: [:oop| self symbolicMethod: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect.
  	self isThreadedVM ifTrue:
  		[aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  	aMenuMorph
  		addLine;
  		add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
  		add: 'print cog methods with prim...' action: [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  		add: 'print cog methods with selector...' action:
  			[|s| s := UIManager default request: 'selector'.
  			s notEmpty ifTrue:
  				[s = 'nil' ifTrue: [s := nil].
  				 cogMethodZone methodsDo:
  					[:m|
  					(s ifNil: [m selector = objectMemory nilObject]
  					 ifNotNil: [(objectMemory numBytesOf: m selector) = s size
  							and: [(self str: s
  									n: (m selector + objectMemory baseHeaderSize)
  									cmp: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  						[cogit printCogMethod: m]]]];
  		add: 'print cog methods with method...' action:
  			[(self promptHex: 'method') ifNotNil: [:methodOop|
  			 cogMethodZone methodsDo:
  				[:m|
  				m methodObject = methodOop ifTrue:
  					[cogit printCogMethod: m]]]];
  		add: 'print cog method for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodFor: pc]];
  		add: 'print cog method header for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodHeaderFor: pc]];
  		add: 'print trampoline table' target: cogit action: #printTrampolineTable;
  		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  		add: (cogit printRegisters
  				ifTrue: ['no print registers each instruction']
  				ifFalse: ['print registers each instruction'])
  			action: [cogit printRegisters: cogit printRegisters not];
  		add: (cogit printInstructions
  				ifTrue: ['no print instructions each instruction']
  				ifFalse: ['print instructions each instruction'])
  			action: [cogit printInstructions: cogit printInstructions not];
  		addLine;
  		add: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: 'click step' action: [cogit setClickStepBreakBlock];
  		add: 'set break pc', cogit breakPC menuPrompt, '...-ve to disable or remove' action: [cogit promptForBreakPC];
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
+ 		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector (MNU:foo for MNU)'.
+ 											s notEmpty ifTrue:
+ 												[(s size > 4 and: [s beginsWith: 'MNU:'])
+ 													ifTrue: [self setBreakMNUSelector: (s allButFirst: 4)]
+ 													ifFalse: [self setBreakSelector: s]]];
- 		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
- 											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: 'set break block...' action: [|s| s := UIManager default request: 'break block' initialAnswer: '[:theCogit| false]'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: 'set cogit break method...' action: [(self promptHex: 'cogit breakMethod') ifNotNil: [:bm| cogit setBreakMethod: bm]];
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

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 *'>
+ 	| selector cogMethod |
- 	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	(self exclude: aMethodObj selector: aSelectorOop) ifTrue:
  		[^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.
  					^nil]]]
  		ifFalse: [self deny: (coInterpreter methodHasCogMethod: aMethodObj)].
  	self deny: (objectMemory isOopCompiledMethod: (coInterpreter ultimateLiteralOf: aMethodObj)).
+ 	selector := aSelectorOop = objectMemory nilObject
+ 					ifTrue: [coInterpreter maybeSelectorOfMethod: aMethodObj]
+ 					ifFalse: [aSelectorOop].
+ 	"coInterpreter stringOf: selector"
- 	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
+ 		compilationBreak: selector
+ 		point: (objectMemory lengthOf: selector)
- 		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.
  	receiverTags := objectMemory receiverTagBitsForMethod: methodObj.
  	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 changed:
  ----- Method: RegisterAllocatingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  	| nextPC branchDescriptor unforwardRcvr argReg targetPC
  	  unforwardArg  rcvrReg postBranchPC retry fixup
  	  comparison
  	  needMergeToTarget needMergeToContinue |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #toContinueLabel type: #'AbstractInstruction *'>
  	<var: #toTargetLabel type: #'AbstractInstruction *'>
  	<var: #comparison type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := target ].
  
  	"If an operand is an annotable constant, it may be forwarded, so we need to store it into a 
  	register so the forwarder check can jump back to the comparison after unforwarding the constant.
  	However, if one of the operand is an unnanotable constant, does not allocate a register for it 
  	(machine code will use operations on constants) and does not generate forwarder checks."
  	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
  
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
  		rcvrNeedsReg: unforwardRcvr 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
  
  	"If not followed by a branch, resolve to true or false."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^self 
  			genIdenticalNoBranchArgIsConstant: unforwardArg not
  			rcvrIsConstant: unforwardRcvr not
  			argReg: argReg 
  			rcvrReg: rcvrReg 
  			orNotIf: orNot].
  	
  	self assert: (unforwardArg or: [unforwardRcvr]).
  	self ssPop: 2. "If we had moveAllButTop: 2 volatileSimStackEntriesToRegistersPreserving: we could avoid the extra ssPop:s"
  	self moveVolatileSimStackEntriesToRegistersPreserving:
  		(self allocatedRegisters bitOr: (argReg = NoReg
  										ifTrue: [self registerMaskFor: rcvrReg]
+ 										ifFalse:
+ 											[rcvrReg = NoReg
+ 												ifTrue: [self registerMaskFor: argReg]
+ 												ifFalse: [self registerMaskFor: rcvrReg and: argReg]])).
- 										ifFalse: [self registerMaskFor: rcvrReg and: argReg])).
  	retry := self Label.
  	self ssPop: -2.
  	self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	(self fixupAt: nextPC) notAFixup "The next instruction is dead.  we can skip it."
  		ifTrue:  [deadCode := true]
  		ifFalse: [self deny: deadCode]. "push dummy value below"
  
  	"self printSimStack; printSimStack: (self fixupAt: postBranchPC) mergeSimStack"
  	"If there are merges to be performed on the forward branches we have to execute
  	 the merge code only along the path requiring that merge, and exactly once."
  	needMergeToTarget := self mergeRequiredForJumpTo: targetPC.
  	needMergeToContinue := self mergeRequiredForJumpTo: postBranchPC.
  	orNot == branchDescriptor isBranchTrue
  		ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
  			[fixup := needMergeToContinue
  						ifTrue: [0] "jumps will fall-through to to-continue merge code"
  						ifFalse: [self ensureFixupAt: postBranchPC].
  			 comparison := self JumpZero: (needMergeToTarget
  												ifTrue: [0] "comparison will be fixed up to to-target merge code"
  												ifFalse: [self ensureFixupAt: targetPC])]
  		ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
  			[fixup := needMergeToTarget
  						ifTrue: [0] "jumps will fall-through to to-target merge code"
  						ifFalse: [self ensureFixupAt: targetPC].
  			 comparison := self JumpZero: (needMergeToContinue
  												ifTrue: [0] "comparison will be fixed up to to-continue merge code"
  												ifFalse: [self ensureFixupAt: postBranchPC])].
  
  	"The forwarders check(s) need(s) to jump back to the comparison (retry) if a forwarder is found,
  	 else jump forward either to the next forwarder check or to the postBranch or branch target (fixup).
  	 But if there is merge code along a path, the jump must be to the merge code."
  	(unforwardArg and: [unforwardRcvr]) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: retry].
  	objectRepresentation 
  		genEnsureOopInRegNotForwarded: (unforwardRcvr ifTrue: [rcvrReg] ifFalse: [argReg]) 
  		scratchReg: TempReg 
  		ifForwarder: retry
  		ifNotForwarder: fixup.
  	"If fixup is zero then the ifNotForwarder path falls through to a Label which is interpreted
  	 as either to-continue or to-target, depending on orNot == branchDescriptor isBranchTrue."
  	orNot == branchDescriptor isBranchTrue
  		ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
  			[needMergeToContinue ifTrue: "fall-through to to-continue merge code"
  				[self Jump: (self ensureFixupAt: postBranchPC)].
  			 needMergeToTarget ifTrue: "fixup comparison to to-target merge code"
  				[comparison jmpTarget: self Label.
  				 self Jump: (self ensureFixupAt: targetPC)]]
  		ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
  			[needMergeToTarget ifTrue: "fall-through to to-target merge code"
  				[self Jump: (self ensureFixupAt: targetPC)].
  			 needMergeToContinue ifTrue: "fixup comparison to to-continue merge code"
  				[comparison jmpTarget: self Label.
  				 self Jump: (self ensureFixupAt: postBranchPC)]].
  
  	deadCode ifFalse: "duplicate the merge fixup's top of stack so as to avoid a false confict."
  		[self ssPushDesc: ((self fixupAt: nextPC) mergeSimStack at: simStackPtr + 1)].
  	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith: (in category 'bytecode generator support') -----
  mergeCurrentSimStackWith: fixup
  	"At a merge point the cogit expects the stack to be in the same state as fixup's mergeSimStack.
  	 mergeSimStack is the state as of some jump forward or backward to this point.  So make
  	 simStack agree with mergeSimStack (it is, um, problematic to plant code at the jump). Values
  	 may have to be assigned to registers.  Registers may have to be swapped.
  	 Generate code to merge the current simStack with that of the target fixup, the goal being to
  	 keep as many registers live as possible."
  	"self printSimStack; printSimStack: fixup mergeSimStack"
  	"self simStackPrintString-> fixup simStackPrintString"
  	"abstractOpcodes object copyFrom: startIndex to: opcodeIndex"
  	<var: #fixup type: #'BytecodeFixup *'>
  	| currentRegisters targetRegisters mergeSimStack current target spillOffset |
  	(mergeSimStack := fixup mergeSimStack) ifNil: [^self].
  	self assert: simStackPtr = fixup simStackPtr.
  	currentRegisters := self liveRegistersFrom: 0 to: simStackPtr in: simStack.
  	targetRegisters := self liveRegistersFrom: 0 to: simStackPtr in: mergeSimStack.
  	self resolveConflicts: (currentRegisters bitAnd: targetRegisters) with: fixup mergeSimStack to: fixup simStackPtr.
  	self assert: (self conflictsResolvedBetweenSimStackAnd: mergeSimStack).
  	(self pushForMergeWith: mergeSimStack)
  		ifTrue:
  			[0 to: simStackPtr do:
  				[:i|
  				 spillOffset := i > methodOrBlockNumTemps
  									ifTrue: [self frameOffsetOfTemporary: i - 1]
  									ifFalse: [0].
  				 ((current := self simStack: simStack at: i)
  					reconcileWith: (target := self simStack: mergeSimStack at: i)
  					spillOffset: spillOffset
  					onSpillOrUnspill:
  						[:targetReg|
  						 self deny: current spilled.
  						 self assert: spillOffset ~= 0.
+ 						 current ensureSpilledAt: spillOffset from: FPReg.
+ 						 simSpillBase <= i ifTrue:
+ 							[simSpillBase := i + 1]]) ifTrue:
+ 					[| targetReg |
+ 					 (i > methodOrBlockNumTemps and: [(targetReg := target registerOrNone) ~= NoReg]) ifTrue:
+ 						[self deassignRegister: targetReg in: simStack.
+ 						 self deassignRegister: targetReg in: mergeSimStack.
+ 						 self deny: (self register: targetReg isInMask: self liveRegistersInSelfAndTemps)]]]]
- 						 current ensureSpilledAt: spillOffset from: FPReg]) ifTrue:
- 					[i > methodOrBlockNumTemps ifTrue:
- 						[self deassignRegister: current registerOrNone in: mergeSimStack.
- 						 self deassignRegister: current registerOrNone in: simStack.
- 						 self deny: (self register: current registerOrNone
- 										isInMask: self liveRegistersInSelfAndTemps)]]]]
  		ifFalse:
  			[simStackPtr to: 0 by: -1 do:
  				[:i|
  				 spillOffset := i > methodOrBlockNumTemps
  									ifTrue: [self frameOffsetOfTemporary: i - 1]
  									ifFalse: [0].
  				 ((current := self simStack: simStack at: i)
  					reconcileWith: (target := self simStack: mergeSimStack at: i)
  					spillOffset: spillOffset
  					onSpillOrUnspill:
  						[:targetReg|
  						 self assert: current spilled.
  						 self assert: spillOffset ~= 0.
  						 targetReg  ~= NoReg
  							ifTrue: [self PopR: targetReg]
  							ifFalse: [self AddCq: objectRepresentation wordSize R: SPReg].
+ 						 current spilled: false.
+ 						 simSpillBase > i ifTrue:
+ 							[simSpillBase := i]]) ifTrue:
+ 					[| targetReg |
+ 					 (i > methodOrBlockNumTemps and: [(targetReg := target registerOrNone) ~= NoReg]) ifTrue:
+ 						[self deassignRegister: targetReg in: simStack.
+ 						 self deassignRegister: targetReg in: mergeSimStack.
+ 						 self deny: (self register: targetReg isInMask: self liveRegistersInSelfAndTemps)]]]].
- 						 current type ~= SSSpill ifTrue:
- 							[current spilled: false.
- 							  simSpillBase > i ifTrue:
- 								[simSpillBase := i]]]) ifTrue:
- 					[i > methodOrBlockNumTemps ifTrue:
- 						[self deassignRegister: current registerOrNone in: mergeSimStack.
- 						 self deassignRegister: current registerOrNone in: simStack.
- 						 self deny: (self register: current registerOrNone
- 										isInMask: self liveRegistersInSelfAndTemps)]]]].
  	self updateSimSpillBase!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>simStackMergeCompatibleWith: (in category 'bytecode generator support') -----
  simStackMergeCompatibleWith: fixup
  	simStackPtr = fixup simStackPtr ifFalse:
  		[^false].
  	simStackPtr to: 0 by: -1 do:
  		[:i| | target current |
  		target := self simStack: fixup mergeSimStack at: i.
  		current := self simStack: simStack at: i.
  		(target isSameEntryAs: current) ifFalse:
  			[^current type caseOf: {
+ 				[SSBaseOffset]	-> [(current offset = (self frameOffsetOfTemporary: i - 1)
+ 									and: [current register = FPReg])
+ 										ifTrue: [true] "current has been spilled virtually"
+ 										ifFalse:
+ 											[target type caseOf: {
+ 												[SSBaseOffset]	-> [false].
+ 												[SSSpill]		-> [false].
+ 												[SSConstant]	-> [false].
+ 												[SSRegister]	-> [false] }]].
- 				[SSBaseOffset]	-> [target type caseOf: {
- 										[SSBaseOffset]	-> [false].
- 										[SSSpill]		-> [false].
- 										[SSConstant]	-> [false].
- 										[SSRegister]	-> [false] }].
  				[SSSpill]		-> [target type caseOf: {
  										[SSBaseOffset]	-> [true].
  										[SSSpill]		-> [true].
  										[SSConstant]	-> [true].
  										[SSRegister]	-> [true] }].
  				[SSConstant]	-> [target type caseOf: {
  										[SSBaseOffset]	-> [false].
  										[SSSpill]		-> [false].
  										[SSConstant]	-> [current constant = target constant].
  										[SSRegister]	-> [false] }].
  				[SSRegister]	-> [target type caseOf: {
  										[SSBaseOffset]	-> [current register = target liveRegister].
  										[SSSpill]		-> [current register = target liveRegister].
  										[SSConstant]	-> [current register = target liveRegister].
  										[SSRegister]	-> [current register = target register] }] }]].
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>codeGeneratorToComputeAccessorDepth (in category 'primitive support') -----
  codeGeneratorToComputeAccessorDepth
+ 	^(VMMaker new
- 	^VMMaker new
  		buildCodeGeneratorForInterpreter: self class primitivesClass
  		includeAPIMethods: false
+ 		initializeClasses: false)
+ 			logger: self transcript;
+ 			yourself!
- 		initializeClasses: false!

Item was changed:
  ----- Method: StackInterpreterSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulationWindow;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'long print ext frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
  		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		addLine;
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  		add: 'inspect interpreter' action: #inspect;
  		addLine;
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
+ 		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector (MNU:foo for MNU)'.
+ 											s notEmpty ifTrue:
+ 												[(s size > 4 and: [s beginsWith: 'MNU:'])
+ 													ifTrue: [self setBreakMNUSelector: (s allButFirst: 4)]
+ 													ifFalse: [self setBreakSelector: s]]];
- 		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
- 											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: 'turn valid exec ptrs assert o', (assertVEPAES ifTrue: ['ff'] ifFalse: ['n']) action: [assertVEPAES := assertVEPAES not];
  		add: 'click step' action: [self setClickStepBreakBlock];
  		add: (printSends
  				ifTrue: ['no print sends']
  				ifFalse: ['print sends'])
  			action: [self ensureDebugAtEachStepBlock.
  					printSends := printSends not];
  		"currently printReturns does nothing"
  		"add: (printReturns
  				ifTrue: ['no print returns']
  				ifFalse: ['print returns'])
  			action: [self ensureDebugAtEachStepBlock.
  					printReturns := printReturns not];"
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!



More information about the Vm-dev mailing list