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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 21 16:25:56 UTC 2021


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

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

Name: VMMaker.oscog-eem.2990
Author: eem
Time: 21 July 2021, 9:25:46.694638 am
UUID: c6bd47ac-2c1b-4eee-a64d-85ead111bf06
Ancestors: VMMaker.oscog-eem.2989

CogARMv8Compiler: fix an offset range limitation bug with storing high number temp vars (as seen in TWindowFrame class>>constructMesh:).

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

Item was changed:
  ----- Method: CogARMv8Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Because we don't use Thumb, each ARMv8 instruction has 4 bytes. Several
  	 abstract opcodes need more than one instruction. Instructions that refer to
  	 constants and/or literals depend on literals being stored out-of-line or encoded
  	 in immediate instruction fields (i.e. we only support OutOfLineLiteralsManager.
  
  	 N.B.  The ^N forms are to get around the old bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  
  	opcode
  		caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]						-> [^0].
  		[Literal]						-> [^self literalSize].
  		[AlignmentNops]			-> [^(operands at: 0) - 4].
  		"Control"
  		[CallFull]					-> [^8].
  		[JumpFull]					-> [^8].
  		[JumpLongZero]			-> [^8].
  		[JumpLongNonZero]		-> [^8].
  		[JumpMulOverflow]			-> [^8].
  		[JumpNoMulOverflow]		-> [^8].
  		[JumpFPOrdered]			-> [^8].
  		[JumpFPUnordered]		-> [^8].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
  		[NativeRetN]				-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
  
  		"Arithmetic"
  		[AddCqR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  												ifTrue: [:ign|4] ifFalse: [8]].
  		[AddCqRR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  												ifTrue: [:ign|4] ifFalse: [8]].
  		[CmpCqR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  												ifTrue: [:ign|4] ifFalse: [8]].
  		[SubCqR]						-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  												ifTrue: [:ign|4] ifFalse: [8]].
  		[LoadEffectiveAddressMwrR]	-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  												ifTrue: [:ign|4] ifFalse: [8]].
  		[AndCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
  		[AndCqRR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
  		[OrCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
  		[OrCqRR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
  		[TstCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
  		[XorCqR]					-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|4] ifFalse:[8]].
  		[AddCwR]					-> [^8].
  		[AndCwR]					-> [^8].
  		[CmpCwR]					-> [^8].
  		[CmpC32R]					-> [^8].
  		[OrCwR]					-> [^8].
  		[SubCwR]					-> [^8].
  		[XorCwR]					-> [^8].
  		[SubRR]					-> [^(operands at: 0) = SP ifTrue: [8] ifFalse: [4]].
  		[SubRRR]					-> [^(operands at: 0) = SP ifTrue: [8] ifFalse: [4]].
  
  		"ARMv8 Specific Arithmetic"
  		[MulOverflowRRR]			-> [^12].
  		"Data Movement"						
  		[MoveAwR]				-> [^((self isAddressRelativeToVarBase: (operands at: 0))
  									    or: [cogit addressIsInCurrentCompilation: (operands at: 0)])
  										ifTrue: [(operands at: 1) ~= SP ifTrue: [4] ifFalse: [8]]
  										ifFalse: [(operands at: 1) ~= SP ifTrue: [8] ifFalse: [12]]].
  		[MoveRAw]				-> [^((self isAddressRelativeToVarBase: (operands at: 1))
  									    or: [cogit addressIsInCurrentCompilation: (operands at: 1)])
  										ifTrue: [(operands at: 0) ~= SP ifTrue: [4] ifFalse: [8]]
  										ifFalse: [(operands at: 0) ~= SP ifTrue: [8] ifFalse: [12]]].
  		[MoveAwRR]			-> [self assert: (self isAddressRelativeToVarBase: (operands at: 0)).
  									^((operands at: 1) = SP or: [(operands at: 2) = SP])
  										ifTrue: [8] ifFalse: [4]].
  		[MoveRRAw]			-> [self assert: (self isAddressRelativeToVarBase: (operands at: 2)).
  									^((operands at: 0) = SP or: [(operands at: 1) = SP])
  										ifTrue: [8] ifFalse: [4]].
+ 		[MoveAbR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveRAb]				-> [^(self isAddressRelativeToVarBase: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveMwrR]			-> [^(self isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveRMwr]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveM32rR]			-> [^(self isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveRM32r]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveM16rR]			-> [^(self isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveRM16r]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveMbrR]			-> [^(self isImm12orImm9offset: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
+ 		[MoveRMbr]			-> [^(self isImm12orImm9offset: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
- 		[MoveAbR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [8]].
- 		[MoveRAb]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
- 											ifTrue: [4]
- 											ifFalse: [8]].
- 		[MoveMwrR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveRMwr]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveM32rR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveRM32r]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveM16rR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveRM16r]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveMbrR]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|4] ifFalse:[8]].
- 		[MoveRMbr]			-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|4] ifFalse:[8]].
  		[MoveM64rRd]			-> [^(self isUnsigned12BitMultipleOf8: (operands at: 0)) ifTrue: [4] ifFalse: [8]].
  		[MoveRdM64r]			-> [^(self isUnsigned12BitMultipleOf8: (operands at: 1)) ifTrue: [4] ifFalse: [8]].
  		[PushCw]				-> [^8].
  		[PushCq]				-> [^8].
  		}
  		otherwise: [^4].
  	^0 "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveRMSr: (in category 'generate machine code - concretize') -----
  concretizeMoveRMSr: unitSizeLog2MinusOne
  	"Mwr/M32r/M16r/Mbr - memory unit whose address is a constant M away from an address in a register"
+ 	^self
+ 		emitSt: unitSizeLog2MinusOne
+ 		rn: (operands at: 2)
+ 		rt: (operands at: 0)
+ 		imm: (operands at: 1) signedIntFromLong64
+ 		shiftBy12: false
+ 
- 	machineCode
- 		at: 0
- 		put: (self st: unitSizeLog2MinusOne
- 				rn: (operands at: 2)
- 				rt: (operands at: 0)
- 				imm: (operands at: 1) signedIntFromLong64
- 				shiftBy12: false).
  	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"!
- 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>emitSt:rn:rt:imm:shiftBy12: (in category 'generate machine code - support') -----
+ emitSt: unitSizeLog2MinusOne rn: baseReg rt: sourceReg imm: offset shiftBy12: shiftBy12
+ 	"C6.2.273	STR (immediate)	C6-1239
+ 	 C6.2.274	STR (register)		C6-1242
+ 	 C6.2.275	STRB (immediate)	C6-1244"
+ 
+ 	| unitSize instrBytes |
+ 	unitSize := 1 << unitSizeLog2MinusOne.
+ 	self deny: SP = sourceReg.
+ 	self deny: baseReg = sourceReg.
+ 	"Unsigned offset, C6-1240"
+ 	(offset \\ unitSize = 0
+ 	 and: [offset / unitSize between: 0 and: 1 << 12 - 1]) ifTrue:
+ 		[machineCode
+ 			at: 0
+ 			put: unitSizeLog2MinusOne << 30
+ 				+ (2r11100100 << 22)
+ 				+ (offset << (10 - unitSizeLog2MinusOne))
+ 				+ (baseReg << 5)
+ 				+ sourceReg.
+ 		 ^4].
+ 	(offset between: -256 and: 255) ifTrue: "Unscaled signed 9-bit offset, C6-1244"
+ 		[machineCode
+ 			at: 0
+ 			put: unitSizeLog2MinusOne << 30
+ 				+ (2r111000000 << 21)
+ 				+ ((offset bitAnd: 511) << 12)
+ 				+ (baseReg << 5)
+ 				+ sourceReg.
+ 		 ^4].
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"
+ 	"cogit processor disassembleInstructionAt: 4 In: machineCode object"
+ 	instrBytes := self emitMoveCw: offset intoR: RISCTempReg at: 0.
+ 	self assert: instrBytes = 4.
+ 	machineCode
+ 		at: 1
+ 		put: unitSizeLog2MinusOne << 30
+ 			+ (2r111000001 << 21)
+ 			+ (RISCTempReg << 16)
+ 			+ (UXTX << 13)
+ 			+ (1 << 11)
+ 			+ (baseReg << 5)
+ 			+ sourceReg.
+ 	^8!

Item was added:
+ ----- Method: CogARMv8Compiler>>isImm12orImm9offset: (in category 'generate machine code - support') -----
+ isImm12orImm9offset: offset
+ 	"ARM64 load/store immediate offsets have an 11 bit unsigned amd a 9 bit signed form."
+ 	^offset >= -256 and: [offset < 4096]!

Item was added:
+ ----- Method: CogARMv8Compiler>>isInImmediateOffsetRange: (in category 'testing') -----
+ isInImmediateOffsetRange: offset
+ 	"ARM64 load/store immediates have an 11 bit unsigned amd a 9 bit signed form."
+ 	^offset >= -256 and: [offset < 4096]!

Item was changed:
  ----- Method: CogARMv8Compiler>>st:rn:rt:imm:shiftBy12: (in category 'generate machine code - support') -----
  st: unitSizeLog2MinusOne rn: baseReg rt: targetReg imm: offset shiftBy12: shiftBy12
  	"C6.2.273	STR (immediate)	C6-1239
  	 C6.2.275	STRB (immediate)	C6-1244"
  
  	| unitSize |
  	unitSize := 1 << unitSizeLog2MinusOne.
  	self deny: SP = targetReg.
  	self deny: baseReg = targetReg.
  	"Unsigned offset, C6-1240"
  	(offset \\ unitSize = 0
  	 and: [offset / unitSize between: 0 and: 1 << 12 - 1]) ifTrue:
  		[^unitSizeLog2MinusOne << 30
  		+ (2r11100100 << 22)
  		+ (offset << (10 - unitSizeLog2MinusOne))
  		+ (baseReg << 5)
  		+ targetReg].
+ 	"Unscaled signed 9-bit offset, C6-1244"
+ 	(self asserta: (offset between: -256 and: 255)) ifFalse:
+ 		[self error: 'unhandled immediate offset in store'].
- 	self assert: (offset between: -256 and: 255).
  	^unitSizeLog2MinusOne << 30
  	  + (2r111000000 << 21)
  	  + ((offset bitAnd: 511) << 12)
  	  + (baseReg << 5)
  	  + targetReg!

Item was changed:
  ----- Method: CogARMv8Compiler>>usesOutOfLineLiteral (in category 'testing') -----
  usesOutOfLineLiteral
  	"Answer if the receiver uses an out-of-line literal.  Needs only
  	 to work for the opcodes created with gen:literal:operand: et al."
  
  	opcode
  		caseOf: {
  		[CallFull]		-> [^true].
  		[JumpFull]		-> [^true].
  		"Arithmetic"
  		[AddCqR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[AddCqRR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[SubCqR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[CmpCqR]		-> [^self isPossiblyShiftableNegatableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:ign|false] ifFalse: [true]].
  		[LoadEffectiveAddressMwrR]
  						-> [^self isPossiblyShiftableImm12: (operands at: 0) signedIntFromLong64
  								ifTrue: [:shift12|false] ifFalse:[true]].
  		[AndCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[AndCqRR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[OrCqRR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[OrCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[TstCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[XorCqR]		-> [^self isImmNImmSImmREncodableBitmask: (operands at: 0) ifTrue: [:n :imms :immr|false] ifFalse:[true]].
  		[AddCwR]		-> [^true].
  		[AndCwR]		-> [^true].
  		[CmpCwR]		-> [^true].
  		[CmpC32R]		-> [^true].
  		[OrCwR]		-> [^true].
  		[SubCwR]		-> [^true].
  		[XorCwR]		-> [^true].
  		"Data Movement"						
  		[MoveCqR]		-> [self isPossiblyShiftableImm12: (operands at: 0)
  								ifTrue: [:shift12| ^false] ifFalse:[].
  							^self isImmNImmSImmREncodableBitmask: (operands at: 0)
  								ifTrue: [:n :imms :immr|false] ifFalse: [true]].
  		[MoveC32R]	-> [^true].
  		[MoveCwR]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
  		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
  		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) not].
  		[MoveAbR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
  		[MoveRAb]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) not].
+ 		[MoveMwrR]	-> [^(self isImm12orImm9offset: (operands at: 0)) not].
+ 		[MoveRMwr]	-> [^(self isImm12orImm9offset: (operands at: 1)) not].
+ 		[MoveMbrR]	-> [^(self isImm12orImm9offset: (operands at: 0)) not].
+ 		[MoveRMbr]	-> [^(self isImm12orImm9offset: (operands at: 1)) not].
+ 		[MoveM16rR]	-> [^(self isImm12orImm9offset: (operands at: 0)) not].
+ 		[MoveRM16r]	-> [^(self isImm12orImm9offset: (operands at: 1)) not].
- 		[MoveMwrR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
- 		[MoveRMwr]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
- 		[MoveMbrR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
- 		[MoveRMbr]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
- 		[MoveM16rR]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 0) ifTrue: [:shift12|false] ifFalse:[true]].
- 		[MoveRM16r]	-> [^self isPossiblyShiftableImm12orImm9: (operands at: 1) ifTrue: [:shift12|false] ifFalse:[true]].
  		[MoveRdM64r]	-> [^(self isUnsigned12BitMultipleOf8: (operands at: 1)) not].
  		[MoveM64rRd]	-> [^(self isUnsigned12BitMultipleOf8: (operands at: 0)) not].
  		[PushCw]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
  		[PushCq]		-> [^((operands at: 0) between: -256 and: 255) not].
  		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) not].
  		}
  		otherwise: [self assert: false].
  	^false "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: Cogit class>>attemptToComputeInstVarNamesFor: (in category 'in-image compilation support') -----
  attemptToComputeInstVarNamesFor: aCompiledMethod
+ 	aCompiledMethod methodClass instSize > 0 ifTrue:
- 	(aCompiledMethod methodClass instSize > 0) ifTrue:
  		[InitializationOptions
  			at: #instVarNames
+ 			put: aCompiledMethod methodClass allInstVarNames]!
- 			put: (aCompiledMethod methodClass allInstVarNames)]!

Item was changed:
  ----- Method: Cogit>>computeMaximumSizes (in category 'generate machine code') -----
  computeMaximumSizes
  	"This pass assigns maximum sizes to all abstract instructions and eliminates jump fixups.
  	 It hence assigns the maximum address an instruction will occur at which allows the next
  	 pass to conservatively size jumps."
  	<inline: false>
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	| relativeAddress |
  	literalsManager dumpLiterals: false.
  	relativeAddress := 0.
  	0 to: opcodeIndex - 1 do:
  		[:i| | abstractInstruction |
+ 		self maybeBreakGeneratingInstructionWithIndex: i.
  		abstractInstruction := self abstractInstructionAt: i.
  		abstractInstruction
  			address: relativeAddress;
  			maxSize: abstractInstruction computeMaximumSize.
  		relativeAddress := relativeAddress + abstractInstruction maxSize]!

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 maybeBreakGeneratingInstructionWithIndex: i.
  		abstractInstruction := self abstractInstructionAt: i.
  		"N.B. if you want to break in resizing, break here, note the instruction index, back up to the
  		 sender, restart, and step into computeMaximumSizes, breaking at this instruction's index."
  		self maybeBreakGeneratingFrom: absoluteAddress to: absoluteAddress + abstractInstruction maxSize.
  		abstractInstruction isPCDependent
  			ifTrue:
  				[abstractInstruction sizePCDependentInstructionAt: absoluteAddress.
  				 fixup := self fixupAtIndex: pcDependentIndex.
  				 pcDependentIndex := pcDependentIndex + 1.
  				 fixup instructionIndex: i.
  				 absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize]
  			ifFalse:
  				[absoluteAddress := abstractInstruction concretizeAt: absoluteAddress]].
  	0 to: pcDependentIndex - 1 do:
  		[:j|
  		fixup := self fixupAtIndex: j.
+ 		self maybeBreakGeneratingInstructionWithIndex: fixup instructionIndex.
  		abstractInstruction := self abstractInstructionAt: fixup instructionIndex.
  		"N.B. if you want to break in resizing, break here, note the instruction index, back up to the
  		 sender, restart, and step into computeMaximumSizes, breaking at this instruction's index."
  		self maybeBreakGeneratingFrom: abstractInstruction address to: abstractInstruction address + abstractInstruction maxSize - 1.
  		abstractInstruction concretizeAt: abstractInstruction address].
  	^absoluteAddress - eventualAbsoluteAddress!

Item was added:
+ ----- Method: Cogit>>maybeBreakGeneratingInstructionWithIndex: (in category 'simulation only') -----
+ maybeBreakGeneratingInstructionWithIndex: index
+ 	"Variation on maybeBreakAt: that only works for integer abstract instruction indexes,
+ 	 so we can have break blocks that stop at any pc, except when generating."
+ 	<cmacro: '(i) 0'> "Simulation only; void in C"
+ 	(InitializationOptions at: #instructionIndex ifAbsent: nil) ifNotNil: [:breakIndex| index = breakIndex ifTrue: [self halt]]!

Item was changed:
  ----- Method: Cogit>>outputInstructionsAt: (in category 'generate machine code') -----
  outputInstructionsAt: startAddress
  	"Store the generated machine code, answering the last address"
  	| absoluteAddress |
  	self ensureWritableCodeZone.
  	absoluteAddress := startAddress.
  	0 to: opcodeIndex - 1 do:
  		[:i| | abstractInstruction |
+ 		self maybeBreakGeneratingInstructionWithIndex: i.
  		abstractInstruction := self abstractInstructionAt: i.
  		self assert: abstractInstruction address = absoluteAddress.
  		abstractInstruction outputMachineCodeAt: absoluteAddress.
  		absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize].
+ 	^absoluteAddress
+ 
+ 	"self abstractInstructionAt: i - 1" "it's usually the preceding instruction that's at fault..."!
- 	^absoluteAddress!



More information about the Vm-dev mailing list