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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 15 01:18:54 UTC 2016


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

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

Name: VMMaker.oscog-eem.1633
Author: eem
Time: 15 January 2016, 5:17:15.513995 pm
UUID: 81214b9c-0c06-4344-9c78-7c030cb61460
Ancestors: VMMaker.oscog-eem.1632

Cogits:
Fix bug with new PIC scheme.  the opffset to the frst jump in the PIC (the jump to the next case) is at firstCPICCaseOffset - backEnd jumpLongByteSize - backEnd loadLiteralByteSize, /not/ firstCPICCaseOffset - backEnd jumpLongByteSize - backEnd loadPICLiteralByteSize.  (This affects only x64 and in-line literal ARM, hence no one's noticed yet).

Fix off-by-two error in 64-bit Spur's genPrimitiveStringAt[Put]

Simulator:
Fix brakBlock: so that setting a break block puts the VM into single step mode.  Fiux same so that this doesn't cause constant breaks in generating machine code.  Fix the usage of clickConfirm so that click step does proimpt for stopping in handleCallOrJumpSimulationTrap:, but doesn't keep prompting there-after.

Make disassembly of trampolines add a cr.

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

Item was added:
+ ----- Method: Boolean>>singleStepRequiredToTriggerIn: (in category '*VMMaker-interpreter simulator') -----
+ singleStepRequiredToTriggerIn: aCogit
+ 	^self!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveStringAt (in category 'primitive generators') -----
  genPrimitiveStringAt
  	| formatReg jumpNotIndexable jumpBadIndex done
  	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig
  	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds |
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #done type: #'AbstractInstruction *'>
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpIsWords type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
  	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
  
  	self genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jumpIsWords := cogit JumpGreaterOrEqual: 0.
  	jumpNotIndexable := cogit Jump: 0.
  
  	jumpIsBytes jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
  		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
  	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	cogit backEnd byteReadsZeroExtend ifFalse:
  			[cogit AndCq: 255 R: ReceiverResultReg].
  	done := cogit Label.
  	self genConvertIntegerToCharacterInReg: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsShorts jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg).
  		cogit AndCq: objectMemory wordSize / 2 - 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
  	cogit Jump: done.
  
  	jumpIsWords jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: ClassReg).
  		cogit AndCq: objectMemory wordSize / 4 - 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> (objectMemory shiftForWord - 1) R: Arg1Reg.
- 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveX32r: Arg1Reg R: ReceiverResultReg R: TempReg.
+ 	cogit SubCq: objectMemory baseHeaderSize >> (objectMemory shiftForWord - 1) R: Arg1Reg.
- 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	jumpWordTooBig := self jumpNotCharacterUnsignedValueInRegister: TempReg.
  	cogit MoveR: TempReg R: ReceiverResultReg.
  	cogit Jump: done.
  
  	jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsOutOfBounds jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpWordTooBig jmpTarget:
  	(jumpNotIndexable jmpTarget: 
  	(jumpBadIndex jmpTarget: cogit Label))))).
  
  	^CompletePrimitive!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveStringAtPut (in category 'primitive generators') -----
  genPrimitiveStringAtPut
  	| formatReg jumpBadIndex jumpBadArg jumpShortsDone jumpWordsDone
  	  jumpBytesOutOfRange jumpShortsOutOfRange jumpWordsOutOfRange
  	  jumpIsBytes jumpIsShorts jumpNotString jumpIsCompiledMethod jumpImmutable
  	  jumpBytesOutOfBounds jumpWordsOutOfBounds jumpShortsOutOfBounds |
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpBadArg type: #'AbstractInstruction *'>
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpShortsDone type: #'AbstractInstruction *'>
  	<var: #jumpWordsDone type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfRange type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfRange type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfRange type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
  	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
  
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	jumpBadArg := self genJumpNotCharacter: Arg1Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
  	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self cppIf: IMMUTABILITY
  		ifTrue:
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  		jumpImmutable := self genJumpBaseHeaderImmutable: TempReg ]
  		ifFalse: 
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: NoReg ].
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format; words and/or bytes.
  		  0 to 8 = pointer objects, forwarders, reserved.
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jumpNotString := cogit JumpBelowOrEqual: 0.
  					cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
  	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
  
  	cogit CmpCq: (objectMemory characterObjectOf: 1 << self numCharacterBits - 1) R: Arg1Reg.
  	jumpWordsOutOfRange := cogit JumpAbove: Arg1Reg.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: ClassReg.
  	cogit AndCq: objectMemory wordSize / 4 - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize >> (objectMemory shiftForWord - 1) R: Arg0Reg.
- 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
  	cogit MoveR: TempReg X32r: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	jumpWordsDone := cogit Jump: 0.
  
  	jumpIsShorts jmpTarget:
  		(cogit CmpCq: (objectMemory characterObjectOf: 65535) R: Arg1Reg).
  	jumpShortsOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
  	cogit AndCq: objectMemory wordSize / 2 - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddR: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	jumpShortsDone := cogit Jump: 0.
  
  	jumpIsBytes jmpTarget:
  		(cogit CmpCq: (objectMemory characterObjectOf: 255) R: Arg1Reg).
  	jumpBytesOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
  	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertCharacterToCodeInReg: TempReg.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
  	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  
  	jumpWordsDone jmpTarget:
  	(jumpShortsDone jmpTarget: cogit genPrimReturn).
  
  	jumpNotString jmpTarget:
  	(jumpBytesOutOfRange jmpTarget:
  	(jumpShortsOutOfRange jmpTarget:
  	(jumpWordsOutOfRange jmpTarget:
  	(jumpIsCompiledMethod jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsOutOfBounds jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget: cogit Label))))))).
  
  	self cppIf: IMMUTABILITY
  		ifTrue: [jumpImmutable jmpTarget: jumpNotString jumpTarget].
  
  	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
  	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
  
  	jumpBadArg jmpTarget:
  	(jumpBadIndex jmpTarget: cogit Label).
  
  	^CompletePrimitive!

Item was changed:
  ----- Method: Cogit>>breakBlock: (in category 'simulation only') -----
  breakBlock: aBlock
  	<doNotGenerate>
  	breakBlock := aBlock.
+ 	breakPC ifNil: [breakPC := true].
  	singleStep := singleStep or: [breakPC singleStepRequiredToTriggerIn: self]!

Item was changed:
  ----- Method: Cogit>>disassembleFrom:to:labels:on: (in category 'disassembly') -----
  disassembleFrom: startAddress to: endAddress labels: labelDictionary on: aStream
  	<doNotGenerate>
+ 	aStream ensureCr.
  	processor disassembleFrom: startAddress to: endAddress in: coInterpreter memory for: self labels: labelDictionary on: aStream.
  	aStream flush!

Item was changed:
  ----- Method: Cogit>>generateInstructionsAt: (in category 'generate machine code') -----
  generateInstructionsAt: eventualAbsoluteAddress
  	"Size pc-dependent instructions and assign eventual addresses to all instructions.
  	 Answer the size of the code.
  	 Compute forward branches based on virtual address (abstract code starts at 0),
  	 assuming that any branches branched over are long.
  	 Compute backward branches based on actual address.
  	 Reuse the fixups array to record the pc-dependent instructions that need to have
  	 their code generation postponed until after the others."
  	| absoluteAddress pcDependentIndex abstractInstruction fixup |
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	absoluteAddress := eventualAbsoluteAddress.
  	pcDependentIndex := 0.
  	0 to: opcodeIndex - 1 do:
  		[:i|
+ 		self cCode: [] inSmalltalk: [self maybeBreakGeneratingAt: absoluteAddress].
- 		self cCode: [] inSmalltalk: [self maybeBreakAt: absoluteAddress].
  		abstractInstruction := self abstractInstructionAt: i.
  		abstractInstruction isPCDependent
  			ifTrue:
  				[abstractInstruction sizePCDependentInstructionAt: absoluteAddress.
  				 fixup := self fixupAt: pcDependentIndex.
  				 pcDependentIndex := pcDependentIndex + 1.
  				 fixup instructionIndex: i.
  				 absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize]
  			ifFalse:
  				[absoluteAddress := abstractInstruction concretizeAt: absoluteAddress]].
  	0 to: pcDependentIndex - 1 do:
  		[:j|
  		fixup := self fixupAt: j.
  		abstractInstruction := self abstractInstructionAt: fixup instructionIndex.
+ 		self cCode: [] inSmalltalk: [self maybeBreakGeneratingAt: abstractInstruction address].
- 		self cCode: [] inSmalltalk: [self maybeBreakAt: abstractInstruction address].
  		abstractInstruction concretizeAt: abstractInstruction address].
  	^absoluteAddress - eventualAbsoluteAddress!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function result savedFramePointer savedStackPointer savedArgumentCount rpc |
  	evaluable := simulatedTrampolines at: aProcessorSimulationTrap address.
  	function := evaluable isBlock
  					ifTrue: ['aBlock; probably some plugin primitive']
  					ifFalse:
  						[evaluable receiver == backEnd ifTrue:
  							[^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  						 evaluable selector].
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[coInterpreter assertValidExternalStackPointers].
  	(function beginsWith: 'ceShort') ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
  	aProcessorSimulationTrap type = #call
  		ifTrue:
  			[processor
  				simulateCallOf: aProcessorSimulationTrap address
  				nextpc: aProcessorSimulationTrap nextpc
  				memory: coInterpreter memory.
  			self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  		ifFalse:
  			[processor
  				simulateJumpCallOf: aProcessorSimulationTrap address
  				memory: coInterpreter memory.
  			 self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  		   	   ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  			 	[(self confirm: 'skip run-time call?') ifFalse:
+ 					[clickConfirm := false. self halt]].
- 					[self halt]].
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: coInterpreter memory)]
  				on: ReenterMachineCode
  				do: [:ex| ex return: ex returnValue].
  			
  	coInterpreter assertValidExternalStackPointers.
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter checkForLastObjectOverwrite.
  		 coInterpreter primFailCode = 0
  			ifTrue: [(#(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
  						primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  						primitiveExecuteMethodArgsArray primitiveExecuteMethod
  						primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  						primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
  							includes: function) ifFalse:
  						[self assert: savedFramePointer = coInterpreter framePointer.
  						 self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  								= coInterpreter stackPointer]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
  		 rpc := processor retpcIn: coInterpreter memory.
  		 self assert: (rpc >= codeBase and: [rpc < methodZone freeStart]).
  		 processor
  			smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  			simulateReturnIn: coInterpreter memory].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
  			or: [#(nil continue continueNoReturn) includes: result]]]).
  	processor cResultRegister: (result
  							ifNil: [0]
  							ifNotNil: [result isInteger
  										ifTrue: [result]
  										ifFalse: [16rF00BA222]])
  
  	"coInterpreter cr.
  	 processor sp + 32 to: processor sp - 32 by: -4 do:
  		[:sp|
  		 sp = processor sp
  			ifTrue: [coInterpreter print: 'sp->'; tab]
  			ifFalse: [coInterpreter printHex: sp].
  		 coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was added:
+ ----- Method: Cogit>>maybeBreakGeneratingAt: (in category 'simulation only') -----
+ maybeBreakGeneratingAt: address
+ 	"Variation on maybeBreakAt: that inly forks for integer breakPCs,
+ 	 so we can have break blocks that stop at any pc, except when generating."
+ 	<doNotGenerate>
+ 	(breakPC = address
+ 	 and: [breakBlock shouldStopIfAtPC: address]) ifTrue:
+ 		[coInterpreter changed: #byteCountText.
+ 		 self halt: 'machine code generation at ', address hex, ' in ', thisContext sender selector]!

Item was changed:
  ----- Method: Cogit>>rewriteCPIC:caseJumpTo: (in category 'in-line cacheing') -----
  rewriteCPIC: cPIC caseJumpTo: target 
  	"adding a new CPIC case, or making an MNU CPIC, requires altering the jump that takes us to the first case to be used"
  	<inline: true>
+ 	backEnd rewriteCPICJumpAt: cPIC asInteger + firstCPICCaseOffset - backEnd jumpLongByteSize - backEnd loadLiteralByteSize target: target!
- 	backEnd rewriteCPICJumpAt: cPIC asInteger + firstCPICCaseOffset - backEnd jumpLongByteSize - backEnd loadPICLiteralByteSize target: target!

Item was changed:
  ----- Method: Cogit>>setClickStepBreakBlock (in category 'simulation only') -----
  setClickStepBreakBlock
  	"Set the break block to present a confirmer, breaking if true, and restoring the previous break block.
  	 If an open debugger on the receiver can be found, proceed it."
  	<doNotGenerate>
+ 	| previousBreakBlock previousBreakPC previousSingleStep previousClickConfirm |
- 	| previousBreakBlock previousBreakPC previousSingleStep |
  	(breakBlock isNil or: [breakBlock method ~~ thisContext method]) ifTrue:
  		[previousBreakBlock := breakBlock.
  		 previousBreakPC := breakPC.
  		 previousSingleStep := singleStep.
+ 		 previousClickConfirm := clickConfirm.
  		 breakBlock := [:ign|
  						(processor pc ~= previousBreakPC
  						 and: [UIManager confirm: 'step?'])
  							ifTrue: [false]
  							ifFalse: [breakBlock := previousBreakBlock.
  									breakPC := previousBreakPC.
  									singleStep := previousSingleStep.
+ 									clickConfirm := previousClickConfirm.
  									true]].
+ 		 singleStep := breakPC := clickConfirm := true].
- 		 singleStep := breakPC := true].
  	(World submorphs
  		detect:
  			[:m|
  			 m model class == Debugger
  			 and: [(m model interruptedProcess suspendedContext findContextSuchThat:
  					[:ctxt|
  					ctxt receiver == self
  					and: [ctxt selector == #simulateCogCodeAt:]]) notNil]]
  		ifNone: []) ifNotNil:
  			[:debuggerWindow|
  			 WorldState addDeferredUIMessage:
  				[debuggerWindow model proceed]]!

Item was changed:
  ----- Method: Cogit>>simulateCogCodeAt: (in category 'simulation only') -----
  simulateCogCodeAt: address "<Integer>"
  	<doNotGenerate>
  	| stackZoneBase |
  	stackZoneBase := coInterpreter stackZoneBase.
  	processor pc: address.
  	[[[singleStep
  		ifTrue:
  			[[processor sp < stackZoneBase ifTrue: [self halt].
  			  self recordProcessing.
  			  self maybeBreakAt: processor pc] value. "So that the Debugger's Over steps over all this"
  			  processor
  					singleStepIn: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd]
  		ifFalse:
  			[processor
  					runInMemory: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd].
  	   ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  	 	[(self confirm: 'continue?') ifFalse:
+ 			[clickConfirm := false. self halt]].
- 			[self halt]].
  	   true] whileTrue]
  		on: ProcessorSimulationTrap
  		do: [:ex| self handleSimulationTrap: ex].
  	 true] whileTrue!



More information about the Vm-dev mailing list