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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 9 19:17:58 UTC 2020


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

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

Name: VMMaker.oscog-eem.2653
Author: eem
Time: 9 January 2020, 11:17:22.618284 am
UUID: d2865fca-938a-40b1-be84-e527d64bac7d
Ancestors: VMMaker.oscog-eem.2652

Cogit:
Use LoadEffectiveAddressMw:r:R: in place of MoveR:R:, AddCq:R: in the remaining few places.
Remove some now-inferred type declarations.

CoInterpreter: change the argument names for the validation routinre introduced for the frame in spectors, to avoid a Slang clash.

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

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetActiveContextLarge:inBlock: (in category 'initialization') -----
  genGetActiveContextLarge: isLarge inBlock: isInBlock
  	"Create a trampoline to answer the active context that will
  	 answer it if a frame is already married, and create it otherwise.
  	 Assume numArgs is in SendNumArgsReg and ClassReg is free."
  	| header slotSize jumpSingle loopHead jumpNeedScavenge continuation exit |
- 	<var: #jumpNeedScavenge type: #'AbstractInstruction *'>
- 	<var: #continuation type: #'AbstractInstruction *'>
- 	<var: #jumpSingle type: #'AbstractInstruction *'>
- 	<var: #loopHead type: #'AbstractInstruction *'>
- 	<var: #exit type: #'AbstractInstruction *'>
  	cogit
  		MoveMw: FoxMethod r: FPReg R: ClassReg;
  		TstCq: MFMethodFlagHasContextFlag R: ClassReg.
  	jumpSingle := cogit JumpZero: 0. "jump if flag bit not set"
  	cogit "since the flag bit was set, get the context in the receiver reg and return"
  		MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
  		RetN: 0.
  	jumpSingle jmpTarget: cogit Label.
  
  	"OK, it doesn't exist; instantiate and initialize it"
  	"set the hasContext flag; See CoInterpreter class>>initializeFrameIndices"
  	cogit
  		OrCq: MFMethodFlagHasContextFlag R: ClassReg;
  		MoveR: ClassReg Mw: FoxMethod r: FPReg.
  	"now get the home CogMethod into ClassReg and save for post-instantiation."
  	isInBlock caseOf: {
  	[InFullBlock]	-> [cogit SubCq: 3 R: ClassReg]. "-3 is -(hasContext+isBlock) flags"
  	[InVanillaBlock]	-> [cogit
  							SubCq: 3 R: ClassReg; "-3 is -(hasContext+isBlock) flags"
  							MoveM16: 0 r: ClassReg R: TempReg;
  							SubR: TempReg R: ClassReg].
  	[0]				-> [cogit SubCq: 1 R: ClassReg]. "-1 is hasContext flag" }.
  
  	"instantiate the context..."
  	slotSize := isLarge ifTrue: [LargeContextSlots] ifFalse: [SmallContextSlots].
  	header := objectMemory
  					headerForSlots: slotSize
  					format: objectMemory indexablePointersFormat
  					classIndex: ClassMethodContextCompactIndex.
  	self flag: #endianness.
  	cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
  	self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
  	cogit
  		LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: slotSize) r: ReceiverResultReg R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	jumpNeedScavenge := cogit JumpAboveOrEqual: 0.
  
  	"Now initialize the fields of the context.  See CoInterpreter>>marryFrame:SP:copyTemps:"
  	"sender gets frame pointer as a SmallInteger"
  	continuation :=
  	cogit MoveR: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (SenderIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"pc gets frame caller as a SmallInteger"
  	cogit MoveMw: FoxSavedFP r: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (InstructionPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the method field, freeing up ClassReg again, and frame's context field,"
  	cogit
  		MoveMw: (cogit offset: CogMethod of: #methodObject) r: ClassReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (MethodIndex * objectMemory wordSize) r: ReceiverResultReg;
  		MoveR: ReceiverResultReg Mw: FoxThisContext r: FPReg.
  
  	"Now compute stack pointer; this is stackPointer (- 1 for return pc if a CISC) - framePointer - wordSize (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
  	"TPR note - the code here is actually doing
  	context stackPointer := ((((fp - sp) / wordSize) - [3|4]) + num args) asSmallInteger"
  	cogit
  		SubR: SPReg R: FPReg R: TempReg; "TempReg := FPReg - SPReg"
  		LogicalShiftRightCq: self log2BytesPerWord R: TempReg;
  		SubCq: (cogit backEnd hasLinkRegister ifTrue: [3] ifFalse: [4]) R: TempReg;
  		AddR: SendNumArgsReg R: TempReg.
  	self genConvertIntegerToSmallIntegerInReg: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (StackPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set closureOrNil to either the stacked receiver or nil"
  	isInBlock > 0
  		ifTrue:
  			[cogit
+ 				LoadEffectiveAddressMw: 2 r: SendNumArgsReg R: TempReg; "+2 for saved fp and saved pc"
- 				MoveR: SendNumArgsReg R: TempReg;
- 				AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  				MoveXwr: TempReg R: FPReg R: TempReg]
  		ifFalse:
  			[cogit genMoveNilR: TempReg].
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (ClosureIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the receiver"
  	cogit
  		MoveMw: FoxMFReceiver r: FPReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (ReceiverIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Now copy the arguments.  This is tricky because of the shortage of registers,.  ClassReg ranges
  	 from 1 to numArgs (SendNumArgsReg), and from ReceiverIndex + 1 to ReceiverIndex + numArgs.
  	 1 to: numArgs do:
  		[:i|
  		temp := longAt(FPReg + ((SendNumArgs - i + 2) * wordSize)). +2 for saved pc and savedfp
  		longAtput(FPReg + FoxMFReceiver + (i * wordSize), temp)]"
  	"TPR note: this is a prime candidate for passing off to the backend to do at least faintly optimal code"
  	cogit MoveCq: 1 R: ClassReg.
  	loopHead := cogit CmpR: SendNumArgsReg R: ClassReg.
  	exit := cogit JumpGreater: 0.
  	cogit
  		MoveR: SendNumArgsReg R: TempReg;
  		SubR: ClassReg R: TempReg;
  		AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  		MoveXwr: TempReg R: FPReg R: TempReg;
  		AddCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) R: ClassReg; "Now convert ClassReg from frame index to context index"
  		MoveR: TempReg Xwr: ClassReg R: ReceiverResultReg;
  		SubCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) - 1 R: ClassReg; "convert back adding 1 ;-)"
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
  	"Finally nil or copy the non-argument temps.
  	 ClassReg := FPReg + FoxMFReceiver.
  	 SendNumArgsReg := SendNumArgsReg+ReceiverIndex.
  	 [ClassReg := ClassReg - wordSize.
  	  backEnd hasLinkRegister
  			ifTrue: [SPReg <= ClassReg]
  			ifFalse: [SPReg < ClassReg]] whileTrue:
  		[receiver[SendNumArgsReg] := *ClassReg.
  		 SendNumArgsReg := SendNumArgsReg + 1]]"
  	coInterpreter marryFrameCopiesTemps ifFalse:
  		[cogit MoveCq: objectMemory nilObject R: TempReg].
+ 	cogit LoadEffectiveAddressMw: FoxMFReceiver r: FPReg R: ClassReg.
- 	cogit
- 		MoveR: FPReg R: ClassReg;
- 		AddCq: FoxMFReceiver R: ClassReg.
  	cogit AddCq: ReceiverIndex + 1 + (objectMemory baseHeaderSize / objectMemory wordSize) R: SendNumArgsReg.
  	"The receiver has already been set.
  	 If on a CISC there's a retpc for the trampoline call on top of stack; if on a RISC there isn't."
  	loopHead := cogit SubCq: objectMemory wordSize R: ClassReg.
  	cogit CmpR: ClassReg R: SPReg.
+ 	exit := cogit backEnd hasLinkRegister
+ 			ifTrue: [cogit JumpAbove: 0]
+ 			ifFalse: [cogit JumpAboveOrEqual: 0].
- 	cogit backEnd hasLinkRegister
- 		ifTrue: [exit := cogit JumpAbove: 0]
- 		ifFalse: [exit := cogit JumpAboveOrEqual: 0].
  
  	coInterpreter marryFrameCopiesTemps ifTrue:
  		[cogit MoveMw: 0 r: ClassReg R: TempReg].
  	cogit
  		MoveR: TempReg Xwr: SendNumArgsReg R: ReceiverResultReg;
  		AddCq: 1 R: SendNumArgsReg;
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
  	cogit RetN: 0.
  	
  	jumpNeedScavenge jmpTarget: cogit Label.
  	cogit backEnd saveAndRestoreLinkRegAround:
  		[cogit
  			CallRT: ceScheduleScavengeTrampoline
  			registersToBeSavedMask: (cogit registerMaskFor: ReceiverResultReg and: SendNumArgsReg and: ClassReg)].
  	cogit Jump: continuation.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genAllocFloatValue:into:scratchReg:scratchReg: (in category 'compile abstract instructions') -----
  genAllocFloatValue: dpreg into: resultReg scratchReg: scratch1 scratchReg: scratch2
  	<returnTypeC: #'AbstractInstruction *'>
  	| allocSize newFloatHeaderSansHash jumpFail |
  	<var: #jumpFail type: #'AbstractInstruction *'>
  	allocSize := objectMemory baseHeaderSize + (objectMemory sizeof: #double).
  	newFloatHeaderSansHash := ((ClassFloatCompactIndex << objectMemory compactClassFieldLSB
  									bitOr: (objectMemory formatOfClass: objectMemory classFloat))
  									bitOr: allocSize)
  									 bitOr: HeaderTypeShort.
  	cogit MoveAw: objectMemory freeStartAddress R: resultReg.
+ 	cogit LoadEffectiveAddressMw: allocSize r: resultReg R: scratch1.
- 	cogit MoveR: resultReg R: scratch1.
- 	cogit AddCq: allocSize R: scratch1.
  	cogit MoveAw: objectMemory scavengeThresholdAddress R: scratch2.
  	cogit CmpR: scratch2 R: scratch1.
  	jumpFail := cogit JumpAboveOrEqual: 0.
  	cogit MoveR: resultReg R: scratch2.
  	self flag: #newObjectHash.
  	cogit AndCq: HashMaskUnshifted << objectMemory wordSize R: scratch2.
  	cogit LogicalShiftLeftCq: HashBitsOffset - objectMemory wordSize R: scratch2.
  	cogit OrCq: newFloatHeaderSansHash R: scratch2.
  	cogit MoveR: scratch2 Mw: 0 r: resultReg.
  	cogit MoveRd: dpreg M64: objectMemory baseHeaderSize r: resultReg.
  	cogit MoveR: scratch1 Aw: objectMemory freeStartAddress.
  	^jumpFail!

Item was changed:
  ----- Method: Cogit>>AddR:R:R: (in category 'abstract instructions') -----
  AddR: addendReg R: badendReg R: destReg
  	"destReg := addendReg + badendReg"
  	<inline: false>
  	<returnTypeC: #'AbstractInstruction *'>
  	| first |
- 	<var: 'first' type: #'AbstractInstruction *'>
  	backEnd hasThreeAddressArithmetic ifTrue:
  		[^self gen: AddRRR operand: addendReg operand: badendReg operand: destReg].
  	self assert: badendReg ~= destReg.
  	first := self gen: MoveRR operand: addendReg operand: destReg.
  	self gen: AddRR operand: badendReg operand: destReg.
  	^first!

Item was changed:
  ----- Method: Cogit>>AndCq:R:R: (in category 'abstract instructions') -----
  AndCq: quickConstant R: srcReg R: destReg
  	<inline: false>
  	<returnTypeC: #'AbstractInstruction *'>
  	| first |
- 	<var: 'first' type: #'AbstractInstruction *'>
  	backEnd hasThreeAddressArithmetic ifTrue:
  		[^self gen: AndCqRR quickConstant: quickConstant operand: srcReg operand: destReg].
  	srcReg = destReg ifTrue:
+ 		[^self gen: AndCqR quickConstant: quickConstant operand: destReg].
- 		[^self gen: AndCqR quickConstant: quickConstant operand: destReg.].
  	first := self gen: MoveRR operand: srcReg operand: destReg.
  	self gen: AndCqR quickConstant: quickConstant operand: destReg.
  	^first!

Item was changed:
  ----- Method: Cogit>>ArithmeticShiftRightCq:R:R: (in category 'abstract instructions') -----
  ArithmeticShiftRightCq: quickConstant R: srcReg R: destReg
  	"destReg := (signed)srcReg >> quickConstant"
  	<inline: false>
  	<returnTypeC: #'AbstractInstruction *'>
  	| first |
- 	<var: 'first' type: #'AbstractInstruction *'>
  	backEnd hasThreeAddressArithmetic ifTrue:
  		[^self gen: ArithmeticShiftRightCqRR operand: quickConstant operand: srcReg operand: destReg].
  	first := self gen: MoveRR operand: srcReg operand: destReg.
  	self gen: ArithmeticShiftRightCqR operand: quickConstant operand: destReg.
  	^first!

Item was changed:
  ----- Method: Cogit>>LogicalShiftLeftCq:R:R: (in category 'abstract instructions') -----
  LogicalShiftLeftCq: quickConstant R: srcReg R: destReg
  	"destReg := srcReg << quickConstant"
  	<inline: false>
  	<returnTypeC: #'AbstractInstruction *'>
  	| first |
- 	<var: 'first' type: #'AbstractInstruction *'>
  	backEnd hasThreeAddressArithmetic ifTrue:
  		[^self gen: LogicalShiftLeftCqRR operand: quickConstant operand: srcReg operand: destReg].
  	first := self gen: MoveRR operand: srcReg operand: destReg.
  	self gen: LogicalShiftLeftCqR operand: quickConstant operand: destReg.
  	^first!

Item was changed:
  ----- Method: Cogit>>LogicalShiftRightCq:R:R: (in category 'abstract instructions') -----
  LogicalShiftRightCq: quickConstant R: srcReg R: destReg
  	"destReg := (unsigned)srcReg >> quickConstant"
  	<inline: false>
  	<returnTypeC: #'AbstractInstruction *'>
  	| first |
- 	<var: 'first' type: #'AbstractInstruction *'>
  	backEnd hasThreeAddressArithmetic ifTrue:
  		[^self gen: LogicalShiftRightCqRR operand: quickConstant operand: srcReg operand: destReg].
  	first := self gen: MoveRR operand: srcReg operand: destReg.
  	self gen: LogicalShiftRightCqR operand: quickConstant operand: destReg.
  	^first!

Item was changed:
  ----- Method: Cogit>>SubR:R:R: (in category 'abstract instructions') -----
  SubR: subReg R: fromReg R: destReg
  	"destReg := fromReg - subReg"
  	<inline: false>
  	<returnTypeC: #'AbstractInstruction *'>
  	| first |
- 	<var: 'first' type: #'AbstractInstruction *'>
  	backEnd hasThreeAddressArithmetic ifTrue:
  		[^self gen: SubRRR operand: subReg operand: fromReg operand: destReg].
  	self assert: subReg ~= destReg.
  	first := self gen: MoveRR operand: fromReg operand: destReg.
  	self gen: SubRR operand: subReg operand: destReg.
  	^first!

Item was changed:
  ----- Method: Cogit>>ZeroExtend16R:R: (in category 'abstract instructions') -----
  ZeroExtend16R: reg1 R: reg2
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
+ 	backEnd canZeroExtend ifFalse:
+ 		[| first |
+ 		 reg1 = reg2
+ 			ifTrue:
+ 				[first := self LogicalShiftLeftCq: BytesPerWord * 8 - 16 R: reg1]
+ 			ifFalse:
+ 				[first := self MoveR: reg1 R: reg2.
+ 				 self LogicalShiftLeftCq: BytesPerWord * 8 - 16 R: reg1].
+ 		self LogicalShiftRightCq: BytesPerWord * 8 - 16 R: reg2.
+ 		^first].
+ 	^self gen: ZeroExtend16RR operand: reg1 operand: reg2!
- 	backEnd canZeroExtend
- 		ifTrue: [^self gen: ZeroExtend16RR operand: reg1 operand: reg2]
- 		ifFalse:
- 			[| first |
- 			 reg1 = reg2
- 				ifTrue:
- 					[first := self LogicalShiftLeftCq: BytesPerWord * 8 - 16 R: reg1]
- 				ifFalse:
- 					[first := self MoveR: reg1 R: reg2.
- 					 self LogicalShiftLeftCq: BytesPerWord * 8 - 16 R: reg1].
- 			self LogicalShiftRightCq: BytesPerWord * 8 - 16 R: reg2.
- 			^first]!

Item was changed:
  ----- Method: Cogit>>ZeroExtend32R:R: (in category 'abstract instructions') -----
  ZeroExtend32R: reg1 R: reg2
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
+ 	backEnd canZeroExtend ifFalse:
+ 		[| first |
+ 		 reg1 = reg2
+ 			ifTrue:
+ 				[first := self LogicalShiftLeftCq: 32 R: reg1]
+ 			ifFalse:
+ 				[first := self MoveR: reg1 R: reg2.
+ 				 self LogicalShiftLeftCq: 32 R: reg1].
+ 		self LogicalShiftRightCq: 32 R: reg2.
+ 		^first].
+ 	^self gen: ZeroExtend32RR operand: reg1 operand: reg2!
- 	backEnd canZeroExtend
- 		ifTrue: [^self gen: ZeroExtend32RR operand: reg1 operand: reg2]
- 		ifFalse:
- 			[| first |
- 			 reg1 = reg2
- 				ifTrue:
- 					[first := self LogicalShiftLeftCq: 32 R: reg1]
- 				ifFalse:
- 					[first := self MoveR: reg1 R: reg2.
- 					 self LogicalShiftLeftCq: 32 R: reg1].
- 			self LogicalShiftRightCq: 32 R: reg2.
- 			^first]!

Item was changed:
  ----- Method: Cogit>>ZeroExtend8R:R: (in category 'abstract instructions') -----
  ZeroExtend8R: reg1 R: reg2
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
+ 	backEnd canZeroExtend ifFalse:
+ 		[| first |
+ 		 reg1 = reg2
+ 			ifTrue:
+ 				[first := self LogicalShiftLeftCq: BytesPerWord * 8 - 8 R: reg1]
+ 			ifFalse:
+ 				[first := self MoveR: reg1 R: reg2.
+ 				 self LogicalShiftLeftCq: BytesPerWord * 8 - 8 R: reg1].
+ 		self LogicalShiftRightCq: BytesPerWord * 8 - 8 R: reg2.
+ 		^first].
+ 	^self gen: ZeroExtend8RR operand: reg1 operand: reg2!
- 	backEnd canZeroExtend
- 		ifTrue: [^self gen: ZeroExtend8RR operand: reg1 operand: reg2]
- 		ifFalse:
- 			[| first |
- 			 reg1 = reg2
- 				ifTrue:
- 					[first := self LogicalShiftLeftCq: BytesPerWord * 8 - 8 R: reg1]
- 				ifFalse:
- 					[first := self MoveR: reg1 R: reg2.
- 					 self LogicalShiftLeftCq: BytesPerWord * 8 - 8 R: reg1].
- 			self LogicalShiftRightCq: BytesPerWord * 8 - 8 R: reg2.
- 			^first]!

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

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genFastPrimTraceUsing:and: (in category 'primitive generators') -----
  genFastPrimTraceUsing: r1 and: r2
  	"Suport for compileInterpreterPrimitive.  Generate inline code so as to record the primitive
  	 trace as fast as possible."
  	backEnd byteReadsZeroExtend ifFalse:
  		[self MoveCq: 0 R: r2].
  	self MoveAb: coInterpreter primTraceLogIndexAddress R: r2.
+ 	self LoadEffectiveAddressMw: 1 r: r2 R: r1.
- 	self MoveR: r2 R: r1.
- 	self AddCq: 1 R: r1.
  	self MoveR: r1 Ab: coInterpreter primTraceLogIndexAddress.
  	methodLabel addDependent:
  		(self annotateAbsolutePCRef:
  			(self MoveCw: methodLabel asInteger R: r1)).
  	self MoveMw: (self offset: CogMethod of: #selector) r: r1 R: TempReg.
  	self MoveCw: coInterpreter primTraceLogAddress asInteger R: r1.
  	self MoveR: TempReg Xwr: r2 R: r1!



More information about the Vm-dev mailing list