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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 9 00:26:11 UTC 2019


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

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

Name: VMMaker.oscog-eem.2607
Author: eem
Time: 8 December 2019, 4:26:01.580137 pm
UUID: c6efe702-f41d-497f-bfac-9bd2a62f2e98
Ancestors: VMMaker.oscog-eem.2606

Cogit:
Apply long desired refactoring such that the concretize operations and dispatchConcretize answer the size of the machine code generasted, instead of assigning m achineCodeSize in every concretize operastion and answering it.  Then assihgn machineCodeSize in only a handfiul of places.  This is both to generate better C code (should be more compact and slightly faster), and for neatness/comprehensibility.

Simulator: Fix a slip in setting options in a VMMaker; we must assign InitializationOptions on setting optionsDictionary to eliminate any stale/bogus options from any previous erroneous invocation.

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

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAddRdRd (in category 'generate machine code - concretize') -----
  concretizeAddRdRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"Add FP regRHS to FP regLHS and stick result in FP regLHS"
  	| regLHS regRHS |
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode at: 0 put:(self faddd: regLHS with: regRHS).
+ 	^4
- 	^machineCodeSize := 4
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAlignmentNops (in category 'generate machine code - concretize') -----
  concretizeAlignmentNops
  	<inline: true>
  	"fill any slots with NOPs - in this case mov  r0, r0 - which is the NOP I always used to use"
  	self assert: machineCodeSize \\ 4 = 0.
  	0 to: machineCodeSize - 1 by: 4 do:
+ 		[:p| self machineCodeAt: p put: 16rE1A00000].
+ 	^machineCodeSize!
- 		[:p| self machineCodeAt: p put: 16rE1A00000]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAndCqRR (in category 'generate machine code - concretize') -----
  concretizeAndCqRR
  	"Will get inlined into concretizeAt: switch."
  	"AND is very important since it's used to mask all sorts of flags in the jit. We take special care to try to find compact ways to make the masks"
  	<inline: true>
  	| val srcReg dstReg |
  	val := operands at: 0.
  	srcReg := operands at: 1.
  	dstReg := operands at: 2.
+ 	^self rotateable8bitBitwiseImmediate: val
- 	self rotateable8bitBitwiseImmediate: val
  		ifTrue:
  			[:rot :immediate :invert|
  			self machineCodeAt: 0 put: (invert
  											ifTrue: [self bics: dstReg rn: srcReg imm: immediate ror: rot]
  											ifFalse: [self ands: dstReg rn: srcReg imm: immediate ror: rot]).
+ 			4]
+ 		ifFalse:
- 			^machineCodeSize := 4]
- 		ifFalse: "let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
  			[| hb |
  			hb := (operands at: 0) highBit.
+ 			"First see if the constant can be made from a simple shift of 0xFFFFFFFF"
+ 			1 << hb = (val +1) ifTrue: "MVN temp reg, 0, making 0xffffffff"
+ 				[self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
+ 				"Then AND reg, temp reg, lsr #(32-hb)"
+ 				 self machineCodeAt: 4 put: (self dataOpType: AndOpcode rd: dstReg rn: srcReg rm: ConcreteIPReg lsr: 32 - hb).
+ 				^8].
+ 			self concretizeDataOperationCwR: AndOpcode]!
- 			1 << hb = (val +1)
- 				ifTrue: "MVN temp reg, 0, making 0xffffffff"
- 					[self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
- 					"Then AND reg, temp reg, lsr #(32-hb)"
- 					 self machineCodeAt: 4 put: (self dataOpType: AndOpcode rd: dstReg rn: srcReg rm: ConcreteIPReg lsr: 32 - hb).
- 					^machineCodeSize := 8]
- 				ifFalse:
- 					[^self concretizeDataOperationCwR: AndOpcode]].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeArithmeticShiftRightCqR (in category 'generate machine code - concretize') -----
  concretizeArithmeticShiftRightCqR
  	"Will get inlined into concretizeAt: switch."
  	"this is an unfortunate waste of an instruction in most cases since the shift can usually be done in a subsequent arithmetic instruction. 
  	Handle for now with a MOVS reg, reg, ASR #distance"
  	<inline: true>
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	"cond 000 1101 0 0000 dest dist -100 srcR"
  	self machineCodeAt: 0 put: (self type: 0 op: MoveOpcode set: 1 rn: 0 rd: reg 
  									shifterOperand: (distance << 7 bitOr: (64 "flag for arithmetic" bitOr: reg))).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeArithmeticShiftRightRR (in category 'generate machine code - concretize') -----
  concretizeArithmeticShiftRightRR
  	"Will get inlined into concretizeAt: switch."
  	"this is an unfortunate waste of an instruction in most cases since the shift can usually be done in a subsequent arithmetic instruction. 
  	Handle for now with a MOVS reg, reg, ASR distReg"
  	<inline: true>
  	| destReg distReg |
  	distReg := operands at: 0.
  	destReg := operands at: 1.
  	"cond 000 1101 0 0000 destR distR 0101 srcR"
  	self machineCodeAt: 0 put: (self type: 0 op: MoveOpcode set: 1 rn: 0 rd: destReg 
  									shifterOperand: (distReg << 8 bitOr: (80 bitOr: destReg))).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeCMPSMULL (in category 'generate machine code - concretize') -----
  concretizeCMPSMULL
  	"Generate a CMP a, b, ASR #31 instruction, specifically for comparing the resutls of SMULLs in genMulR:R:"
  	| hiReg loReg |
  	hiReg := operands at: 0.
  	loReg := operands at: 1.
  	self machineCodeAt: 0
  		put: (self type: 0 op: CmpOpcode set: 1 rn: hiReg rd: 0)
  			+ (31<<7) "the shift amount"
  			+ (2<<5) "the shift type - ASR"
  			+ loReg.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeCall (in category 'generate machine code - concretize') -----
  concretizeCall
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"Call is used only for calls within code-space, See CallFull for general anywhere in address space calling"
  	| offset |
  	self assert: (operands at: 0) ~= 0.
  	self assert: (operands at: 0) \\ 4 = 0.
  	offset := (operands at: 0) signedIntFromLong - (address + 8 "normal pc offset") signedIntFromLong.
  	self assert: (self isInImmediateJumpRange: offset). "+- 24Mb is plenty of range in code space"
  	self machineCodeAt: 0 put: (self bl: offset).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeCallFull (in category 'generate machine code - concretize') -----
  concretizeCallFull
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating calls.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| jumpTarget instrOffset|
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := self longJumpTargetAddress.
  	instrOffset := self moveCw: jumpTarget intoR: ConcreteIPReg.
  	"blx ConcreteIPReg"
  	self machineCodeAt: instrOffset put: (self blx: ConcreteIPReg).
  	self assert: instrOffset = self literalLoadInstructionBytes.
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeClzRR (in category 'generate machine code - concretize') -----
  concretizeClzRR
  	"Count leading zeros
  	First operand is output (dest)
  	Second operand is input (mask)"
  	"v5 CLZ cond 0001 0110 SBO Rd SBO 0001 Rm
  	That is hexa 16rE16FxF1x for cond = AL"
  	"v7 CLZ 11111-010-1-011 Rm(4bits) 1111 Rd(4bits) 1000 Rm(4bits)
  	That is hexa 16rFABxFx8x"
  	<inline: true>
  	| dest mask |
  	dest := operands at: 0.
  	mask := operands at: 1.
  	self machineCodeAt: 0 put:
  		AL << 28 + 16r16F0F10
  		+ (dest << 12) + mask.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeCmpRdRd (in category 'generate machine code - concretize') -----
  concretizeCmpRdRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"Compare FP regB with FP regA and leave the FP status reg ready to be transferred back to ARM with next instruction"
  	| regB regA |
  	regA := operands at:0.
  	regB := operands at: 1.
  	machineCode at: 0 put:(self fcmpFrom: regB to: regA).
+ 	^4
- 	^machineCodeSize := 4
  		
  !

Item was changed:
  ----- Method: CogARMCompiler>>concretizeConditionalInstruction (in category 'generate machine code') -----
  concretizeConditionalInstruction
  	"Concretize the current instruction, but with a condition."
- 	<returnTypeC: #void>
  	| savedCond |
  	self assert: conditionOrNil notNil.
  	savedCond := conditionOrNil.
  	conditionOrNil := nil.
+ 	machineCodeSize := self dispatchConcretize.
- 	self dispatchConcretize.
  	conditionOrNil := savedCond.
  	0 to: machineCodeSize-1 by: 4 do:
  		[:i| | instr |
  		instr := (self machineCodeAt: i) bitClear: 16rF<<28.
+ 		self machineCodeAt: i put: (instr bitOr: (conditionOrNil bitAnd: 16rF)<<28)].
+ 	^machineCodeSize!
- 		self machineCodeAt: i put: (instr bitOr: (conditionOrNil bitAnd: 16rF)<<28)]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeConditionalJump: (in category 'generate machine code - concretize') -----
  concretizeConditionalJump: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| offset |
  	offset := self computeJumpTargetOffsetPlus: 8.
   	self assert: (self isInImmediateJumpRange: offset).
  	self machineCodeAt: 0 put: (self cond: conditionCode br: 0 offset: offset). "B offset"
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeConvertRRd (in category 'generate machine code - concretize') -----
  concretizeConvertRRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at:0.
  	destReg := operands at: 1.
  	machineCode at: 0 put:(self fmsrFrom: srcReg to: 9).
  	machineCode at: 1 put: (self fsitodFrom: 9 to: destReg). "probably not quite right"
+ 	^8
- 	^machineCodeSize := 8
  		
  !

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationCqR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationCqR: armOpcode
  	"Will get inlined into concretizeAt: switch."
  	"4 == Add, 2 == Sub, Xor == 1, And == 0, Or == 12, Bic == 14"
  	<inline: true>
  	|val rd rn |
  	val := operands at: 0.
  	rn := operands at: 1.
  	rd := opcode = CmpOpcode ifTrue: [0] ifFalse:[rn]. "Extra note - if ever a version of this code wants to NOT set the Set flag - Cmp must always have it set or it will pretend to be a SMALALBT and Very Bad Things might happen"
  
  	self  rotateable8bitImmediate: val 
  		ifTrue: [:rot :immediate |
+ 			self machineCodeAt: 0 put: (self type: 1 op: armOpcode set: 1 rn: rn rd: rd shifterOperand: (rot>>1"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
+ 			^4]
+ 		ifFalse: [].
+ 	"first see if the constant can be made from a simple shift of 0xFFFFFFFF"
+ 	val > 0 ifTrue:
+ 		[| hb |
+ 		hb := val highBit.
+ 		1 << hb = (val +1) ifTrue: "MVN temp,  #0, making 0xffffffff"
+ 			[self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
+ 			 "Then armOpcode reg, temp reg, lsr #(32-hb)"
+ 			 self machineCodeAt: 4 put:(self dataOpType: armOpcode rd: rd  rn: rn rm: ConcreteIPReg lsr: (32-hb)).
+ 			 ^8]].
+ 	^self concretizeDataOperationCwR: armOpcode!
- 			self machineCodeAt: 0 put: (self type: 1 op: armOpcode set: 1 rn: rn rd: rd shifterOperand: ((rot>>1)"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
- 			^machineCodeSize := 4]
- 		ifFalse: ["let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
- 				val > 0 ifTrue: [
- 					|hb |
- 					hb := val highBit.
- 					1 << hb = (val +1)
- 						ifTrue: [ "MVN temp,  #0, making 0xffffffff"
- 							self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
- 							"Then armOpcode reg, temp reg, lsr #(32-hb)"
- 							 self machineCodeAt: 4 put:(self dataOpType: armOpcode rd: rd  rn: rn rm: ConcreteIPReg lsr: (32-hb)).
- 							^machineCodeSize :=8]].
- 					^self concretizeDataOperationCwR: armOpcode].
- 	^0 "to keep Slang happy"
- 	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationCwR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationCwR: armOpcode
  	"Will get inlined into concretizeAt: switch."
  	"Load the word into the RISCTempReg, then cmp R, RISCTempReg"
  	<inline: true>
  	| constant rn rd instrOffset|
  	constant := operands at: 0.
  	rn := operands at: 1.
  	rd := armOpcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
  	instrOffset := self moveCw: constant intoR: ConcreteIPReg.
  	self machineCodeAt: instrOffset 
  		put: (self type: 0 op: armOpcode set: 1 rn: rn rd: rd shifterOperand: ConcreteIPReg).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationRR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationRR: armOpcode
  	"Will get inlined into concretizeAt: switch."
  	"Load the word into the RISCTempReg, then op R, RISCTempReg"
  	<inline: true>
  	| rn rd srcReg |
  	srcReg := operands at: 0.
  	rn := operands at: 1.
  	rd := armOpcode = CmpOpcode ifTrue: [0] ifFalse: [rn].
  	self machineCodeAt: 0 
  		put: (self type: 0 op: armOpcode set: 1 rn: rn rd: rd shifterOperand: srcReg).
+ 	^4.!
- 	^machineCodeSize := 4.!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDivRdRd (in category 'generate machine code - concretize') -----
  concretizeDivRdRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"FP divide regLHS by regRHS and stick result in regLHS"
  	| regLHS regRHS |
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode at: 0 put:(self fdivd: regLHS by: regRHS).
+ 	^4
- 	^machineCodeSize := 4
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeFPConditionalJump: (in category 'generate machine code - concretize') -----
  concretizeFPConditionalJump: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset |
  	"transfer the FP status to ARM cpsr and then jump accordingly"
  	offset := self computeJumpTargetOffsetPlus: 8+4 "pc is always 2 instr ahead plus add another to refer to the actual branch".
   	self assert: (self isInImmediateJumpRange: offset).
  	self machineCodeAt: 0 put: self fmstat. "FMSTAT: copy the FPSCR to CPSR"
  	self machineCodeAt: 4 put: (self cond: conditionCode br: 0 offset: offset). "B offset"
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeFill32 (in category 'generate machine code') -----
  concretizeFill32
  	"fill with operand 0 according to the processor's endianness"
  	self machineCodeAt: 0 put: (operands at: 0).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeInvertibleDataOperationCqR: (in category 'generate machine code - concretize') -----
  concretizeInvertibleDataOperationCqR: armOpcode
  	"Will get inlined into concretizeAt: switch."
  	"Xor == 1, And == 0, Or == 12, Bic == 14"
  	<inline: true>
  	| val rn |
  	val := operands at: 0.
  	rn := operands at: 1.
  	self deny: opcode = CmpOpcode.
  
  	self rotateable8bitBitwiseImmediate: val 
  		ifTrue:
  			[:rot :immediate : invert|
  			self machineCodeAt: 0
  				put: (self
  						type: 1
  						op: (invert ifTrue: [self inverseOpcodeFor: armOpcode] ifFalse: [armOpcode])
  						set: 1
  						rn: rn
  						rd: rn
  						shifterOperand: (rot >> 1"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
+ 			^4]
+ 		ifFalse: [].
+ 	"first see if the constant can be made from a simple shift of 0xFFFFFFFF"
+ 	val > 0 ifTrue:
+ 		[| hb |
+ 		hb := val highBit.
+ 		1 << hb = (val +1) ifTrue: "MVN temp,  #0, making 0xffffffff"
+ 			[self machineCodeAt: 0 put: (self mvn: ConcreteIPReg imm: 0 ror: 0).
+ 			 "Then armOpcode reg, temp reg, lsr #(32-hb)"
+ 			 self machineCodeAt: 4 put: (self dataOpType: armOpcode rd: rn  rn: rn rm: ConcreteIPReg lsr: 32 - hb).
+ 			^8]].
+ 	 ^self concretizeDataOperationCqR: armOpcode!
- 			^machineCodeSize := 4]
- 		ifFalse: "let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
- 			[val > 0 ifTrue:
- 				[| hb |
- 				hb := val highBit.
- 				1 << hb = (val +1) ifTrue: "MVN temp,  #0, making 0xffffffff"
- 					[self machineCodeAt: 0 put: (self mvn: ConcreteIPReg imm: 0 ror: 0).
- 					 "Then armOpcode reg, temp reg, lsr #(32-hb)"
- 					 self machineCodeAt: 4 put: (self dataOpType: armOpcode rd: rn  rn: rn rm: ConcreteIPReg lsr: 32 - hb).
- 					^machineCodeSize := 8]].
- 			 ^self concretizeDataOperationCqR: armOpcode].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeJumpFull (in category 'generate machine code - concretize') -----
  concretizeJumpFull
  	"Will get inlined into concretizeAt: switch."
  	"A JumpFull is used when we need to jump to anywhere in 32bit address space rather than somewhere known to be in code-space. It also must be relocatable and non-varying with the jump range. On ARM this means using the build-long-const + BX sequence."
  	<inline: true>
  	| jumpTarget instrOffset|
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := self longJumpTargetAddress.
  	instrOffset := self moveCw: jumpTarget intoR: ConcreteIPReg.
  	"bx ConcreteIPReg"
  	self machineCodeAt: instrOffset put: (self bx: ConcreteIPReg).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeJumpR (in category 'generate machine code - concretize') -----
  concretizeJumpR
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	"bx reg"
  	self machineCodeAt: 0 put: (self bx: reg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code - concretize') -----
  concretizeLoadEffectiveAddressMwrR
  	"Will get inlined into concretizeAt: switch."
  	"destReg = srcReg (which contains an address) + offset"
  	<inline: true>
  	| srcReg offset destReg instrOffset |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
+ 	^self rotateable8bitImmediate: offset
- 	self rotateable8bitImmediate: offset
  		ifTrue:
  			[ :rot :immediate | 
  			self machineCodeAt: 0 
  				"add destReg, srcReg, #immediate ROR rot"
  				put: (self add: destReg rn: srcReg imm: immediate ror: rot<<1).
+ 			4]
- 			machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self moveCw: offset intoR: ConcreteIPReg.
  			"add destReg, srcReg, ConcreteIPReg"
  			self machineCodeAt: 16 put: (self add: destReg rn: srcReg rm: ConcreteIPReg).
+ 			instrOffset + 4]!
- 			machineCodeSize := instrOffset + 4].
- 	^machineCodeSize "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLogicalShiftLeftCqR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftLeftCqR
  	"Will get inlined into concretizeAt: switch."
  	"this is an unfortunate waste of an instruction in most cases since the shift can usually be done in a subsequent arithmetic instruction. 
  	Handle for now with a MOVS reg, reg, LSL #distance"
  	<inline: true>
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	"cond 000 1101 0 0000 dest dista 000 srcR"
  	self machineCodeAt: 0 put: (self type: 0 op: MoveOpcode set: 1 rn: 0 rd: reg shifterOperand: (distance << 7 bitOr: reg)).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLogicalShiftLeftRR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftLeftRR
  	"Will get inlined into concretizeAt: switch."
  	"this is an unfortunate waste of an instruction in most cases since the shift can usually be done in a subsequent arithmetic instruction. 
  	Handle for now with a MOVS reg, reg, LSL distReg" 
  	<inline: true>
  	| destReg distReg |
  	distReg := operands at: 0.
  	destReg := operands at: 1.
  	"cond 000 1101 0 0000 dest dist 0001 srcR"
  	self machineCodeAt: 0 put: (self type: 0 op: MoveOpcode set: 1 rn: 0 rd: destReg 
  									shifterOperand: (distReg << 8 bitOr: (16 bitOr: destReg))).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLogicalShiftRightCqR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftRightCqR
  	"Will get inlined into concretizeAt: switch."
  	"this is an unfortunate waste of an instruction in most cases since the shift can usually be done in a subsequent arithmetic instruction. 
  	Handle for now with a MOVS reg, reg, LSR #distance"
  	<inline: true>
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	"cond 000 1101 0 0000 dest dist -010 srcR"
  	self machineCodeAt: 0 put: (self type: 0 op: MoveOpcode set: 1 rn: 0 rd: reg 
  									shifterOperand: (distance << 7 bitOr: (32 bitOr: reg))).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLogicalShiftRightRR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftRightRR
  	"Will get inlined into concretizeAt: switch."
  	"this is an unfortunate waste of an instruction in most cases since the shift can usually be done in a subsequent arithmetic instruction. 
  	Handle for now with a MOVS reg, reg, LSR distReg"
  	<inline: true>
  	| destReg distReg |
  	distReg := operands at: 0.
  	destReg := operands at: 1.
  	"cond 000 1101 0 0000 dest dist 0011 srcR"
  	self machineCodeAt: 0 put: (self type: 0 op: MoveOpcode set: 1 rn: 0 rd: destReg 
  									shifterOperand: (distReg << 8 bitOr: (48 bitOr: destReg))).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMSR (in category 'generate machine code - concretize') -----
  concretizeMSR
  	"Generate an MSR CPSR_f, #flags instruction.
  Note that we only have business with the NZCV flags so we use
  N -> 8
  Z -> 4
  C -> 2
  V -> 1.
  You don't want to mess with this too much."
  	|  flags |
  	flags := operands at: 0.
  	self machineCodeAt: 0 put: (self msr: flags).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveAbR (in category 'generate machine code - concretize') -----
  concretizeMoveAbR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcAddr destReg instrOffset|
  	srcAddr := operands at: 0.
  	destReg := operands at: 1.
  	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self ldrb: destReg rn: ConcreteVarBaseReg plus: 1 imm: srcAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	"load the address into ConcreteIPReg"
  	instrOffset := self moveCw: srcAddr intoR: ConcreteIPReg.
  	"We *could* overwrite the last instruction above with a LDR a, b, last-byte-of-srcAddr BUT that would break if we change to loading literals instead of forming long constants"
  	self machineCodeAt: instrOffset put: (self ldrb: destReg rn: ConcreteIPReg plus: 1 imm: 0).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveAwR (in category 'generate machine code - concretize') -----
  concretizeMoveAwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcAddr destReg instrOffset|
  	srcAddr := operands at: 0.
  	destReg := operands at: 1.
  	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self ldr: destReg rn: ConcreteVarBaseReg plusImm: srcAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	"load the address into ConcreteIPReg"
  	instrOffset := self moveCw: srcAddr intoR: ConcreteIPReg.
  	"We *could* overwrite the last instruction above with a LDR a, b, last-byte-of-srcAddr BUT that would break if we change to loading literals instead of forming long constants"
  	self machineCodeAt: instrOffset put: (self ldr: destReg rn: ConcreteIPReg plusImm: 0).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveCqR (in category 'generate machine code - concretize') -----
  concretizeMoveCqR
  	"Will get inlined into concretizeAt: switch."
  	"If the quick constant is in fact a shiftable 8bit, generate the apropriate MOV, otherwise do what is necessary for a whole word."
  	<var: #word type: #sqInt>
  	<inline: true>
+ 	| word reg invVal |
- 	|word reg|
  	word := operands at: 0.
  	reg := operands at: 1.
  	self 
  		rotateable8bitImmediate: word 
+ 		ifTrue:
+ 			[:rot :immediate |
- 		ifTrue: [:rot :immediate |
  			self machineCodeAt: 0 put: (self mov: reg imm: immediate ror: rot).
+ 			^4]
+ 		ifFalse:
+ 			[].
+ 	invVal := word < 0 ifTrue: [-1 - word] ifFalse: [word bitInvert32].
+ 	^self rotateable8bitImmediate: invVal
+ 		ifTrue: [ :rot :immediate |
+ 			self machineCodeAt: 0 put: (self mvn: reg imm: immediate ror: rot).
+ 			4]
+ 		ifFalse: [self concretizeMoveCwR]!
- 			^machineCodeSize := 4]
- 		ifFalse: [|invVal|
- 			word <0
- 				ifTrue:[invVal := -1 - word]
- 				ifFalse:[invVal := word bitInvert32].
- 			self rotateable8bitImmediate: invVal
- 				ifTrue: [ :rot :immediate |
- 					self machineCodeAt: 0 put: (self mvn: reg imm: immediate ror: rot).
- 					^machineCodeSize := 4]
- 				ifFalse: [^self concretizeMoveCwR]].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveCwR (in category 'generate machine code - concretize') -----
  concretizeMoveCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	^self loadCwInto: (operands at: 1)!
- 	^machineCodeSize := self loadCwInto: (operands at: 1)!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveM16rR (in category 'generate machine code - concretize') -----
  concretizeMoveM16rR
  	"Will get inlined into concretizeAt: switch."
  	"ldrh destReg, [srcReg, #immediate],
  	or 
  	move offset to ConcreteIPReg
  	ldrh destReg, [srcReg, ConcreteIPReg]"
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| srcReg offset destReg instrOffset|
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	self is8BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "ldrh destReg, [srcReg, #immediate]"
  				put: (self ldrh: destReg rn: srcReg plus: u imm: immediate).
+ 			^4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self moveCw: offset intoR: ConcreteIPReg.
  			"ldrh destReg, [srcReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self ldrh: destReg rn: srcReg rm: ConcreteIPReg).
+ 			^instrOffset + 4 ].
- 			^machineCodeSize := instrOffset + 4 ].
  	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveM64rRd (in category 'generate machine code - concretize') -----
  concretizeMoveM64rRd
  	"Will get inlined into concretizeAt: switch."	
  	<inline: true>
  	"Load a float from srcReg+offset into FP destReg"
  	| srcReg offset destReg u|
  	offset := operands at: 0.
  	u := offset >0 ifTrue:[1] ifFalse:[0].
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode at: 0 put: (self fldd: destReg rn: srcReg plus: u imm: offset>>2).
+ 	^4
- 	^machineCodeSize := 4
  !

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
  concretizeMoveMbrR
  	"Will get inlined into concretizeAt: switch."
  	"ldrb destReg, [srcReg, #immediate] or ldrb destReg, [srcReg, ConcreteIPReg]"
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| srcReg offset destReg instrOffset|
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
+ 	^self is12BitValue: offset
- 	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "ldrb destReg, [srcReg, #immediate]"
  				put: (self ldrb: destReg rn: srcReg plus: u imm: immediate).
+ 			4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[(self isAddressRelativeToVarBase: offset)
  				ifTrue:
  					[self machineCodeAt: 0 put: (self adds: ConcreteIPReg rn: ConcreteVarBaseReg imm: offset - cogit varBaseAddress ror: 0).
  					 instrOffset := 4]
  				ifFalse:
  					[instrOffset := self moveCw: offset intoR: ConcreteIPReg].
  			 "ldrb destReg, [srcReg, ConcreteIPReg]"
  			 self machineCodeAt: instrOffset put: (self ldrb: destReg rn: srcReg rm: ConcreteIPReg).
+ 			 instrOffset + 4]!
- 			 ^machineCodeSize := instrOffset + 4].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveMwrR (in category 'generate machine code - concretize') -----
  concretizeMoveMwrR
  	"Will get inlined into concretizeAt: switch."
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| srcReg offset destReg instrOffset|
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
+ 	^self is12BitValue: offset
- 	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "ldr destReg, [srcReg, #immediate]"
  				put: (self ldr: destReg rn: srcReg plus: u imm: immediate).
+ 			4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self moveCw: offset intoR: ConcreteIPReg.
  			"ldr destReg, [srcReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self ldr: destReg rn: srcReg rm: ConcreteIPReg).
+ 			instrOffset + 4]!
- 			^machineCodeSize := instrOffset + 4].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRAb (in category 'generate machine code - concretize') -----
  concretizeMoveRAb
  	"Will get inlined into concretizeAt: switch."
  	"LEA ConcreteIPReg
  	strb srcReg, [ConcreteIPReg]"
  	<inline: true>
  	| srcReg destAddr instrOffset|
  	srcReg := operands at: 0.
  	destAddr := operands at: 1.
  	(self isAddressRelativeToVarBase: destAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self strb: srcReg rn: ConcreteVarBaseReg plus: 1 imm: destAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	"load the address into ConcreteIPReg"
  	instrOffset := self moveCw: destAddr intoR: ConcreteIPReg.
  	"We *could* overwrite the last instruction above with a LDR a, b, last-byte-of-srcAddr BUT that would break if we change to loading literals instead of forming long constants"
  	self machineCodeAt: instrOffset put: (self strb: srcReg rn: ConcreteIPReg plus: 1 imm: 0).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
  concretizeMoveRAw
  	"Will get inlined into concretizeAt: switch."
  	"LEA ConcreteIPReg
  	str srcReg, [ConcreteIPReg]"
  	<inline: true>
  	| srcReg destAddr instrOffset|
  	srcReg := operands at: 0.
  	destAddr := operands at: 1.
  	(self isAddressRelativeToVarBase: destAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self str: srcReg rn: ConcreteVarBaseReg plusImm: destAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	"load the address into ConcreteIPReg"
  	instrOffset := self moveCw: destAddr intoR: ConcreteIPReg.
  	"We *could* overwrite the last instruction above with a LDR a, b, last-byte-of-srcAddr BUT that would break if we change to loading literals instead of forming long constants"
  	self machineCodeAt: instrOffset put: (self str: srcReg rn: ConcreteIPReg plusImm: 0).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRM16r (in category 'generate machine code - concretize') -----
  concretizeMoveRM16r
  	"Will get inlined into concretizeAt: switch."
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| srcReg offset baseReg instrOffset|
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	baseReg := operands at: 2.
+ 	^self is12BitValue: offset
- 	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "strh 	srcReg, [baseReg, #immediate]"
  				put: (self strh: srcReg rn: baseReg plus: u imm: immediate).
+ 			4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[(self isAddressRelativeToVarBase: offset)
  				ifTrue:
  					[self machineCodeAt: 0 put: (self adds: ConcreteIPReg rn: ConcreteVarBaseReg imm: offset - cogit varBaseAddress ror: 0).
  					 instrOffset := 4]
  				ifFalse:
  					[instrOffset := self moveCw: offset intoR: ConcreteIPReg].
  			"strb 	srcReg, [baseReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self strh: srcReg rn: baseReg rm: ConcreteIPReg).
+ 			instrOffset + 4]!
- 			^machineCodeSize := instrOffset + 4 ].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRMbr (in category 'generate machine code - concretize') -----
  concretizeMoveRMbr
  	"Will get inlined into concretizeAt: switch."
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| srcReg offset baseReg instrOffset|
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	baseReg := operands at: 2.
+ 	^self is12BitValue: offset
- 	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0 "strb 	srcReg, [baseReg, #immediate]"
  				put: (self strb: srcReg rn: baseReg plus: u imm: immediate).
+ 			4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[(self isAddressRelativeToVarBase: offset)
  				ifTrue:
  					[self machineCodeAt: 0 put: (self adds: ConcreteIPReg rn: ConcreteVarBaseReg imm: offset - cogit varBaseAddress ror: 0).
  					 instrOffset := 4]
  				ifFalse:
  					[instrOffset := self moveCw: offset intoR: ConcreteIPReg].
  			"strb 	srcReg, [baseReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self strb: srcReg rn: baseReg rm: ConcreteIPReg).
+ 			instrOffset + 4]!
- 			^machineCodeSize := instrOffset + 4 ].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRMwr (in category 'generate machine code - concretize') -----
  concretizeMoveRMwr
  	"Will get inlined into concretizeAt: switch."
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| srcReg offset baseReg instrOffset|
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	baseReg := operands at: 2.
+ 	^self is12BitValue: offset
- 	self is12BitValue: offset
  		ifTrue:
  			[ :u :immediate | 
  			self machineCodeAt: 0  "str 	srcReg, [baseReg, #immediate]"
  				put: (self str: srcReg rn: baseReg plus: u imm: immediate).
+ 			4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[instrOffset := self moveCw: offset intoR: ConcreteIPReg.
  			"str srcReg, [baseReg, ConcreteIPReg]"
  			self machineCodeAt: instrOffset put: (self str: srcReg rn: baseReg rm: ConcreteIPReg).
+ 			instrOffset + 4]!
- 			^machineCodeSize := instrOffset + 4].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRR (in category 'generate machine code - concretize') -----
  concretizeMoveRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	"cond 000 1101 0 0000 dest 0000 0000 srcR"
  	self machineCodeAt: 0 put: (self mov: destReg rn: srcReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRXbrR (in category 'generate machine code - concretize') -----
  concretizeMoveRXbrR
  	"Will get inlined into concretizeAt: switch."
  	"Write the word in R(src) into memory at address (base+1*index)"
  	<inline: true>
  	| index base src |
  	src := operands at: 0.
  	index := operands at: 1.
  	base := operands at: 2.
  	"str	b	src, [base, +index, LSL #0]"
  	"cond 011 1100 0 base srcR 00000 00 0 index"
  	self machineCodeAt: 0 put: (self strb: src rn: base rm: index).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRXwrR (in category 'generate machine code - concretize') -----
  concretizeMoveRXwrR
  	"Will get inlined into concretizeAt: switch."
  	"Write the word in R(src) into memory at address (base+4*index)"
  	<inline: true>
  	| index base src |
  	src := operands at: 0.
  	index := operands at: 1. "index is number of *words* = 4* bytes"
  	base := operands at: 2.
  	"str		src, [base, +index, LSL #2]"
  	"cond 011 1100 0 base srcR 00010 00 0 inde"
  	self machineCodeAt: 0 put: (self memMxr: AL reg: src base: base p: 1 u: 1 b: 0 w: 0 l: 0 rmLsl2: index).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRdM64r (in category 'generate machine code - concretize') -----
  concretizeMoveRdM64r
  	"Will get inlined into concretizeAt: switch."	
  	<inline: true>
  	"Store FP fpReg to dstReg+offset"
  	| dstReg offset fpReg u|
  	offset := operands at: 1.
  	u := offset >0 ifTrue:[1] ifFalse:[0].
  	dstReg := operands at: 2.
  	fpReg := operands at: 0.
  	machineCode at: 0 put: (self fstd: fpReg rn: dstReg plus: u imm: offset>>2).
+ 	^4
- 	^machineCodeSize := 4
  !

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveXbrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXbrRR
  	"Will get inlined into concretizeAt: switch."
  	
  	<inline: true>
  	| index base dest |
  	index := operands at: 0. "index is number of *bytes*"
  	base := operands at: 1.
  	dest := operands at: 2.
  	"LDRB	dest, [base, +index, LSL #0]"
  	"cond 011 1100 1 base dest 00000 00 0 inde"
  	self machineCodeAt: 0 put: (self ldrb: dest rn: base rm: index).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveXwrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXwrRR
  	"Will get inlined into concretizeAt: switch."
  	
  	<inline: true>
  	| index base dest |
  	index := operands at: 0.
  	base := operands at: 1.
  	dest := operands at: 2.
  	"LDR	dest, [base, +index, LSL #2]"
  	"cond 011 1100 1 base dest 00010 00 0 inde bulit by lowest level generator so we can do the lsl #2 on the index register"
  	self machineCodeAt: 0 put: (self memMxr: AL reg: dest base: base p: 1 u: 1 b: 0 w: 0 l: 1 rmLsl2: index).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMulRdRd (in category 'generate machine code - concretize') -----
  concretizeMulRdRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"FP multiply regLHS by regRHS and stick result in regLHS"
  	| regLHS regRHS |
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode at: 0 put:(self fmuld: regLHS with: regRHS).
+ 	^4
- 	^machineCodeSize := 4
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeNegateR (in category 'generate machine code - concretize') -----
  concretizeNegateR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	"RSB destReg, srcReg, #0"
  	self machineCodeAt: 0 put: (self type: 1 op: RsbOpcode set: 0 rn: reg rd: reg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeNegateableDataOperationCqR: (in category 'generate machine code - concretize') -----
  concretizeNegateableDataOperationCqR: armOpcode
  	"Will get inlined into concretizeAt: switch."
  	"4 == Add, 2 == Sub, 10 = Cmp"
  	<inline: true>
  	| val rd rn |
  	val := operands at: 0.
  	rn := operands at: 1.
  	"Extra note - if ever a version of this code wants to NOT set the Set flag
  	 - Cmp must always have it set or it will pretend to be a SMALALBT and Very Bad Things might happen."
  	rd := opcode = CmpOpcode ifTrue: [0] ifFalse: [rn].
  
  	self rotateable8bitSignedImmediate: val 
  		ifTrue:
  			[:rot :immediate : negate|
  			self machineCodeAt: 0
  				put: (self
  						type: 1
  						op: (negate ifTrue: [self inverseOpcodeFor: armOpcode] ifFalse: [armOpcode])
  						set: 1
  						rn: rn
  						rd: rd
  						shifterOperand: (rot >> 1"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
+ 			^4]
- 			^machineCodeSize := 4]
  		ifFalse: "let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
  			[val > 0 ifTrue:
  				[| hb |
  				hb := val highBit.
  				1 << hb = (val +1) ifTrue: "MVN temp,  #0, making 0xffffffff"
  					[self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
  					 "Then armOpcode reg, temp reg, lsr #(32-hb)"
  					 self machineCodeAt: 4 put:(self dataOpType: armOpcode rd: rd  rn: rn rm: ConcreteIPReg lsr: 32 - hb).
+ 					^8]].
- 					^machineCodeSize := 8]].
  			 ^self concretizeDataOperationCwR: armOpcode].
  	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeNop (in category 'generate machine code - concretize') -----
  concretizeNop
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"(CogARMCompiler new  mov: 0 rn: 0 ) hex -> MOV r0, r0"
  	self machineCodeAt: 0 put: 16rE1A00000.
+ 	^4
- 	^machineCodeSize := 4
  			!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePopR (in category 'generate machine code - concretize') -----
  concretizePopR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| destReg |
  	destReg := operands at: 0.
  	"LDR destReg, [SP], #4"
  	self machineCodeAt: 0 put: (self popR: destReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePrefetchAw (in category 'generate machine code - concretize') -----
  concretizePrefetchAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand instrOffset|
  	addressOperand := operands at: 0.
  	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
  		[self machineCodeAt: 0 put: (self pld: ConcreteVarBaseReg plus: 1 offset: addressOperand - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	instrOffset := self moveCw: addressOperand intoR: ConcreteIPReg.
  	"pld	[ConcreteIPReg]"
  	self machineCodeAt: instrOffset put: (self pld: ConcreteIPReg plus: 1offset: 0).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushCq (in category 'generate machine code - concretize') -----
  concretizePushCq
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| word instrOffset |
  	word := operands at: 0.
  	self 
  		rotateable8bitBitwiseImmediate: word 
  		ifTrue:
  			[:rot :immediate :invert|
  			self machineCodeAt: 0
  				put: (invert
  						ifTrue: [self mvn: ConcreteIPReg imm: immediate ror: rot]
  						ifFalse: [self mov: ConcreteIPReg imm: immediate ror: rot]).
  			instrOffset := 4]
  		ifFalse:
  			[instrOffset := self moveCw: word intoR: ConcreteIPReg].
  	self machineCodeAt: instrOffset put: (self pushR: ConcreteIPReg).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushCw (in category 'generate machine code - concretize') -----
  concretizePushCw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| word instrOffset |
  	word := operands at: 0.	
  	(self inCurrentCompilation: word)
  		ifTrue:
  			[instrOffset := self loadCwInto: ConcreteIPReg]
  		ifFalse:
  			[self 
  				rotateable8bitBitwiseImmediate: word 
  				ifTrue:
  					[:rot :immediate :invert|
  					self machineCodeAt: 0
  						put: (invert
  								ifTrue: [self mvn: ConcreteIPReg imm: immediate ror: rot]
  								ifFalse: [self mov: ConcreteIPReg imm: immediate ror: rot]).
  					instrOffset := 4]
  				ifFalse:
  					[instrOffset := self loadCwInto: ConcreteIPReg]].
  	self machineCodeAt: instrOffset put: (self pushR: ConcreteIPReg).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushOrPopMultipleRegisters: (in category 'generate machine code - concretize') -----
  concretizePushOrPopMultipleRegisters: doPush
  	self assert: (operands at: 0) ~= 0.
  	machineCode at: 0 put: AL << 28
  						  + (doPush     "2r100PUSWL"
  								ifTrue: [2r10010010 << 20]
  								ifFalse: [2r10001011 << 20])
  						  + (SP << 16)
  						  + (operands at: 0).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushR (in category 'generate machine code - concretize') -----
  concretizePushR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg |
  	srcReg := operands at: 0.
  	"cond | 010 | 1001 | 0 | -Rn- | -Rd- | 0000 0000 0100" "STR srcReg, [sp, #-4]"
  	self machineCodeAt: 0 put: (self pushR: srcReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeRetN (in category 'generate machine code - concretize') -----
  concretizeRetN
  	"Will get inlined into concretizeAt: switch."
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| offset |
  	offset := operands at: 0.
  	offset = 0 ifTrue:
  		[self machineCodeAt: 0 put: (self mov: PC rn: LR). "pop	{pc}"
+ 		^4].
- 		^machineCodeSize := 4].
  	self assert: offset < 255. "We have an 8 bit immediate. If needed, we could rotate it less than 30 bit."
  
  	self machineCodeAt: 0 put: (self add: SP rn: SP imm: offset  ror: 0).
  	self machineCodeAt: 4 put: (self mov: PC rn: LR).  "pop	{pc}"
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeSMULL (in category 'generate machine code - concretize') -----
  concretizeSMULL
  	| srcA srcB hiResultReg loResultReg |
  	"Generate an SMULL loResultReg, hiResultReg, srcA, srcB instruction"
  	srcA := operands at: 0.
  	"NOTE: srcB contains the other mutiplicand at this point. It is OK to use it as the destination for the low part of the result and in fact this saves us moving it later"
  	loResultReg := srcB := operands at: 1.
  	hiResultReg := RISCTempReg.
  	self machineCodeAt: 0
  		put: (self type: 0 op: 6 set: 0 rn: hiResultReg rd: loResultReg)
  			+ (srcA << 8)
  			+ (9 << 4)
  			+ srcB.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeSqrtRd (in category 'generate machine code - concretize') -----
  concretizeSqrtRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"Square root of FP regLHS into regLHS"
  	| regLHS  |
  	regLHS := operands at: 0.
  	machineCode at: 0 put:(self fsqrtd: regLHS).
+ 	^4
- 	^machineCodeSize := 4
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeStop (in category 'generate machine code - concretize') -----
  concretizeStop
  	<inline: true>
  	self machineCodeAt: 0 put: self stop.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeSubCqR (in category 'generate machine code - concretize') -----
  concretizeSubCqR
  	"Will get inlined into concretizeAt: switch."
  	"Try whether the quick constant is a small negative number. If it is, optimize."
  	<var: #word type: #sqInt>
  	<inline: true>
  	| word |
  	word := operands at: 0.
  	self rotateable8bitImmediate: word
  		ifTrue: [ :rot :immediate | | reg |
  			reg := operands at: 1.
  			self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot).
+ 			^4]
+ 		ifFalse: [].
+ 	"before building a full load of a big constant, see if we can do an add of the constant negated"
+ 	^self rotateable8bitImmediate: word negated
+ 		ifTrue: [ :rot :immediate | | reg |
+ 			reg := operands at: 1.
+ 			self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot).
+ 			4]
+ 		ifFalse: [self concretizeDataOperationCwR: SubOpcode]!
- 			^machineCodeSize := 4]
- 		ifFalse: [
- 			"before building a full load of a big constant, see if we can do an add of the constant negated"
- 			self rotateable8bitImmediate: word negated
- 				ifTrue: [ :rot :immediate | | reg |
- 					reg := operands at: 1.
- 					self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot).
- 					^machineCodeSize := 4]
- 				ifFalse: [^self concretizeDataOperationCwR: SubOpcode]].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeSubRdRd (in category 'generate machine code - concretize') -----
  concretizeSubRdRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS |
  	"Subtract FP regRHS from FP regLHS and leave the result in FP regLHS"
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode at: 0 put:(self fsubd: regLHS with: regRHS).
+ 	^4
- 	^machineCodeSize := 4
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeTstCqR (in category 'generate machine code - concretize') -----
  concretizeTstCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	^self rotateable8bitImmediate: (operands at: 0)
- 	self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := operands at: 1.
  			self machineCodeAt: 0 put: (self tst: reg rn: reg imm: immediate ror: rot).
+ 			4]
+ 		ifFalse: [self concretizeDataOperationCwR: TstOpcode]!
- 			^machineCodeSize := 4]
- 		ifFalse: [^self concretizeDataOperationCwR: TstOpcode].
- 	^0 "to keep Slang happy"!

Item was changed:
  ----- Method: CogARMCompiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
- 	<returnTypeC: #void>
  	conditionOrNil ifNotNil:
+ 		[^self concretizeConditionalInstruction].
- 		[self concretizeConditionalInstruction.
- 		 ^self].
  		 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[Literal]					-> [^self concretizeLiteral].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill32]					-> [^self concretizeFill32].
  		[Nop]					-> [^self concretizeNop].
  		"Control"
  		[Call]						-> [^self concretizeCall]. "call code within code space"
  		[CallFull]					-> [^self concretizeCallFull]. "call code anywhere in address space"
  		[JumpR]						-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeJumpFull]."jump within address space"
  		[JumpLong]					-> [^self concretizeConditionalJump: AL]."jumps witihn code space"
  		[JumpLongZero]			-> [^self concretizeConditionalJump: EQ].
  		[JumpLongNonZero]		-> [^self concretizeConditionalJump: NE].
  		[Jump]						-> [^self concretizeConditionalJump: AL].
  		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
  		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
  		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
  		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
  		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
  		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
  		[JumpCarry]				-> [^self concretizeConditionalJump: CS].
  		[JumpNoCarry]				-> [^self concretizeConditionalJump: CC].
  		[JumpLess]					-> [^self concretizeConditionalJump: LT].
  		[JumpGreaterOrEqual]		-> [^self concretizeConditionalJump: GE].
  		[JumpGreater]				-> [^self concretizeConditionalJump: GT].
  		[JumpLessOrEqual]			-> [^self concretizeConditionalJump: LE].
  		[JumpBelow]				-> [^self concretizeConditionalJump: CC]. "unsigned lower"
  		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CS]. "unsigned greater or equal"
  		[JumpAbove]				-> [^self concretizeConditionalJump: HI].
  		[JumpBelowOrEqual]		-> [^self concretizeConditionalJump: LS].
  		[JumpFPEqual]				-> [^self concretizeFPConditionalJump: EQ].
  		[JumpFPNotEqual]			-> [^self concretizeFPConditionalJump: NE].
  		[JumpFPLess]				-> [^self concretizeFPConditionalJump: LT].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeFPConditionalJump: GE].
  		[JumpFPGreater]			-> [^self concretizeFPConditionalJump: GT].
  		[JumpFPLessOrEqual]		-> [^self concretizeFPConditionalJump: LE].
  		[JumpFPOrdered]			-> [^self concretizeFPConditionalJump: VC].
  		[JumpFPUnordered]			-> [^self concretizeFPConditionalJump: VS].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeNegateableDataOperationCqR: AddOpcode].
  		[AndCqR]					-> [^self concretizeInvertibleDataOperationCqR: AndOpcode].
  		[AndCqRR]					-> [^self concretizeAndCqRR].
  		[CmpCqR]					-> [^self concretizeNegateableDataOperationCqR: CmpOpcode].
  		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[XorCqR]					-> [^self concretizeInvertibleDataOperationCqR: XorOpcode].
  		[AddCwR]					-> [^self concretizeDataOperationCwR: AddOpcode].
  		[AndCwR]					-> [^self concretizeDataOperationCwR: AndOpcode].
  		[CmpCwR]					-> [^self concretizeDataOperationCwR: CmpOpcode].
  		[OrCwR]					-> [^self concretizeDataOperationCwR: OrOpcode].
  		[SubCwR]					-> [^self concretizeDataOperationCwR: SubOpcode].
  		[XorCwR]					-> [^self concretizeDataOperationCwR: XorOpcode].
  		[AddRR]						-> [^self concretizeDataOperationRR: AddOpcode].
  		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
  		[CmpRR]					-> [^self concretizeDataOperationRR: CmpOpcode].
  		[OrRR]						-> [^self concretizeDataOperationRR: OrOpcode].
  		[SubRR]						-> [^self concretizeDataOperationRR: SubOpcode].
  		[XorRR]						-> [^self concretizeDataOperationRR: XorOpcode].
  		[AddRdRd]					-> [^self concretizeAddRdRd].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeDivRdRd].
  		[MulRdRd]					-> [^self concretizeMulRdRd].
  		[SubRdRd]					-> [^self concretizeSubRdRd].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		[ClzRR]						-> [^self concretizeClzRR].
  		"ARM Specific Arithmetic" 
  		[SMULL]			-> [^self concretizeSMULL]	.
  		[CMPSMULL]		-> [^self concretizeCMPSMULL].
  		[MSR]				-> [^self concretizeMSR].
  		"ARM Specific Data Movement"
  		[PopLDM]			-> [^self concretizePushOrPopMultipleRegisters: false].
  		[PushSTM]			-> [^self concretizePushOrPopMultipleRegisters: true].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR] 			 -> [^self concretizeMoveAbR].
   		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
+ 		[ConvertRRd]		-> [^self concretizeConvertRRd]}.
+ 
+ 	^0 "keep Slang happy"!
- 		[ConvertRRd]		-> [^self concretizeConvertRRd]}!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeAddCqR (in category 'generate machine code - concretize') -----
  concretizeAddCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| constant reg offset |
  	constant := operands at: 0.
  	reg := operands at: 1.
  
  	self deny: reg = SP. "For now; how to add an immediate to the SP?"
  	self isPossiblyShiftableImm12: constant 
  		ifTrue:
  			[:shift|
  			"C6.2.8		ADDS (immediate)	C6-769"
  			machineCode
  				at: 0
  				put: 2r101100010 << 23
  					+ (shift ifTrue: [constant >> 2 + (1 << 22)] ifFalse: [constant << 10])
  					+ (reg << 5)
  					+ reg.
+ 			^4]
- 			^machineCodeSize := 4]
  		ifFalse: [].
  	offset := self moveCw: constant intoR: RISCTempReg.
  	"C6.2.7		ADDS (extended register)		C6-766"
  	machineCode
  				at: offset // 4
  				put: 2r10101011001
  					+ (RISCTempReg << 16)
  					+ (SXTX << 13)
  					+ (reg << 5)
  					+ reg.
+ 	^offset + 4!
- 	^machineCodeSize := offset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeAndCqRDest: (in category 'generate machine code - concretize') -----
  concretizeAndCqRDest: destReg
  	"C6.2.14	ANDS (immediate)	C6-779
  	 C6.2.329	TST (immediate)	C6-1346"
  	| srcReg constant offset |
  	constant := operands at: 0.
  	srcReg := operands at: 1.
  	self isImmNImmSImmREncodableBitmask: constant
  		ifTrue:
  			[:n :imms :immr|
  			 machineCode
  				at: 0
  				put: 2r111100100 << 23
  					+ (n << 22)
  					+ (immr << 16)
  					+ (imms << 10)
  					+ (srcReg << 5)
  					+ destReg.
+ 			 ^4]
- 			 ^machineCodeSize := 4]
  		ifFalse: [].
  	offset := self moveCw: constant intoR: RISCTempReg.
  	"C6.2.15	ANDS (shifted register)		C6-781"
  	machineCode
  				at: offset // 4
  				put: 2r11101010 << 24
  					+ (RISCTempReg << 16)
  					+ (srcReg << 5)
  					+ destReg.
+ 	^offset + 4!
- 	^machineCodeSize := offset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeCmpCqR (in category 'generate machine code - concretize') -----
  concretizeCmpCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| constant rn offset |
  	constant := operands at: 0.
  	rn := operands at: 1.
  
  	self is6BitSignedImmediate: constant 
  		ifTrue:
  			[:immediate : negate|
  			"C6.2.46	CCMN (immediate)	C6-833
  			 C6.2.48	CCMP (immediate)	C6-837"
  			machineCode
  				at: 0
  				put: 2r11111010010000000000100000001111
  					+ (AL << 12)
  					+ (negate ifTrue: [1 << 30] ifFalse: [0])
  					+ (immediate << 16)
  					+ (rn << 5).
+ 			^4]
- 			^machineCodeSize := 4]
  		ifFalse: [].
  	offset := self moveCw: constant intoR: RISCTempReg.
  	"C6.2.49	CCMP (register)	C6-839"
  	machineCode
  				at: offset // 4
  				put: 2r11111010010000000000000000001111
  					+ (AL << 12)
  					+ (RISCTempReg << 16)
  					+ (rn << 5).
+ 	^offset + 4!
- 	^machineCodeSize := offset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeDataOperationRR: (in category 'generate machine code - concretize') -----
+ concretizeDataOperationRR: armOpcode
- concretizeDataOperationRR: opcode
  	"C3.4	Data processing - register	C3-219
  
  	- Arithmetic (shifted register).
  	- Arithmetic (extended register) on page C3-220.
  	- Arithmetic with carry on page C3-221.
  	- Flag manipulation instructions on page C3-221.
  	- Logical (shifted register) on page C3-221.
  	- Move (register) on page C3-222.
  	- Shift (register) on page C3-222.
  	- Multiply and divide on page C3-223.
  	- CRC32 on page C3-224.
  	- Bit operation on page C3-225.
  	- Conditional select on page C3-225.
  	- Conditional comparison on page C3-226."
  
  	"C3.4.2		Arithmetic (extended register)
  
  	The extended register instructions provide an optional sign-extension or zero-extension of a portion of the second source register value,
  	 followed by an optional left shift by a constant amount of 1-4, inclusive.
  		ADD (extended register) on page C6-758
  		ADDS (extended register) on page C6-766
  		SUB (extended register) on page C6-1308
  		SUBS (extended register) on page C6-1318
  		CMN (extended register) on page C6-850
  		CMP (extended register) on page C6-856"
  
  	self shouldNotImplement!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeLiteral (in category 'generate machine code') -----
  concretizeLiteral
  	"Generate an out-of-line literal.  Copy the value and any annotation from the stand-in in the literals manager."
  	| literalAsInstruction literal |
  	<var: 'literal' type: #usqInt>
  	literalAsInstruction := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	literal := (self isAnInstruction: literalAsInstruction)
  				ifTrue: [literalAsInstruction address]
  				ifFalse: [self cCode: [literalAsInstruction asUnsignedInteger]
  							inSmalltalk: [literalAsInstruction]].
  	self assert: (dependent notNil and: [dependent opcode = Literal]).
  	dependent annotation ifNotNil:
  		[self assert: annotation isNil.
  		 annotation := dependent annotation].
  	dependent address ifNotNil: [self assert: dependent address = address].
  	dependent address: address.
  	machineCode
  		at: 0 put: (literal bitAnd: 16rFFFFFFFF);
  		at: 1 put: (literal >> 32).
+ 	^8!
- 	machineCodeSize := 8!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeLogicalShiftLeftCqR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftLeftCqR
  	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
  	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
  	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
  	| reg constant |
  	constant := operands at: 0.
  	reg := operands at: 1.
  	self assert: (constant between: 1 and: 63).
  	machineCode
  		at: 0
  		put: 2r1101001101 << 22
  			+ (constant << 16)
  			+ (63 << 10)
  			+ (reg << 5)
  			+ reg.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveAwR (in category 'generate machine code - concretize') -----
  concretizeMoveAwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcAddr destReg instrOffset|
  	srcAddr := operands at: 0.
  	destReg := operands at: 1.
  	"ldr srcReg, [VarBaseReg, #offset] except that this is illegal for SP/X31"
  	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
  		[srcAddr < cogit varBaseAddress ifTrue:
  			[self shouldBeImplemented.
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		 destReg ~= SP ifTrue:
  			[machineCode
  				at: 0
  				put: (self ldrn: VarBaseReg rt: destReg imm: srcAddr - cogit varBaseAddress shiftBy12: false).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		 machineCode
  			at: 0
  			put: (self ldrn: VarBaseReg rt: RISCTempReg imm: srcAddr - cogit varBaseAddress shiftBy12: false);
  			at: 1
  			put: (self movern: RISCTempReg rd: destReg).
+ 		^8].
- 		^machineCodeSize := 8].
  	"LEA ConcreteIPReg
  	 ldr destReg, [ConcreteIPReg]"
  	instrOffset := self moveCw: srcAddr intoR: RISCTempReg.
  	self deny: SP = destReg.
  	machineCode
  		at: instrOffset // 4
  		put: (self ldrn: RISCTempReg rt: destReg imm: 0 shiftBy12: false).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveM16rR (in category 'generate machine code - concretize') -----
  concretizeMoveM16rR
  	"C6.2.168	LDURH	C6-1061"
  	| offset destReg srcReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	(offset between: -256 and: 255)
  		ifTrue:
  			[machineCode
  				at: 0
  				put: 2r0111100001 << 22
  					+ ((offset bitAnd: 1 << 9 - 1) << 12)
  					+ (srcReg << 5)
  					+ destReg.
+ 			^4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[self shouldBeImplemented]!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
  concretizeMoveMbrR
  	"C6.2.167	LDURB	C6-1060"
  	| offset destReg srcReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	(offset between: -256 and: 255)
  		ifTrue:
  			[machineCode
  				at: 0
  				put: 2r0011100001 << 22
  					+ ((offset bitAnd: 1 << 9 - 1) << 12)
  					+ (srcReg << 5)
  					+ destReg.
+ 			^4]
- 			^machineCodeSize := 4]
  		ifFalse:
  			[self shouldBeImplemented]!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveMwrR (in category 'generate machine code - concretize') -----
  concretizeMoveMwrR
  	<inline: true>
  	| srcReg offset destReg |
  	<var: #offset type: #sqInt>
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode
  		at: 0
  		put: (self ldrn: srcReg rt: destReg imm: offset shiftBy12: false).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
  concretizeMoveRAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg destAddr instrOffset|
  	srcReg := operands at: 0.
  	destAddr := operands at: 1.
  	"str srcReg, [VarBaseReg, #offset] except that this is illegal for SP/X31"
  	(self isAddressRelativeToVarBase: destAddr) ifTrue:
  		[destAddr < cogit varBaseAddress ifTrue:
  			[self shouldBeImplemented.
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		 srcReg ~= SP ifTrue:
  			[machineCode
  				at: 0
  				put: (self strn: srcReg rt: VarBaseReg imm: destAddr - cogit varBaseAddress shiftBy12: false).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 0
  			put: (self movern: srcReg rd: RISCTempReg);
  			at: 1
  			put: (self strn: RISCTempReg rt: VarBaseReg imm: destAddr - cogit varBaseAddress shiftBy12: false).
+ 		^8].
- 		^machineCodeSize := 8].
  	"LEA ConcreteIPReg
  	 str srcReg, [ConcreteIPReg]"
  	instrOffset := self moveCw: destAddr intoR: RISCTempReg.
  	machineCode
  		at: instrOffset // 4
  		put: (self strn: srcReg rt: RISCTempReg imm: 0 shiftBy12: false).
+ 	^instrOffset + 4!
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveRR (in category 'generate machine code - concretize') -----
  concretizeMoveRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	"C6.2.184 MOV (to/from SP) p1089
  	 C6.2.188 MOV (register) p1096"
  	machineCode
  		at: 0
  		put: ((srcReg = SP or: [destReg = SP])
  				ifTrue:  [2r10010001000000000000000000000000 + (srcReg << 5) + destReg]
  				ifFalse: [2r10101010000000000000001111100000 + (srcReg << 16) + destReg]).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveXwrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXwrRR
  	"Xwr - memory word whose address is r * word size away from an address in a register"
  	"C6.2.132	LDR (register)	C6-981"
  	| destReg srcReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	self deny: SP = destReg.
  	machineCode
  		at: 0
  		put: 2r11111000011 << 21
  			+ (destReg << 16)
  			+ (UXTX << 13)
  			+ (1 << 12)
  			+ (srcReg << 5)
  			+ destReg.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeNegateR (in category 'generate machine code - concretize') -----
  concretizeNegateR
  	"C6.2.313	SUBS (extended register)	C6-1318"
  	| reg |
  	reg := operands at: 0.
  	self deny: SP = reg.
  	machineCode
  		at: 0
  		put: 2r11101011001 << 21
  			+ (31 << 16)
  			+ (UXTX << 13)
  			+ (reg << 5)
  			+ reg.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeRetN (in category 'generate machine code - concretize') -----
  concretizeRetN
  	"Will get inlined into concretizeAt: switch."
  	<var: #offset type: #sqInt>
  	<inline: true>
  	| offset |
  	offset := operands at: 0.
  	"C6.2.218 RET p1147"
  	offset = 0 ifTrue:
  		[machineCode at: 0 put: 2r11010110010111110000000000000000 + (LR << 5).
+ 		^4].
- 		^machineCodeSize := 4].
  
  	"C6.2.4 ADD (immediate) p761"
  	machineCode
  		at: 0 put: (self addrn: SP rd: SP imm: offset shiftBy12: false);
  		at: 4 put: 2r11010110010111110000000000000000 + (LR << 5).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeSubCqR (in category 'generate machine code - concretize') -----
  concretizeSubCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| constant reg offset |
  	constant := operands at: 0.
  	reg := operands at: 1.
  
  	self deny: reg = SP. "For now; how to add an immediate to the SP?"
  	self isPossiblyShiftableImm12: constant 
  		ifTrue:
  			[:shift|
  			"C6.2.314		SUBS (immediate)	C6-1321"
  			machineCode
  				at: 0
  				put: 2r111100010 << 23
  					+ (shift ifTrue: [constant >> 2 + (1 << 22)] ifFalse: [constant << 10])
  					+ (reg << 5)
  					+ reg.
+ 			^4]
- 			^machineCodeSize := 4]
  		ifFalse: [].
  	offset := self moveCw: constant intoR: RISCTempReg.
  	"C6.2.313	SUBS (extended register)		C6-1318"
  	machineCode
  				at: offset // 4
  				put: 2r11101011001
  					+ (RISCTempReg << 16)
  					+ (SXTX << 13)
  					+ (reg << 5)
  					+ reg.
+ 	^offset + 4!
- 	^machineCodeSize := offset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeSubRR (in category 'generate machine code - concretize') -----
  concretizeSubRR
  	"C6.2.313	SUBS (extended register)	C6-1318"
  	| destReg srcReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	self deny: SP = destReg.
  	machineCode
  		at: 0
  		put: 2r11101011001 << 21
  			+ (destReg << 16)
  			+ (UXTX << 13)
  			+ (srcReg << 5)
  			+ destReg.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
- 	<returnTypeC: #void>
  		 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[Literal]					-> [^self concretizeLiteral].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill32]					-> [^self concretizeFill32].
  		[Nop]					-> [^self concretizeNop].
  		"Control"
  		[Call]						-> [^self concretizeCall]. "call code within code space"
  		[CallFull]					-> [^self concretizeCallFull]. "call code anywhere in address space"
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeJumpFull]."jump within address space"
  		[JumpLong]				-> [^self concretizeConditionalJump: AL]."jumps witihn code space"
  		[JumpLongZero]			-> [^self concretizeConditionalJump: EQ].
  		[JumpLongNonZero]		-> [^self concretizeConditionalJump: NE].
  		[Jump]						-> [^self concretizeConditionalJump: AL].
  		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
  		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
  		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
  		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
  		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
  		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
  		[JumpCarry]				-> [^self concretizeConditionalJump: CS].
  		[JumpNoCarry]				-> [^self concretizeConditionalJump: CC].
  		[JumpLess]					-> [^self concretizeConditionalJump: LT].
  		[JumpGreaterOrEqual]		-> [^self concretizeConditionalJump: GE].
  		[JumpGreater]				-> [^self concretizeConditionalJump: GT].
  		[JumpLessOrEqual]			-> [^self concretizeConditionalJump: LE].
  		[JumpBelow]				-> [^self concretizeConditionalJump: CC]. "unsigned lower"
  		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CS]. "unsigned greater or equal"
  		[JumpAbove]				-> [^self concretizeConditionalJump: HI].
  		[JumpBelowOrEqual]		-> [^self concretizeConditionalJump: LS].
  		[JumpFPEqual]				-> [^self concretizeFPConditionalJump: EQ].
  		[JumpFPNotEqual]			-> [^self concretizeFPConditionalJump: NE].
  		[JumpFPLess]				-> [^self concretizeFPConditionalJump: LT].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeFPConditionalJump: GE].
  		[JumpFPGreater]			-> [^self concretizeFPConditionalJump: GT].
  		[JumpFPLessOrEqual]		-> [^self concretizeFPConditionalJump: LE].
  		[JumpFPOrdered]			-> [^self concretizeFPConditionalJump: VC].
  		[JumpFPUnordered]		-> [^self concretizeFPConditionalJump: VS].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]						-> [^self concretizeAddCqR].
  		[AndCqR]						-> [^self concretizeInvertibleDataOperationCqR: AndOpcode].
  		[AndCqRR]						-> [^self concretizeAndCqRDest: (operands at: 1)].
  		[CmpCqR]						-> [^self concretizeCmpCqR].
  		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
  		[SubCqR]						-> [^self concretizeSubCqR].
  		[TstCqR]						-> [^self concretizeAndCqRDest: XZR].
  		[XorCqR]						-> [^self concretizeInvertibleDataOperationCqR: XorOpcode].
  		[AddCwR]						-> [^self concretizeDataOperationCwR: AddOpcode].
  		[AndCwR]						-> [^self concretizeDataOperationCwR: AndOpcode].
  		[CmpCwR]						-> [^self concretizeDataOperationCwR: CmpOpcode].
  		[OrCwR]						-> [^self concretizeDataOperationCwR: OrOpcode].
  		[SubCwR]						-> [^self concretizeDataOperationCwR: SubOpcode].
  		[XorCwR]						-> [^self concretizeDataOperationCwR: XorOpcode].
  		[AddRR]						-> [^self concretizeAddRR].
  		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
  		[CmpRR]						-> [^self concretizeDataOperationRR: CmpOpcode].
  		[OrRR]							-> [^self concretizeDataOperationRR: OrOpcode].
  		[SubRR]						-> [^self concretizeSubRR].
  		[XorRR]							-> [^self concretizeDataOperationRR: XorOpcode].
  		[AddRdRd]						-> [^self concretizeAddRdRd].
  		[CmpRdRd]						-> [^self concretizeCmpRdRd].
  		[DivRdRd]						-> [^self concretizeDivRdRd].
  		[MulRdRd]						-> [^self concretizeMulRdRd].
  		[SubRdRd]						-> [^self concretizeSubRdRd].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]		-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		[ClzRR]							-> [^self concretizeClzRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR] 			-> [^self concretizeMoveAbR].
   		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]		-> [^self concretizeMoveMbrR].
  		[MoveRMbr]		-> [^self concretizeMoveRMbr].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		[ConvertRdR]		-> [^self concretizeConvertRdR].
  		[ConvertRRs]		-> [^self concretizeConvertRRs].
  		[ConvertRsR]		-> [^self concretizeConvertRsR].
  		[ConvertRsRd]		-> [^self concretizeConvertRsRd].
  		[ConvertRdRs]		-> [^self concretizeConvertRdRs].
  			
  		[SignExtend8RR]	-> [^self concretizeSignExtend8RR].
  		[SignExtend16RR]	-> [^self concretizeSignExtend16RR].
  		[SignExtend32RR]	-> [^self concretizeSignExtend32RR].
  		
  		[ZeroExtend8RR]	-> [^self concretizeZeroExtend8RR].
  		[ZeroExtend16RR]	-> [^self concretizeZeroExtend16RR].
+ 		[ZeroExtend32RR]	-> [^self concretizeZeroExtend32RR] }.
+ 
+ 	^0 "keep Slang happy"!
- 		[ZeroExtend32RR]	-> [^self concretizeZeroExtend32RR].}!

Item was changed:
  ----- Method: CogARMv8Compiler>>moveCw:intoR: (in category 'generate machine code - support') -----
  moveCw: constant intoR: destReg
  	"Emit a load of constant into destReg.  Answer the number of bytes of machine code
  	 generated. Literals are stored out-of-line; emit a LDR (literal) with the relevant offset."
  	 <var: 'constant' type: #usqInt>
  	<inline: true>
  	self deny: destReg = SP.
  	self assert: (cogit addressIsInCurrentCompilation: dependent address).
  	self assert: dependent address \\ 4 = 0.
  	self assert: (dependent address - address) abs < (1<<18).
  	"C6.2.131	LDR (literal)		C6-979"
  	machineCode
  		at: 0
  		put: 2r01011 << 27
  			+ (dependent address - address << 3 "5 - 2")
  			+ destReg.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogAbstractInstruction>>concretizeAt: (in category 'generate machine code') -----
  concretizeAt: actualAddress
  	"Generate concrete machine code for the instruction at actualAddress,
  	 setting machineCodeSize, and answer the following address."
  
  	address := actualAddress.
+ 	machineCodeSize := self dispatchConcretize.
- 	self dispatchConcretize.
  	self assert: (maxSize = nil or: [maxSize >= machineCodeSize]).
  	^actualAddress + machineCodeSize!

Item was changed:
  ----- Method: CogAbstractInstruction>>concretizeLabel (in category 'generate machine code') -----
  concretizeLabel
  	<inline: true>
  	<var: #dependentChain type: #'AbstractInstruction *'>
  	| dependentChain |
  	dependentChain := dependent.
  	[dependentChain isNil] whileFalse:
  		[dependentChain updateLabel: self.
  		 dependentChain := dependentChain dependent].
+ 	^0!
- 	^machineCodeSize := 0!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeAddCqR (in category 'generate machine code') -----
  concretizeAddCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 0 put: 16r83;
  			at: 1 put: (self mod: ModReg RM: reg RO: 0);
  			at: 2 put: (value bitAnd: 16rFF).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r05;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 0);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeAddCwR (in category 'generate machine code') -----
  concretizeAddCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r05;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 0);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeAddcCqR (in category 'generate machine code') -----
  concretizeAddcCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 0 put: 16r83;
  			at: 1 put: (self mod: ModReg RM: reg RO: 2);
  			at: 2 put: (value bitAnd: 16rFF).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r15;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 2);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeAddcRR (in category 'generate machine code') -----
  concretizeAddcRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"Assemble the ADC instruction"
  	| regLHS regRHS |
  	regLHS := operands at: 0.
  	regRHS := operands at: 1.
  	machineCode
  		at: 0 put: 16r13;
  		at: 1 put: (self mod: ModReg RM: regLHS RO: regRHS).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeAlignmentNops (in category 'generate machine code') -----
  concretizeAlignmentNops
  	<inline: true>
  	self flag: 'if performance is an issue generate longer nops'.
  	0 to: machineCodeSize - 1 do:
  		[:i|
+ 		machineCode at: i put: 16r90].
+ 	^machineCodeSize!
- 		machineCode at: i put: 16r90]!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeAndCqR (in category 'generate machine code') -----
  concretizeAndCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| mask reg |
  	mask := operands at: 0.
  	reg := operands at: 1.
  	(self isQuick: mask) ifTrue:
  		[machineCode
  			at: 0 put: 16r83;
  			at: 1 put: (self mod: ModReg RM: reg RO: 4);
  			at: 2 put: (mask bitAnd: 16rFF).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r25;
  			at: 1 put: (mask bitAnd: 16rFF);
  			at: 2 put: (mask >> 8 bitAnd: 16rFF);
  			at: 3 put: (mask >> 16 bitAnd: 16rFF);
  			at: 4 put: (mask >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 4);
  		at: 2 put: (mask bitAnd: 16rFF);
  		at: 3 put: (mask >> 8 bitAnd: 16rFF);
  		at: 4 put: (mask >> 16 bitAnd: 16rFF);
  		at: 5 put: (mask >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeAndCwR (in category 'generate machine code') -----
  concretizeAndCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r25;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r83;
  		at: 1 put: (self mod: ModReg RM: reg RO: 4);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeArithmeticShiftRightCqR (in category 'generate machine code') -----
  concretizeArithmeticShiftRightCqR
  	<inline: true>
  	| shiftCount reg |
  	shiftCount := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	shiftCount = 1 ifTrue:
  		[machineCode
  			at: 0 put: 16rD1;
  			at: 1 put: (self mod: ModReg RM: reg RO: 7).
+ 		^2].
- 		^machineCodeSize := 2].
  
  	machineCode
  		at: 0 put: 16rC1;
  		at: 1 put: (self mod: ModReg RM: reg RO: 7);
  		at: 2 put: shiftCount.
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeArithmeticShiftRightRR (in category 'generate machine code') -----
  concretizeArithmeticShiftRightRR
  	"On the x86 the only instructions that shift by the value of a
  	 register require the shift count to be  in %ecx.  So we may
  	 have to use swap instructions to get the count into %ecx."
  	<inline: true>
  	| shiftCountReg destReg regToShift |
  	shiftCountReg := operands at: 0.
  	destReg := operands at: 1.
  	shiftCountReg = ECX ifTrue:
  		[machineCode
  			at: 0 put: 16rD3;
  			at: 1 put: (self mod: ModReg RM: destReg RO: 7).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	regToShift := destReg == shiftCountReg
  					ifTrue: [ECX]
  					ifFalse: [destReg = ECX
  								ifTrue: [shiftCountReg]
  								ifFalse: [destReg]].
  	shiftCountReg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r90 + ECX; "XCHG EAX,ECX"
  			at: 1 put: 16rD3;			"SAR ECX,EAX"
  			at: 2 put: (self mod: ModReg RM: regToShift RO: 7);
  			at: 3 put: 16r90 + ECX. "XCHG EAX,ECX"
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16r87;		"XCHG E?X,ECX"
  		at: 1 put: (self mod: ModReg RM: ECX RO: shiftCountReg);
  		at: 2 put: 16rD3;		"SAR ECX,E!!X"
  		at: 3 put: (self mod: ModReg RM: regToShift RO: 7);
  		at: 4 put: 16r87;		"XCHG E?X,ECX"
  		at: 5 put: (self mod: ModReg RM: ECX RO: shiftCountReg).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeBSR (in category 'generate machine code') -----
  concretizeBSR
  	"Bit Scan Reverse
  	First operand is output register (dest)
  	Second operand is input register (mask)"
  	"BSR"
  	<inline: true>
  	| dest mask |
  	dest := operands at: 0.
  	mask := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rBD;
  		at: 2 put: (self mod: ModReg RM: dest RO: mask).
+ 	 ^3!
- 	 ^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCDQ (in category 'generate machine code') -----
  concretizeCDQ
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	machineCode at: 0 put: 16r99.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCLD (in category 'generate machine code') -----
  concretizeCLD
  	<inline: true>
  	machineCode at: 0 put: 16rFC.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCMPXCHGAwR (in category 'generate machine code') -----
  concretizeCMPXCHGAwR
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB1;
  		at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 3 put: (addressOperand bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 6 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCMPXCHGMwrR (in category 'generate machine code') -----
  concretizeCMPXCHGMwrR
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r0F;
  				at: 1 put: 16rB1;
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB1;
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB1;
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB1;
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCPUID (in category 'generate machine code') -----
  concretizeCPUID
  	<inline: true>
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rA2.
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCall (in category 'generate machine code') -----
  concretizeCall
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset |
  	self assert: (operands at: 0) ~= 0.
  	offset := (operands at: 0) signedIntFromLong - (address + 5) signedIntFromLong.
  	machineCode
  		at: 0 put: 16rE8;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8 bitAnd: 16rFF);
  		at: 3 put: (offset >> 16 bitAnd: 16rFF);
  		at: 4 put: (offset >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCallR (in category 'generate machine code') -----
  concretizeCallR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg |
  	"CmpRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rFF;
  		at: 1 put: (self mod: ModReg RM: reg RO: 2).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeClzRR (in category 'generate machine code') -----
  concretizeClzRR
  	"Count leading zeros
  	First operand is output (dest)
  	Second operand is input (mask)"
  	"LZCNT"
  	<inline: true>
  	| dest mask |
  	dest := operands at: 0.
  	mask := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16rBD;
  		at: 3 put: (self mod: ModReg RM: dest RO: mask).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCmpCqR (in category 'generate machine code') -----
  concretizeCmpCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 0 put: 16r83;
  			at: 1 put: (self mod: ModReg RM: reg RO: 7);
  			at: 2 put: (value bitAnd: 16rFF).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r3D;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 7);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCmpCwR (in category 'generate machine code') -----
  concretizeCmpCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r3D;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 7);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCmpRdRd (in category 'generate machine code') -----
  concretizeCmpRdRd
  	"Will get inlined into concretizeAt: switch.
  	 We use UCOMISD (see p 4-260 [2])"
  	<inline: true>
  	| regLHS regRHS |
  	"CmpRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode
  		at: 0 put: 16r66;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r2E;
  		at: 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeCmpRsRs (in category 'generate machine code') -----
  concretizeCmpRsRs
  	"Will get inlined into concretizeAt: switch.
  	 We use UCOMISS (see p 4-260 [2])"
  	<inline: true>
  	| regLHS regRHS |
  	"CmpRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16r2E;
  		at: 2 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConditionalJump: (in category 'generate machine code') -----
  concretizeConditionalJump: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| offset |
  	offset := self computeJumpTargetOffsetPlus: 2.
  	(machineCodeSize = 0 "size not determined because no sizeJump pass; generating initial trampolines"
  		ifTrue: [self isQuick: offset]
  		ifFalse: [machineCodeSize = 2]) ifTrue:
  		[machineCode
  			at: 0 put: 16r70 + conditionCode;
  			at: 1 put: (offset bitAnd: 16rFF).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	^self concretizeConditionalJumpLong: conditionCode!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConditionalJumpLong: (in category 'generate machine code') -----
  concretizeConditionalJumpLong: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| offset |
  	offset := self computeJumpTargetOffsetPlus: 6.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16r80 + conditionCode;
  		at: 2 put: (offset bitAnd: 16rFF);
  		at: 3 put: (offset >> 8 bitAnd: 16rFF);
  		at: 4 put: (offset >> 16 bitAnd: 16rFF);
  		at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConvertRRd (in category 'generate machine code') -----
  concretizeConvertRRd
  	"Will get inlined into concretizeAt: switch."
  	"CVTSI2D"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r2A;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConvertRRs (in category 'generate machine code') -----
  concretizeConvertRRs
  	"Will get inlined into concretizeAt: switch."
  	"CVTSI2SS"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r2A;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConvertRdR (in category 'generate machine code') -----
  concretizeConvertRdR
  	"Will get inlined into concretizeAt: switch."
  	"CVTSD2SI"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at:0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r2D;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConvertRdRs (in category 'generate machine code') -----
  concretizeConvertRdRs
  	"Will get inlined into concretizeAt: switch."
  	"CVTSD2SS"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r5A;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConvertRsR (in category 'generate machine code') -----
  concretizeConvertRsR
  	"Will get inlined into concretizeAt: switch."
  	"CVTSS2SI"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r2D;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeConvertRsRd (in category 'generate machine code') -----
  concretizeConvertRsRd
  	"Will get inlined into concretizeAt: switch."
  	"CVTSS2SD"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r5A;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeFENCE: (in category 'generate machine code') -----
  concretizeFENCE: regOpcode
  	<inline: true>
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rAE;
  		at: 2 put: (self mod: ModReg RM: 0 RO: regOpcode).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeFSTPD (in category 'generate machine code') -----
  concretizeFSTPD
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := 3.
  	offset := operands at: 0.
  	destReg := operands at: 1.
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			"FSTP dest"
  			[machineCode
  				at: 0 put: 16rDD;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 2 put: (offset bitAnd: 16rFF).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		"FSTP dest"
  		machineCode
  			at: 0 put: 16rDD;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 		^6].
- 		^machineCodeSize := 6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rDD;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 2 put: (self s: SIB1 i: 4 b: destReg);
  			at: 3 put: (offset bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16rDD;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 2 put: (self s: SIB1 i: 4 b: destReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeFSTPS (in category 'generate machine code') -----
  concretizeFSTPS
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := 3.
  	offset := operands at: 0.
  	destReg := operands at: 1.
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			"FSTP dest"
  			[machineCode
  				at: 0 put: 16rD9;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 2 put: (offset bitAnd: 16rFF).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		"FSTP dest"
  		machineCode
  			at: 0 put: 16rD9;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 		^6].
- 		^machineCodeSize := 6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rD9;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 2 put: (self s: SIB1 i: 4 b: destReg);
  			at: 3 put: (offset bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16rD9;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 2 put: (self s: SIB1 i: 4 b: destReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeFill32 (in category 'generate machine code') -----
  concretizeFill32
  	<inline: true>
  	| word |
  	<var: #word type: #'usqIntptr_t'>
  	word := operands at: 0.
  	machineCode at: 0 put: (word bitAnd: 16rFF).
  	machineCode at: 1 put: (word >> 8 bitAnd: 16rFF).
  	machineCode at: 2 put: (word >> 16 bitAnd: 16rFF).
  	machineCode at: 3 put: (word >> 24 bitAnd: 16rFF).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeIDIVR (in category 'generate machine code') -----
  concretizeIDIVR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regDivisor |
  	regDivisor := operands at: 0.
  	machineCode
  		at: 0 put: 16rF7;
  		at: 1 put: (self mod: ModReg RM: regDivisor RO: 7).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeJump (in category 'generate machine code') -----
  concretizeJump
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| jumpTarget offset |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	cogit assertSaneJumpTarget: jumpTarget.
  	(self isAnInstruction: jumpTarget) ifTrue:
  		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
  	self assert: jumpTarget ~= 0.
  	offset := jumpTarget signedIntFromLong - (address + 2) signedIntFromLong.
  	(machineCodeSize = 0 "size not determined because no sizeJump pass; generating initial trampolines"
  		ifTrue: [self isQuick: offset]
  		ifFalse: [machineCodeSize = 2]) ifTrue:
  		[machineCode
  			at: 0 put: 16rEB;
  			at: 1 put: (offset bitAnd: 16rFF).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	offset := jumpTarget signedIntFromLong - (address + 5) signedIntFromLong.
  	machineCode
  		at: 0 put: 16rE9;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8 bitAnd: 16rFF);
  		at: 3 put: (offset >> 16 bitAnd: 16rFF);
  		at: 4 put: (offset >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeJumpLong (in category 'generate machine code') -----
  concretizeJumpLong
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| jumpTarget offset |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	(self isAnInstruction: jumpTarget) ifTrue:
  		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
  	self assert: jumpTarget ~= 0.
  	offset := jumpTarget signedIntFromLong - (address + 5) signedIntFromLong.
  	machineCode
  		at: 0 put: 16rE9;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8 bitAnd: 16rFF);
  		at: 3 put: (offset >> 16 bitAnd: 16rFF);
  		at: 4 put: (offset >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeJumpR (in category 'generate machine code') -----
  concretizeJumpR
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rFF;
  		at: 1 put: (self mod: ModReg RM: reg RO: 4).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeLOCK (in category 'generate machine code') -----
  concretizeLOCK
  	<inline: true>
  	machineCode at: 0 put: 16rF0.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code') -----
  concretizeLoadEffectiveAddressMwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r8D;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 2 put: (offset bitAnd: 16rFF).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		machineCode
  			at: 0 put: 16r8D;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 		^6].
- 		^machineCodeSize := 6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r8D;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16r8D;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeLogicalShiftLeftCqR (in category 'generate machine code') -----
  concretizeLogicalShiftLeftCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	distance = 1 ifTrue:
  		[machineCode
  			at: 0 put: 16rD1;
  			at: 1 put: (self mod: ModReg RM: reg RO: 4).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	machineCode
  		at: 0 put: 16rC1;
  		at: 1 put: (self mod: ModReg RM: reg RO: 4);
  		at: 2 put: distance.
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeLogicalShiftLeftRR (in category 'generate machine code') -----
  concretizeLogicalShiftLeftRR
  	<inline: true>
  	"On the x86 the only instructions that shift by the value of a
  	 register require the shift count to be  in %ecx.  So we may
  	 have to use swap instructions to get the count into %ecx."
  	| shiftCountReg destReg regToShift |
  	shiftCountReg := operands at: 0.
  	destReg := operands at: 1.
  	shiftCountReg = ECX ifTrue:
  		[machineCode
  			at: 0 put: 16rD3;
  			at: 1 put: (self mod: ModReg RM: destReg RO: 4).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	regToShift := destReg == shiftCountReg
  					ifTrue: [ECX]
  					ifFalse: [destReg = ECX
  								ifTrue: [shiftCountReg]
  								ifFalse: [destReg]].
  	shiftCountReg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r90 + ECX; "XCHG EAX,ECX"
  			at: 1 put: 16rD3;			"SAR ECX,EAX"
  			at: 2 put: (self mod: ModReg RM: regToShift RO: 4);
  			at: 3 put: 16r90 + ECX. "XCHG EAX,ECX"
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16r87;		"XCHG E?X,ECX"
  		at: 1 put: (self mod: ModReg RM: ECX RO: shiftCountReg);
  		at: 2 put: 16rD3;		"SAR ECX,E!!X"
  		at: 3 put: (self mod: ModReg RM: regToShift RO: 4);
  		at: 4 put: 16r87;		"XCHG E?X,ECX"
  		at: 5 put: (self mod: ModReg RM: ECX RO: shiftCountReg).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeLogicalShiftRightCqR (in category 'generate machine code') -----
  concretizeLogicalShiftRightCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	distance = 1 ifTrue:
  		[machineCode
  			at: 0 put: 16rD1;
  			at: 1 put: (self mod: ModReg RM: reg RO: 5).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	machineCode
  		at: 0 put: 16rC1;
  		at: 1 put: (self mod: ModReg RM: reg RO: 5);
  		at: 2 put: distance.
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMOVSB (in category 'generate machine code') -----
  concretizeMOVSB
  	<inline: true>
  	machineCode at: 0 put: 16rA4.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMOVSD (in category 'generate machine code') -----
  concretizeMOVSD
  	<inline: true>
  	machineCode at: 0 put: 16rA5.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveAbR (in category 'generate machine code') -----
  concretizeMoveAbR
  	"N.B. we zero-extend because we state byteReadsZeroExtend."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB6;
  		at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 3 put: (addressOperand bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 6 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveAwR (in category 'generate machine code') -----
  concretizeMoveAwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg := operands at: 1.
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16rA1;
  			at: 1 put: (addressOperand bitAnd: 16rFF);
  			at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
  			at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
  			at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 			^5].
- 			^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r8B;
  		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 2 put: (addressOperand bitAnd: 16rFF);
  		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveCqR (in category 'generate machine code') -----
  concretizeMoveCqR
  	"Will get inlined into concretizeAt: switch.
  	 Note that for quick constants, xor reg,reg, movq r8 may be shorter.  But
  	 we don't consider it worthwhile and so just provide concretizeMoveCwR."
  	<inline: true>
  	| reg |
  	(operands at: 0) ~= 0 ifTrue:
  		[^self concretizeMoveCwR].
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: 16r31;
  		at: 1 put: (self mod: ModReg RM: reg RO: reg).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveCwR (in category 'generate machine code') -----
  concretizeMoveCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value |
  	value := operands at: 0.
  	machineCode
  		at: 0 put: 16rB8 + (operands at: 1);
  		at: 1 put: (value bitAnd: 16rFF);
  		at: 2 put: (value >> 8 bitAnd: 16rFF);
  		at: 3 put: (value >> 16 bitAnd: 16rFF);
  		at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveM16rR (in category 'generate machine code') -----
  concretizeMoveM16rR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r0F;
  				at: 1 put: 16rB7;
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB7;
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB7;
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB7;
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveM32rRs (in category 'generate machine code') -----
  concretizeMoveM32rRs
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16rF3;
  				at: 1 put: 16r0F;
  				at: 2 put: 16r10;
  				at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 4 put: (offset bitAnd: 16rFF).
+ 			 ^5].
- 			 ^machineCodeSize := 5].
  		machineCode
  			at: 0 put: 16rF3;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r10;
  			at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 4 put: (offset bitAnd: 16rFF);
  			at: 5 put: (offset >> 8 bitAnd: 16rFF);
  			at: 6 put: (offset >> 16 bitAnd: 16rFF);
  			at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 		^8].
- 		^machineCodeSize := 8].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rF3;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r10;
  			at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 5 put: (offset bitAnd: 16rFF).
+ 		 ^6].
- 		 ^machineCodeSize := 6].
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r10;
  		at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 5 put: (offset bitAnd: 16rFF);
  		at: 6 put: (offset >> 8 bitAnd: 16rFF);
  		at: 7 put: (offset >> 16 bitAnd: 16rFF);
  		at: 8 put: (offset >> 24 bitAnd: 16rFF).
+ 	^9!
- 	^machineCodeSize := 9!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveM64rRd (in category 'generate machine code') -----
  concretizeMoveM64rRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16rF2;
  				at: 1 put: 16r0F;
  				at: 2 put: 16r10;
  				at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 4 put: (offset bitAnd: 16rFF).
+ 			 ^5].
- 			 ^machineCodeSize := 5].
  		machineCode
  			at: 0 put: 16rF2;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r10;
  			at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 4 put: (offset bitAnd: 16rFF);
  			at: 5 put: (offset >> 8 bitAnd: 16rFF);
  			at: 6 put: (offset >> 16 bitAnd: 16rFF);
  			at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 		^8].
- 		^machineCodeSize := 8].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rF2;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r10;
  			at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 5 put: (offset bitAnd: 16rFF).
+ 		 ^6].
- 		 ^machineCodeSize := 6].
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r10;
  		at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 5 put: (offset bitAnd: 16rFF);
  		at: 6 put: (offset >> 8 bitAnd: 16rFF);
  		at: 7 put: (offset >> 16 bitAnd: 16rFF);
  		at: 8 put: (offset >> 24 bitAnd: 16rFF).
+ 	^9!
- 	^machineCodeSize := 9!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveM8rR (in category 'generate machine code') -----
  concretizeMoveM8rR
  	"Will get inlined into concretizeAt: switch."
  	"movzwl"
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r0F;
  				at: 1 put: 16rB6;
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB6;
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB6;
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB6;
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveMbrR (in category 'generate machine code') -----
  concretizeMoveMbrR
  	"N.B. we zero-extend because we state byteReadsZeroExtend."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r0f;
  				at: 1 put: 16rb6;
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 0 put: 16r0f;
  			at: 1 put: 16rb6;
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r0f;
  			at: 1 put: 16rb6;
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r0f;
  		at: 1 put: 16rb6;
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveMwrR (in category 'generate machine code') -----
  concretizeMoveMwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(offset = 0 and: [srcReg ~= EBP]) ifTrue:
  			[machineCode
  				at: 0 put: 16r8B;
  				at: 1 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^2].
- 			 ^machineCodeSize := 2].
  		(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r8B;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 2 put: (offset bitAnd: 16rFF).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		machineCode
  			at: 0 put: 16r8B;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 		^6].
- 		^machineCodeSize := 6].
  	"ESP:"
  	offset = 0 ifTrue:
  		[machineCode
  			at: 0 put: 16r8B;
  			at: 1 put: (self mod: ModRegInd RM: srcReg RO: destReg);
  			at: 2 put: (self s: SIB1 i: 4 b: srcReg).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r8B;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16r8B;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRAb (in category 'generate machine code') -----
  concretizeMoveRAb
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg |
  	reg := operands at: 0.
  	addressOperand := operands at: 1.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16rA2;
  			at: 1 put: (addressOperand bitAnd: 16rFF);
  			at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
  			at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
  			at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 			^5].
- 			^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r88;
  		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 2 put: (addressOperand bitAnd: 16rFF);
  		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRAw (in category 'generate machine code') -----
  concretizeMoveRAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg |
  	reg := operands at: 0.
  	addressOperand := operands at: 1.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16rA3;
  			at: 1 put: (addressOperand bitAnd: 16rFF);
  			at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
  			at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
  			at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 			^5].
- 			^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r89;
  		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 2 put: (addressOperand bitAnd: 16rFF);
  		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRM16r (in category 'generate machine code') -----
  concretizeMoveRM16r
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 1.
  	srcReg := operands at: 0.
  	destReg := operands at: 2.
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r66;
  				at: 1 put: 16r89;
  				at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 0 put: 16r66;
  			at: 1 put: 16r89;
  			at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	machineCode
  		at: 0 put: 16r66;
  		at: 1 put: 16r89;
  		at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 3 put: (self s: SIB1 i: 4 b: destReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRMbr (in category 'generate machine code') -----
  concretizeMoveRMbr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 1.
  	srcReg := operands at: 0.
  	destReg := operands at: 2.
  	srcReg >= 4 ifTrue: [self error: 'invalid register'].
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r88;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 2 put: (offset bitAnd: 16rFF).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		machineCode
  			at: 0 put: 16r88;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 		^6].
- 		^machineCodeSize := 6].
  	machineCode
  		at: 0 put: 16r88;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 2 put: (self s: SIB1 i: 4 b: destReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRMwr (in category 'generate machine code') -----
  concretizeMoveRMwr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	destReg ~= ESP ifTrue:
  		[(offset = 0 and: [destReg ~= EBP]) ifTrue:
  			[machineCode
  				at: 0 put: 16r89;
  				at: 1 put: (self mod: ModRegInd RM: destReg RO: srcReg).
+ 			 ^2].
- 			 ^machineCodeSize := 2].
  		 (self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r89;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 2 put: (offset bitAnd: 16rFF).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		machineCode
  			at: 0 put: 16r89;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 		^6].
- 		^machineCodeSize := 6].
  	"ESP:"
  	offset = 0 ifTrue:
  		[machineCode
  			at: 0 put: 16r89;
  			at: 1 put: (self mod: ModRegInd RM: destReg RO: srcReg);
  			at: 2 put: (self s: SIB1 i: 4 b: destReg).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r89;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 2 put: (self s: SIB1 i: 4 b: destReg);
  			at: 3 put: (offset bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16r89;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 2 put: (self s: SIB1 i: 4 b: destReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRXbrR (in category 'generate machine code') -----
  concretizeMoveRXbrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| src index base swapreg mcIdx |
  	src := operands at: 0.
  	index := operands at: 1.
  	base := operands at: 2.
  	mcIdx := 0.
  	swapreg := NoReg.
  	src >= 4 ifTrue: "x86 allows movb %rl, mem only with %al, %bl, %cl, %dl, so swap with the first one that isn't used."
  		[swapreg := src.
  		 index = EAX ifTrue: [index := swapreg].
  		 base = EAX ifTrue: [base := swapreg].
  		 src := EAX. 
  		 mcIdx := 1.
  		 machineCode at: 0 put: 16r90 + swapreg].
  	base ~= EBP ifTrue:
  		[machineCode
  			at: mcIdx + 0 put: 16r88;
  			at: mcIdx + 1 put: (self mod: ModRegInd RM: 4 RO: src);
  			at: mcIdx + 2 put: (self s: SIB1 i: index b: base).
  		 swapreg ~= NoReg ifTrue:
  			[machineCode at: mcIdx + 3 put: 16r90 + swapreg].
+ 		 ^3 + (2 * mcIdx)].
- 		 ^machineCodeSize := 3 + (2 * mcIdx)].
  	machineCode
  		at: mcIdx + 0 put: 16r88;
  		at: mcIdx + 1 put: (self mod: ModRegRegDisp8 RM: 4 RO: src);
  		at: mcIdx + 2 put: (self s: SIB1 i: index b: base);
  		at: mcIdx + 3 put: 0.
  	swapreg ~= NoReg ifTrue:
  		[machineCode at: mcIdx + 4 put: 16r90 + swapreg].
+ 	 ^4 + (2 * mcIdx)!
- 	 ^machineCodeSize := 4 + (2 * mcIdx)!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRXwrR (in category 'generate machine code') -----
  concretizeMoveRXwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| index base src |
  	src := operands at: 0.
  	index := operands at: 1.
  	base := operands at: 2.
  	base ~= EBP ifTrue:
  		[machineCode
  			at: 0 put: 16r89;
  			at: 1 put: (self mod: ModRegInd RM: 4 RO: src);
  			at: 2 put: (self s: SIB4 i: index b: base).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	machineCode
  		at: 0 put: 16r89;
  		at: 1 put: (self mod: ModRegRegDisp8 RM: 4 RO: src);
  		at: 2 put: (self s: SIB4 i: index b: base);
  		at: 3 put: 0.
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRdM64r (in category 'generate machine code') -----
  concretizeMoveRdM64r
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16rF2;
  				at: 1 put: 16r0F;
  				at: 2 put: 16r11;
  				at: 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 4 put: (offset bitAnd: 16rFF).
+ 			 ^5].
- 			 ^machineCodeSize := 5].
  		machineCode
  			at: 0 put: 16rF2;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r11;
  			at: 3 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF);
  			at: 5 put: (offset >> 8 bitAnd: 16rFF);
  			at: 6 put: (offset >> 16 bitAnd: 16rFF);
  			at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 		^8].
- 		^machineCodeSize := 8].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rF2;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r11;
  			at: 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 4 put: (self s: SIB1 i: 4 b: destReg);
  			at: 5 put: (offset bitAnd: 16rFF).
+ 		 ^6].
- 		 ^machineCodeSize := 6].
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r11;
  		at: 3 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 4 put: (self s: SIB1 i: 4 b: destReg);
  		at: 5 put: (offset bitAnd: 16rFF);
  		at: 6 put: (offset >> 8 bitAnd: 16rFF);
  		at: 7 put: (offset >> 16 bitAnd: 16rFF);
  		at: 8 put: (offset >> 24 bitAnd: 16rFF).
+ 	^9!
- 	^machineCodeSize := 9!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRdRd (in category 'generate machine code') -----
  concretizeMoveRdRd
  	"Will get inlined into concretizeAt: switch."
  	"MOVSD"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r11;
  		at: 3 put: (self mod: ModReg RM: destReg RO: srcReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRsM32r (in category 'generate machine code') -----
  concretizeMoveRsM32r
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			"MOVSD destReg, srcReg"
  			[machineCode
  				at: 0 put: 16rF3;
  				at: 1 put: 16r0F;
  				at: 2 put: 16r11;
  				at: 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 4 put: (offset bitAnd: 16rFF).
+ 			 ^5].
- 			 ^machineCodeSize := 5].
  		"MOVSD destReg, srcReg"
  		machineCode
  			at: 0 put: 16rF3;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r11;
  			at: 3 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF);
  			at: 5 put: (offset >> 8 bitAnd: 16rFF);
  			at: 6 put: (offset >> 16 bitAnd: 16rFF);
  			at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 		^8].
- 		^machineCodeSize := 8].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rF3;
  			at: 1 put: 16r0F;
  			at: 2 put: 16r11;
  			at: 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 4 put: (self s: SIB1 i: 4 b: destReg);
  			at: 5 put: (offset bitAnd: 16rFF).
+ 		 ^6].
- 		 ^machineCodeSize := 6].
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r11;
  		at: 3 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 4 put: (self s: SIB1 i: 4 b: destReg);
  		at: 5 put: (offset bitAnd: 16rFF);
  		at: 6 put: (offset >> 8 bitAnd: 16rFF);
  		at: 7 put: (offset >> 16 bitAnd: 16rFF);
  		at: 8 put: (offset >> 24 bitAnd: 16rFF).
+ 	^9!
- 	^machineCodeSize := 9!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRsRs (in category 'generate machine code') -----
  concretizeMoveRsRs
  	"Will get inlined into concretizeAt: switch."
  	"MOVSS"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r11;
  		at: 3 put: (self mod: ModReg RM: destReg RO: srcReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveXbrRR (in category 'generate machine code') -----
  concretizeMoveXbrRR
  	"N.B. we zero-extend because we state byteReadsZeroExtend."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| index base dest |
  	index := operands at: 0.
  	base := operands at: 1.
  	dest := operands at: 2.
  	base ~= EBP ifTrue:
  		[machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB6;
  			at: 2 put: (self mod: ModRegInd RM: 4 RO: dest);
  			at: 3 put: (self s: SIB1 i: index b: base).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB6;
  		at: 2 put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
  		at: 3 put: (self s: SIB1 i: index b: base);
  		at: 4 put: 0.
+ 	 ^5!
- 	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveXwrRR (in category 'generate machine code') -----
  concretizeMoveXwrRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| index base dest |
  	index := operands at: 0.
  	base := operands at: 1.
  	dest := operands at: 2.
  	base ~= EBP ifTrue:
  		[machineCode
  			at: 0 put: 16r8B;
  			at: 1 put: (self mod: ModRegInd RM: 4 RO: dest);
  			at: 2 put: (self s: SIB4 i: index b: base).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	machineCode
  		at: 0 put: 16r8B;
  		at: 1 put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
  		at: 2 put: (self s: SIB4 i: index b: base);
  		at: 3 put: 0.
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMulRR (in category 'generate machine code') -----
  concretizeMulRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg1 reg2 |
  	reg1 := operands at: 0.
  	reg2 := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rAF;
  		at: 2 put: (self mod: ModReg RM: reg1 RO: reg2).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeNegateR (in category 'generate machine code') -----
  concretizeNegateR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rF7;
  		at: 1 put: (self mod: ModReg RM: reg RO: 3).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeNop (in category 'generate machine code') -----
  concretizeNop
  	<inline: true>
  	machineCode at: 0 put: 16r90.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeNotR (in category 'generate machine code') -----
  concretizeNotR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rF7;
  		at: 1 put: (self mod: ModReg RM: reg RO: 2).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeOpRR: (in category 'generate machine code') -----
  concretizeOpRR: x86opcode
  	| regLHS regRHS |
  	regLHS := operands at: 0.
  	regRHS := operands at: 1.
  	machineCode
  		at: 0 put: x86opcode;
  		at: 1 put: (self mod: ModReg RM: regLHS RO: regRHS).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeOrCqR (in category 'generate machine code') -----
  concretizeOrCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| mask reg |
  	mask := operands at: 0.
  	reg := operands at: 1.
  	(self isQuick: mask) ifTrue:
  		[machineCode
  			at: 0 put: 16r83;
  			at: 1 put: (self mod: ModReg RM: reg RO: 1);
  			at: 2 put: (mask bitAnd: 16rFF).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r0D;
  			at: 1 put: (mask bitAnd: 16rFF);
  			at: 2 put: (mask >> 8 bitAnd: 16rFF);
  			at: 3 put: (mask >> 16 bitAnd: 16rFF);
  			at: 4 put: (mask >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 1);
  		at: 2 put: (mask bitAnd: 16rFF);
  		at: 3 put: (mask >> 8 bitAnd: 16rFF);
  		at: 4 put: (mask >> 16 bitAnd: 16rFF);
  		at: 5 put: (mask >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeOrCwR (in category 'generate machine code') -----
  concretizeOrCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r0D;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r83;
  		at: 1 put: (self mod: ModReg RM: reg RO: 1);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizePopR (in category 'generate machine code') -----
  concretizePopR
  	<inline: true>
  	machineCode at: 0 put: 16r58 + (operands at: 0).
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizePrefetchAw (in category 'generate machine code') -----
  concretizePrefetchAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand |
  	"Note that maxSize has been set to 7 or 0 in computeMaximumSize whether hasSSEInstructions or not"
  	maxSize > 0 ifTrue:
  		[addressOperand := operands at: 0.
  		 machineCode
  			at: 0 put: 16r0f;
  			at: 1 put: 16r18;
  			at: 2 put: (self mod: 0 RM: 5 RO: 1); "prefetch0, prefetch using the T0 temporal data hint"
  			at: 3 put: (addressOperand bitAnd: 16rFF);
  			at: 4 put: (addressOperand >> 8 bitAnd: 16rFF);
  			at: 5 put: (addressOperand >> 16 bitAnd: 16rFF);
  			at: 6 put: (addressOperand >> 24 bitAnd: 16rFF)].
+ 	^maxSize!
- 	^machineCodeSize := maxSize!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizePushCq (in category 'generate machine code') -----
  concretizePushCq
  	<inline: true>
  	| value |
  	value := operands at: 0.
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 0 put: 16r6A;
  			at: 1 put: (value bitAnd: 16rFF).
+ 		^2].
- 		^machineCodeSize := 2].
  	machineCode
  		at: 0 put: 16r68;
  		at: 1 put: (value bitAnd: 16rFF);
  		at: 2 put: (value >> 8 bitAnd: 16rFF);
  		at: 3 put: (value >> 16 bitAnd: 16rFF);
  		at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizePushCw (in category 'generate machine code') -----
  concretizePushCw
  	<inline: true>
  	| value |
  	value := operands at: 0.
  	machineCode
  		at: 0 put: 16r68;
  		at: 1 put: (value bitAnd: 16rFF);
  		at: 2 put: (value >> 8 bitAnd: 16rFF);
  		at: 3 put: (value >> 16 bitAnd: 16rFF);
  		at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizePushR (in category 'generate machine code') -----
  concretizePushR
  	<inline: true>
  	machineCode at: 0 put: 16r50 + (operands at: 0).
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeREP (in category 'generate machine code') -----
  concretizeREP
  	<inline: true>
  	machineCode at: 0 put: 16rF3.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeRetN (in category 'generate machine code') -----
  concretizeRetN
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset |
  	offset := operands at: 0.
  	offset = 0 ifTrue:
  		[machineCode at: 0 put: 16rC3.
+ 		^1].
- 		^machineCodeSize := 1].
  	machineCode
  		at: 0 put: 16rC2;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeReverseOpRR: (in category 'generate machine code') -----
  concretizeReverseOpRR: x86opcode
  	| regLHS regRHS |
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode
  		at: 0 put: x86opcode;
  		at: 1 put: (self mod: ModReg RM: regLHS RO: regRHS).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSEE2OpRdRd: (in category 'generate machine code') -----
  concretizeSEE2OpRdRd: opCode
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS |
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: opCode;
  		at: 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSEEOpRsRs: (in category 'generate machine code') -----
  concretizeSEEOpRsRs: opCode
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS |
  	regRHS := self operands at: 0.
  	regLHS := self operands at: 1.
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: opCode;
  		at: 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSignExtend16RR (in category 'generate machine code') -----
  concretizeSignExtend16RR
  	"Will get inlined into concretizeAt: switch."
  	"movswl"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rBF;
  		at: 2 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 3!
- 	^ machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSignExtend8RR (in category 'generate machine code') -----
  concretizeSignExtend8RR
  	"Will get inlined into concretizeAt: switch."
  	"movsbl"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rBE;
  		at: 2 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 3!
- 	^ machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSqrtRd (in category 'generate machine code') -----
  concretizeSqrtRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r51;
  		at: 3 put: (self mod: ModReg RM: reg RO: reg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSqrtRs (in category 'generate machine code') -----
  concretizeSqrtRs
  	"Will get inlined into concretizeAt: switch."
  	"SRTSS"
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rF3;
  		at: 1 put: 16r0F;
  		at: 2 put: 16r51;
  		at: 3 put: (self mod: ModReg RM: reg RO: reg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeStop (in category 'generate machine code') -----
  concretizeStop
  	<inline: true>
  	machineCode at: 0 put: 16rCC.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSubCqR (in category 'generate machine code') -----
  concretizeSubCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 0 put: 16r83;
  			at: 1 put: (self mod: ModReg RM: reg RO: 5);
  			at: 2 put: (value bitAnd: 16rFF).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r2D;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 5);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSubCwR (in category 'generate machine code') -----
  concretizeSubCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r2D;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 5);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeSubbRR (in category 'generate machine code') -----
  concretizeSubbRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"Assemble the SBB instruction"
  	| regLHS regRHS |
  	regLHS := operands at: 0.
  	regRHS := operands at: 1.
  	machineCode
  		at: 0 put: 16r1B;
  		at: 1 put: (self mod: ModReg RM: regLHS RO: regRHS).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeTstCqR (in category 'generate machine code') -----
  concretizeTstCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| mask reg |
  	mask := operands at: 0.
  	reg := operands at: 1.
  	((self isQuick: mask) and: [reg < 4]) ifTrue:
  		[machineCode
  			at: 0 put: 16rF6;
  			at: 1 put: (self mod: ModReg RM: reg RO: 0);
  			at: 2 put: (mask bitAnd: 16rFF).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16rA9;
  			at: 1 put: (mask bitAnd: 16rFF);
  			at: 2 put: (mask >> 8 bitAnd: 16rFF);
  			at: 3 put: (mask >> 16 bitAnd: 16rFF);
  			at: 4 put: (mask >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16rF7;
  		at: 1 put: (self mod: ModReg RM: reg RO: 0);
  		at: 2 put: (mask bitAnd: 16rFF);
  		at: 3 put: (mask >> 8 bitAnd: 16rFF);
  		at: 4 put: (mask >> 16 bitAnd: 16rFF);
  		at: 5 put: (mask >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeXCHGAwR (in category 'generate machine code') -----
  concretizeXCHGAwR
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: 16r87;
  		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 2 put: (addressOperand bitAnd: 16rFF);
  		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeXCHGMwrR (in category 'generate machine code') -----
  concretizeXCHGMwrR
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r87;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 2 put: (offset bitAnd: 16rFF).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		machineCode
  			at: 0 put: 16r87;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 		^6].
- 		^machineCodeSize := 6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r87;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 0 put: 16r87;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeXCHGRR (in category 'generate machine code') -----
  concretizeXCHGRR
  	<inline: true>
  	| reg1 reg2 |
  	reg1 := operands at: 0.
  	reg2 := operands at: 1.
  	reg2 = EAX ifTrue:
  		[reg2 := reg1.
  		 reg1 := EAX].
  	reg1 = EAX ifTrue:
  		[machineCode at: 0 put: 16r90 + reg2.
+ 		 ^1].
- 		 ^machineCodeSize := 1].
  	machineCode
  		at: 0 put: 16r87;
  		at: 1 put: (self mod: ModReg RM: reg1 RO: reg2).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeXorCwR (in category 'generate machine code') -----
  concretizeXorCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16r35;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r81;
  		at: 1 put: (self mod: ModReg RM: reg RO: 6);
  		at: 2 put: (value bitAnd: 16rFF);
  		at: 3 put: (value >> 8 bitAnd: 16rFF);
  		at: 4 put: (value >> 16 bitAnd: 16rFF);
  		at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^6!
- 	 ^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeXorRdRd (in category 'generate machine code') -----
  concretizeXorRdRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS |
  	regRHS := self operands at: 0.
  	regLHS := self operands at: 1.
  	machineCode
  		at: 0 put: 16r66;
  		at: 1 put: 16r0f;
  		at: 2 put: 16r57;
  		at: 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeXorRsRs (in category 'generate machine code') -----
  concretizeXorRsRs
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS |
  	regRHS := self operands at: 0.
  	regLHS := self operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16r57;
  		at: 2 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeZeroExtend16RR (in category 'generate machine code') -----
  concretizeZeroExtend16RR
  	"Will get inlined into concretizeAt: switch."
  	"movzwl"
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB7;
  		at: 2 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 3!
- 	^ machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeZeroExtend8RR (in category 'generate machine code') -----
  concretizeZeroExtend8RR
  	"Will get inlined into concretizeAt: switch."
  	"movzbl"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB6;
  		at: 2 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 3!
- 	^ machineCodeSize := 3!

Item was changed:
  ----- Method: CogIA32Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
- 	<returnTypeC: #void>
  	opcode >= CDQ ifTrue:
  		[^self dispatchConcretizeProcessorSpecific].
+ 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill32]				-> [^self concretizeFill32].
  		[Nop]				-> [^self concretizeNop].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallR]					-> [^self concretizeCallR].
  		[CallFull]				-> [^self concretizeCall].
  		[JumpR]				-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpLong].
  		[JumpLong]			-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeAddCwR].
  		[AddRR]					-> [^self concretizeOpRR: 16r03].
  		[AddcRR]					-> [^self concretizeAddcRR].
  		[AddcCqR]					-> [^self concretizeAddcCqR].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AddRsRs]					-> [^self concretizeSEEOpRsRs: 16r58].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[AndRR]					-> [^self concretizeOpRR: 16r23].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[CmpRR]					-> [^self concretizeReverseOpRR: 16r39].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[CmpRsRs]					-> [^self concretizeCmpRsRs].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[DivRsRs]					-> [^self concretizeSEEOpRsRs: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[MulRsRs]					-> [^self concretizeSEEOpRsRs: 16r59].
  		[OrCqR]					-> [^self concretizeOrCqR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[OrRR]						-> [^self concretizeOpRR: 16r0B].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[SubRR]					-> [^self concretizeOpRR: 16r2B].
  		[SubbRR]					-> [^self concretizeSubbRR].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SubRsRs]					-> [^self concretizeSEEOpRsRs: 16r5C].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[SqrtRs]						-> [^self concretizeSqrtRs].
  		[XorCwR]						-> [^self concretizeXorCwR].
  		[XorRR]							-> [^self concretizeOpRR: 16r33].
  		[XorRdRd]						-> [^self concretizeXorRdRd].
  		[XorRsRs]						-> [^self concretizeXorRsRs].
  		[NegateR]						-> [^self concretizeNegateR].
  		[NotR]							-> [^self concretizeNotR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]		-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[ClzRR]						-> [^self concretizeClzRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeReverseOpRR: 16r89].
  		[MoveRdRd]		-> [^self concretizeMoveRdRd].
  		[MoveRsRs]			-> [^self concretizeMoveRsRs].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]		-> [^self concretizeMoveMbrR].
  		[MoveRMbr]		-> [^self concretizeMoveRMbr].
  		[MoveRM8r]		-> [^self concretizeMoveRMbr].
  		[MoveM8rR]		-> [^self concretizeMoveM8rR].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM32rR]		-> [^self concretizeMoveMwrR].
  		[MoveRM32r]		-> [^self concretizeMoveRMwr].
  		[MoveM32rRs]		-> [^self concretizeMoveM32rRs].
  		[MoveRsM32r]		-> [^self concretizeMoveRsM32r].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		[ConvertRdR]		-> [^self concretizeConvertRdR].
  		
  		[ConvertRsRd]		-> [^self concretizeConvertRsRd].
  		[ConvertRdRs]		-> [^self concretizeConvertRdRs].
  		[ConvertRsR]		-> [^self concretizeConvertRsR].
  		[ConvertRRs]		-> [^self concretizeConvertRRs].
  			
  		[SignExtend8RR]		-> [^self concretizeSignExtend8RR].
  		[SignExtend16RR]		-> [^self concretizeSignExtend16RR].
  		
  		[ZeroExtend8RR]		-> [^self concretizeZeroExtend8RR].
+ 		[ZeroExtend16RR]		-> [^self concretizeZeroExtend16RR] }.
+ 
+ 	^0 "keep Slang happy"!
- 		[ZeroExtend16RR]		-> [^self concretizeZeroExtend16RR].}!

Item was changed:
  ----- Method: CogIA32Compiler>>dispatchConcretizeProcessorSpecific (in category 'generate machine code') -----
  dispatchConcretizeProcessorSpecific
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is part of the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the number of literals limits in the SqueakV3 (blue book derived)
  	 bytecode set."
- 	<returnTypeC: #void>
  	opcode caseOf: {
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
  		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
  		[LFENCE]				-> [^self concretizeFENCE: 5].
  		[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7].
  		[LOCK]					-> [^self concretizeLOCK].
  		[XCHGAwR]				-> [^self concretizeXCHGAwR].
  		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		[FSTPS]					-> [^self concretizeFSTPS].
  		[FSTPD]				-> [^self concretizeFSTPD].
  		[REP]					-> [^self concretizeREP].
  		[CLD]					-> [^self concretizeCLD].
  		[MOVSB]				-> [^self concretizeMOVSB].
  		[MOVSD]				-> [^self concretizeMOVSD].
  		[BSR]					-> [^self concretizeBSR].
  	}!

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler>>concretizeArithCwR: (in category 'generate machine code') -----
  concretizeArithCwR: x64opcode
  	| value reg reverse |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reverse := x64opcode = 16r85 or: [x64opcode = 16r39]. "Tst & Cmp; backwards"
  	machineCode
  		at:  0 put: (self rexR: RISCTempReg x: 0 b: RISCTempReg);
  		at:  1 put: 16rB8 + (RISCTempReg bitAnd: 7);
  		at:  2 put: (value bitAnd: 16rFF);
  		at:  3 put: (value >> 8 bitAnd: 16rFF);
  		at:  4 put: (value >> 16 bitAnd: 16rFF);
  		at:  5 put: (value >> 24 bitAnd: 16rFF);
  		at:  6 put: (value >> 32 bitAnd: 16rFF);
  		at:  7 put: (value >> 40 bitAnd: 16rFF);
  		at:  8 put: (value >> 48 bitAnd: 16rFF);
  		at:  9 put: (value >> 56 bitAnd: 16rFF);
  		at: 10 put: (reverse
  					ifTrue: [self rexR: RISCTempReg x: 0 b: reg]
  					ifFalse: [self rexR: reg x: 0 b: RISCTempReg]);
  		at: 11 put: x64opcode;
  		at: 12 put: (reverse
  					ifTrue: [self mod: ModReg RM: reg RO: RISCTempReg]
  					ifFalse: [self mod: ModReg RM: RISCTempReg RO: reg]).
  	self assert: (machineCode at: 12) > 16r90. "See literalBeforeFollowingAddress:"
+ 	^13!
- 	^machineCodeSize := 13!

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler>>concretizeMoveCwR (in category 'generate machine code') -----
  concretizeMoveCwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg offset |
  	value := operands at: 0.
  	reg := operands at: 1.
  	(self isAnInstruction: (cogit cCoerceSimple: value to: #'AbstractInstruction *')) ifTrue:
  		[value := (cogit cCoerceSimple: value to: #'AbstractInstruction *') address].
  	(cogit addressIsInCurrentCompilation: value) ifTrue:
  		[offset := value - (address + 7).
  		 machineCode
  			at: 0 put: (self rexR: reg x: 0 b: 0);
  			at: 1 put: 16r8D; "LoadEffectiveAddress"
  			at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	machineCode
  		at:  0 put: (self rexR: 0 x: 0 b: reg);
  		at:  1 put: 16rB8 + (reg bitAnd: 7);
  		at:  2 put: (value bitAnd: 16rFF);
  		at:  3 put: (value >> 8 bitAnd: 16rFF);
  		at:  4 put: (value >> 16 bitAnd: 16rFF);
  		at:  5 put: (value >> 24 bitAnd: 16rFF);
  		at:  6 put: (value >> 32 bitAnd: 16rFF);
  		at:  7 put: (value >> 40 bitAnd: 16rFF);
  		at:  8 put: (value >> 48 bitAnd: 16rFF);
  		at:  9 put: (value >> 56 bitAnd: 16rFF).
  	"Add a nop to disambiguate between MoveCwR/PushCw and ArithCwR, which ends with a (self mod: ModReg RM: 0 RO: 0)"
  	machineCode at: 10 put: 16r90.
+ 	^11!
- 	^machineCodeSize := 11!

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler>>concretizePushCw (in category 'generate machine code') -----
  concretizePushCw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value offset |
  	value := operands at: 0.
  	(self isAnInstruction: (cogit cCoerceSimple: value to: #'AbstractInstruction *')) ifTrue:
  		[value := (cogit cCoerceSimple: value to: #'AbstractInstruction *') address].
  	(cogit addressIsInCurrentCompilation: value) ifTrue:
  		[offset := value - (address + 7).
  		 machineCode
  			at: 0 put: (self rexR: RISCTempReg x: 0 b: 0);
  			at: 1 put: 16r8D; "LoadEffectiveAddress"
  			at: 2 put: (self mod: ModRegInd RM: 5 RO: RISCTempReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF);
  			at: 7 put: 16r41;
  			at: 8 put: 16r48 + RISCTempReg.
+ 		^9].
- 		^machineCodeSize := 9].
  	machineCode
  		at:  0 put: (self rexR: RISCTempReg x: 0 b: RISCTempReg);
  		at:  1 put: 16rB8 + (RISCTempReg bitAnd: 7);
  		at:  2 put: (value bitAnd: 16rFF);
  		at:  3 put: (value >> 8 bitAnd: 16rFF);
  		at:  4 put: (value >> 16 bitAnd: 16rFF);
  		at:  5 put: (value >> 24 bitAnd: 16rFF);
  		at:  6 put: (value >> 32 bitAnd: 16rFF);
  		at:  7 put: (value >> 40 bitAnd: 16rFF);
  		at:  8 put: (value >> 48 bitAnd: 16rFF);
  		at:  9 put: (value >> 56 bitAnd: 16rFF);
  		at: 10 put: 16r41;
  		at: 11 put: 16r48 + RISCTempReg. "The 48 will disambiguate between MoveCwR, PushCw and ArithCwR, which ends with a (self mod: ModReg RM: 0 RO: 0)"
  	self assert: (machineCode at: 11) < 16r90. "see literalBeforeFollowingAddress:"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>canMulRR (in category 'testing') -----
  canMulRR
+ 	^false!
- 	^true!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAddCheckOverflowCqR (in category 'generate machine code - concretize') -----
  concretizeAddCheckOverflowCqR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  
  	"Save original LHS"
  	self machineCodeAt: 8 put: (self adduR: OverflowTemp1 R: leftReg R: ZR). 
  	
  	"The actual addition"
  	self machineCodeAt: 12 put: (self adduR: destReg R: leftReg R: AT). 
  
  	"Set sign bit of OverflowTemp2 if sign of result differs from sign of RHS."
  	self machineCodeAt: 16 put: (self xorR: OverflowTemp2 R: destReg R: AT).
  	"Set sign bit of OverflowTemp1 if sign of result differs from sign of LHS."
  	self machineCodeAt: 20 put: (self xorR: OverflowTemp1 R: destReg R: OverflowTemp1).
  	"Set sign bit of Overflow if sign of result differs from both LHS and RHS, which indicates overflow."
  	self machineCodeAt: 24 put: (self andR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^28!
- 	^machineCodeSize := 28!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAddCheckOverflowRR (in category 'generate machine code - concretize') -----
  concretizeAddCheckOverflowRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  
  	"Save original LHS"
  	self machineCodeAt: 0 put: (self adduR: OverflowTemp1 R: leftReg R: ZR). 
  	
  	"The actual addition"
  	self machineCodeAt: 4 put: (self adduR: destReg R: leftReg R: rightReg). 
  
  	"Set sign bit of OverflowTemp2 if sign of result differs from sign of RHS."
  	self machineCodeAt: 8 put: (self xorR: OverflowTemp2 R: destReg R: rightReg).
  	"Set sign bit of OverflowTemp1 if sign of result differs from sign of LHS."
  	self machineCodeAt: 12 put: (self xorR: OverflowTemp1 R: destReg R: OverflowTemp1).
  	"Set sign bit of Overflow if sign of result differs from both LHS and RHS, which indicates overflow."
  	self machineCodeAt: 16 put: (self andR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^20!
- 	^machineCodeSize := 20!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAddCqR (in category 'generate machine code - concretize') -----
  concretizeAddCqR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	
  	(rightImm between: -16r8000 and: 16r7FFF) ifFalse: [^self concretizeAddCwR].
  	
  	self machineCodeAt: 0 put: (self addiuR: destReg R: leftReg C: rightImm).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAddCwR (in category 'generate machine code - concretize') -----
  concretizeAddCwR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  	self machineCodeAt: 8 put: (self adduR: destReg R: leftReg R: AT).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAddRR (in category 'generate machine code - concretize') -----
  concretizeAddRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self adduR: destReg R: leftReg R: rightReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAlignmentNops (in category 'generate machine code - concretize') -----
  concretizeAlignmentNops
  	self assert: machineCodeSize \\ 4 = 0.
  	0 to: machineCodeSize - 1 by: 4 do:
+ 		[:p | self machineCodeAt: p put: self nop].
+ 	^machineCodeSize!
- 		[:p | self machineCodeAt: p put: self nop]!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAndCqR (in category 'generate machine code - concretize') -----
  concretizeAndCqR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	
  	(rightImm between: -16r8000 and: 16r7FFF) ifFalse: [^self concretizeAndCwR].
  	
  	self machineCodeAt: 0 put: (self andiR: destReg R: leftReg C: rightImm).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAndCqRR (in category 'generate machine code - concretize') -----
  concretizeAndCqRR
  	| value srcReg dstReg |
  	value := operands at: 0.
  	srcReg := operands at: 1.
  	dstReg := operands at: 2.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self andR: dstReg R: srcReg R: AT).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAndCwR (in category 'generate machine code - concretize') -----
  concretizeAndCwR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  	self machineCodeAt: 8 put: (self andR: destReg R: leftReg R: AT).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAndRR (in category 'generate machine code - concretize') -----
  concretizeAndRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self andR: destReg R: leftReg R: rightReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeArithmeticShiftRightCqR (in category 'generate machine code - concretize') -----
  concretizeArithmeticShiftRightCqR
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	self machineCodeAt: 0 put: (self sraR: reg R: reg C: distance).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeArithmeticShiftRightRR (in category 'generate machine code - concretize') -----
  concretizeArithmeticShiftRightRR
  	| destReg distReg |
  	distReg := operands at: 0.
  	destReg := operands at: 1.
  	self machineCodeAt: 0 put: (self sravR: destReg R: destReg R: distReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 4.
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self machineCodeAt: 0 put: (self beqR: leftReg R: rightReg offset: offset).
  	self machineCodeAt: 4 put: (self nop). "Delay slot"
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrLongEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrLongEqualRR
  	| jumpTargetInstruction jumpTargetAddr leftReg rightReg |
  	<var: #jumpTargetInstruction type: #'AbstractInstruction *'>
  	jumpTargetInstruction := self longJumpTargetAddress.
  	self flag: #todo. "Check not crossing 256MB block."
  	jumpTargetAddr := jumpTargetInstruction asUnsignedInteger bitAnd: 16rFFFFFFF.
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  
  	self machineCodeAt: 0 put: (self bneR: leftReg R: rightReg offset: 12).
  	self machineCodeAt: 4 put: (self nop). "Delay slot"
  	self machineCodeAt: 8 put: (self jA: jumpTargetAddr).
  	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^16!
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrLongNotEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrLongNotEqualRR
  	| jumpTargetInstruction jumpTargetAddr leftReg rightReg |
  	<var: #jumpTargetInstruction type: #'AbstractInstruction *'>
  	jumpTargetInstruction := self longJumpTargetAddress.
  	self flag: #todo. "Check not crossing 256MB block."
  	jumpTargetAddr := jumpTargetInstruction asUnsignedInteger bitAnd: 16rFFFFFFF.
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  
  	self machineCodeAt: 0 put: (self beqR: leftReg R: rightReg offset: 12).
  	self machineCodeAt: 4 put: (self nop). "Delay slot"
  	self machineCodeAt: 8 put: (self jA: jumpTargetAddr).
  	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^16!
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrNotEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrNotEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 4.
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self machineCodeAt: 0 put: (self bneR: leftReg R: rightReg offset: offset).
  	self machineCodeAt: 4 put: (self nop). "Delay slot"
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrSignedGreaterEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrSignedGreaterEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltR: BranchTemp R: leftReg R: rightReg).
  	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrSignedGreaterRR (in category 'generate machine code - concretize') -----
  concretizeBrSignedGreaterRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltR: BranchTemp R: rightReg R: leftReg).
  	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrSignedLessEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrSignedLessEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltR: BranchTemp R: rightReg R: leftReg).
  	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrSignedLessRR (in category 'generate machine code - concretize') -----
  concretizeBrSignedLessRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltR: BranchTemp R: leftReg R: rightReg).
  	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedGreaterEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrUnsignedGreaterEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltuR: BranchTemp R: leftReg R: rightReg).
  	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedGreaterRR (in category 'generate machine code - concretize') -----
  concretizeBrUnsignedGreaterRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltuR: BranchTemp R: rightReg R: leftReg).
  	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedLessEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrUnsignedLessEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltuR: BranchTemp R: rightReg R: leftReg).
  	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedLessRR (in category 'generate machine code - concretize') -----
  concretizeBrUnsignedLessRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := operands at: 1.
  	rightReg := operands at: 2.
  	self assert: leftReg ~= BranchTemp.
  	self assert: rightReg ~= BranchTemp.
  	self machineCodeAt: 0 put: (self sltuR: BranchTemp R: leftReg R: rightReg).
  	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeCallFull (in category 'generate machine code - concretize') -----
  concretizeCallFull
  	| jumpTargetInstruction jumpTargetAddr |
  	<var: #jumpTargetInstruction type: #'AbstractInstruction *'>
  	jumpTargetInstruction := self longJumpTargetAddress.
  	jumpTargetAddr := jumpTargetInstruction asUnsignedInteger.
  	self machineCodeAt: 0 put: (self luiR: TargetReg C: (self high16BitsOf: jumpTargetAddr)).
  	self machineCodeAt: 4 put: (self oriR: TargetReg R: TargetReg C: (self low16BitsOf: jumpTargetAddr)).
  	self machineCodeAt: 8 put: (self jalR: TargetReg).
  	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^16!
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeClzRR (in category 'generate machine code - concretize') -----
  concretizeClzRR
  	| destReg leftReg rightReg |
  	destReg := rightReg := operands at: 0.
  	leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self clzR: destReg R: leftReg R:  rightReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeDivRR (in category 'generate machine code - concretize') -----
  concretizeDivRR
  	| dividendReg divisorReg |
  	dividendReg := operands at: 0.
  	divisorReg := operands at: 1.
  	self machineCodeAt: 0 put: (self divR: dividendReg R: divisorReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeFill32 (in category 'generate machine code - concretize') -----
  concretizeFill32
  	"fill with operand 0 according to the processor's endianness.
  	 You might think this is bogus and we should fill with stop instrurctions instead,
  	 but this is used to leave room for a CMBlock header before the code for a block;
  	 the gaps get filled in by fillInBlockHeadersAt: after code has been generated."
  	self machineCodeAt: 0 put: (operands at: 0).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJump (in category 'generate machine code - concretize') -----
  concretizeJump
  	| offset |
  	offset := self computeJumpTargetOffsetPlus: 4.
  	self flag: #BranchRange.
  	self machineCodeAt: 0 put: (self beqR: ZR R: ZR offset: offset).
  	self machineCodeAt: 4 put: self nop. "Delay slot"
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpFull (in category 'generate machine code - concretize') -----
  concretizeJumpFull
  	| jumpTargetInstruction jumpTargetAddr |
  	<var: #jumpTargetInstruction type: #'AbstractInstruction *'>
  	jumpTargetInstruction := self longJumpTargetAddress.
  	jumpTargetAddr := jumpTargetInstruction asUnsignedInteger.
  	self machineCodeAt: 0 put: (self luiR: TargetReg C: (self high16BitsOf: jumpTargetAddr)).
  	self machineCodeAt: 4 put: (self oriR: TargetReg R: TargetReg C: (self low16BitsOf: jumpTargetAddr)).
  	self machineCodeAt: 8 put: (self jR: TargetReg).
  	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^16!
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpR (in category 'generate machine code - concretize') -----
  concretizeJumpR
  	| reg |
  	self flag: #OABI. "Does this ever target C code? If so we should move the target into TargetReg first."
  	reg := operands at: 0.
  	self machineCodeAt: 0 put: (self jR: reg).
  	self machineCodeAt: 4 put: self nop. "Delay slot"
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code - concretize') -----
  concretizeLoadEffectiveAddressMwrR
  	<var: #offset type: #sqInt>
  	| baseReg offset destReg |
  	offset := operands at: 0.
  	baseReg := operands at: 1.
  	destReg := operands at: 2.
  	(self isShortOffset: offset) ifTrue:
  		[self machineCodeAt: 0 put: (self addiuR: destReg R: baseReg C: offset).
+ 		^4].
- 		^machineCodeSize := 4].
  	
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: offset)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: offset)).
  	self machineCodeAt: 8 put: (self adduR: destReg R: baseReg R: AT).
+ 	^12.
- 	^machineCodeSize := 12.
  !

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeLogicalShiftLeftCqR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftLeftCqR
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	self machineCodeAt: 0 put: (self sllR: reg R: reg C: distance).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeLogicalShiftLeftRR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftLeftRR
  	| destReg distReg |
  	distReg := operands at: 0.
  	destReg := operands at: 1.
  	self machineCodeAt: 0 put: (self sllvR: destReg R: destReg R: distReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeLogicalShiftRightCqR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftRightCqR
  	| distance reg |
  	distance := (operands at: 0) min: 31.
  	reg := operands at: 1.
  	self machineCodeAt: 0 put: (self srlR: reg R: reg C: distance).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeLogicalShiftRightRR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftRightRR
  	| destReg distReg |
  	distReg := operands at: 0.
  	destReg := operands at: 1.
  	self machineCodeAt: 0 put: (self srlvR: destReg R: destReg R: distReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveAbR (in category 'generate machine code - concretize') -----
  concretizeMoveAbR
  	| srcAddr destReg |
  	srcAddr := operands at: 0.
  	destReg := operands at: 1.
  
  	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self lwR: destReg base: ConcreteVarBaseReg offset: srcAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: srcAddr)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: srcAddr)).
  	self machineCodeAt: 8 put: (self lbuR: destReg base: AT offset: 0).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveAwR (in category 'generate machine code - concretize') -----
  concretizeMoveAwR
  	| srcAddr destReg |
  	srcAddr := operands at: 0.
  	destReg := operands at: 1.
  
  	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self lwR: destReg base: ConcreteVarBaseReg offset: srcAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: srcAddr)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: srcAddr)).
  	self machineCodeAt: 8 put: (self lwR: destReg base: AT offset: 0).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveCqR (in category 'generate machine code - concretize') -----
  concretizeMoveCqR
  	<var: #word type: #sqInt>
  	| word reg |
  	word := operands at: 0.
  	reg := operands at: 1.
  	
  	(word between: -16r8000 and: 16r7FFF) ifFalse: [^self concretizeMoveCwR].
  	"Could also load up to 16rFFFF with ori or 16rXXXX0000 with lui"
  	
  	self machineCodeAt: 0 put: (self addiuR: reg R: ZR C: word).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveCwR (in category 'generate machine code - concretize') -----
  concretizeMoveCwR
  	<var: #word type: #sqInt>
  	| word reg |
  	word := operands at: 0.
  	reg := operands at: 1.
  	self machineCodeAt: 0 put: (self luiR: reg C: (self high16BitsOf: word)).
  	self machineCodeAt: 4 put: (self oriR: reg R: reg C: (self low16BitsOf: word)).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveHighR (in category 'generate machine code - concretize') -----
  concretizeMoveHighR
  	| destReg |
  	destReg := operands at: 0.
  	self machineCodeAt: 0 put: (self mfhiR: destReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveLowR (in category 'generate machine code - concretize') -----
  concretizeMoveLowR
  	| destReg |
  	destReg := operands at: 0.
  	self machineCodeAt: 0 put: (self mfloR: destReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveM16rR (in category 'generate machine code - concretize') -----
  concretizeMoveM16rR
  	<var: #offset type: #sqInt>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	self machineCodeAt: 0 put: (self lhuR: destReg base: srcReg offset: offset).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
  concretizeMoveMbrR
  	<var: #offset type: #sqInt>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	self machineCodeAt: 0 put: (self lbuR: destReg base: srcReg offset: offset).
+ 	^4
- 	^machineCodeSize := 4
  	!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveMwrR (in category 'generate machine code - concretize') -----
  concretizeMoveMwrR
  	<var: #offset type: #sqInt>
  	| baseReg offset destReg |
  	offset := operands at: 0.
  	baseReg := operands at: 1.
  	destReg := operands at: 2.
  	(self isShortOffset: offset) ifTrue:
  		[self machineCodeAt: 0 put: (self lwR: destReg base: baseReg offset: offset).
+ 		^4].
- 		^machineCodeSize := 4].
  	
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: offset)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: offset)).
  	self machineCodeAt: 8 put: (self adduR: AT R: baseReg R: AT).
  	self machineCodeAt: 12 put: (self lwR: destReg base: AT offset: 0).
+ 	^16.
- 	^machineCodeSize := 16.
  !

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRAb (in category 'generate machine code - concretize') -----
  concretizeMoveRAb
  	| srcReg destAddr |
  	srcReg := operands at: 0.
  	destAddr := operands at: 1.
  
  	(self isAddressRelativeToVarBase: destAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self swR: srcReg base: ConcreteVarBaseReg offset: destAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: destAddr)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: destAddr)).
  	self machineCodeAt: 8 put: (self sbR: srcReg base: AT offset: 0).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
  concretizeMoveRAw
  	| srcReg destAddr |
  	srcReg := operands at: 0.
  	destAddr := operands at: 1.
  
  	(self isAddressRelativeToVarBase: destAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self swR: srcReg base: ConcreteVarBaseReg offset: destAddr - cogit varBaseAddress).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: destAddr)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: destAddr)).
  	self machineCodeAt: 8 put: (self swR: srcReg base: AT offset: 0).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRM16r (in category 'generate machine code - concretize') -----
  concretizeMoveRM16r
  	<var: #offset type: #sqInt>
  	| srcReg offset destReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	self machineCodeAt: 0 put: (self shR: srcReg base: destReg offset: offset).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRMbr (in category 'generate machine code - concretize') -----
  concretizeMoveRMbr
  	<var: #offset type: #sqInt>
  	| srcReg offset destReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	self machineCodeAt: 0 put: (self sbR: srcReg base: destReg offset: offset).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRMwr (in category 'generate machine code - concretize') -----
  concretizeMoveRMwr
  	<var: #offset type: #sqInt>
  	| srcReg offset baseReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	baseReg := operands at: 2.
  	self machineCodeAt: 0 put: (self swR: srcReg base: baseReg offset: offset).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRR (in category 'generate machine code - concretize') -----
  concretizeMoveRR
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	self machineCodeAt: 0 put: (self adduR: destReg R: srcReg R: ZR).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRXbrR (in category 'generate machine code - concretize') -----
  concretizeMoveRXbrR
  	| srcReg indexReg baseReg |
  	srcReg := operands at: 0.
  	indexReg := operands at: 1.
  	baseReg := operands at: 2.
  	self machineCodeAt: 0 put: (self adduR: AT R: baseReg R: indexReg).
  	self machineCodeAt: 4 put: (self sbR: srcReg base: AT offset: 0).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRXwrR (in category 'generate machine code - concretize') -----
  concretizeMoveRXwrR
  	| srcReg indexReg baseReg |
  	srcReg := operands at: 0.
  	indexReg := operands at: 1.
  	baseReg := operands at: 2.
  	self machineCodeAt: 0 put: (self sllR: AT R: indexReg C: 2). "index is number of words"
  	self machineCodeAt: 4 put: (self adduR: AT R: baseReg R: AT).
  	self machineCodeAt: 8 put: (self swR: srcReg base: AT offset: 0).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveXbrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXbrRR
  	| indexReg baseReg destReg |
  	indexReg := operands at: 0. "index is number of *bytes*"
  	baseReg := operands at: 1.
  	destReg := operands at: 2.
  	self machineCodeAt: 0 put: (self adduR: AT R: baseReg R: indexReg).
  	self machineCodeAt: 4 put: (self lbuR: destReg base: AT offset: 0).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveXwrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXwrRR
  	| indexReg baseReg destReg |
  	indexReg := operands at: 0.
  	baseReg := operands at: 1.
  	destReg := operands at: 2.
  	self machineCodeAt: 0 put: (self sllR: AT R: indexReg C: 2). "index is in words"
  	self machineCodeAt: 4 put: (self adduR: AT R: baseReg R: AT).
  	self machineCodeAt: 8 put: (self lwR: destReg base: AT offset: 0).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMulCheckOverflowRR (in category 'generate machine code - concretize') -----
  concretizeMulCheckOverflowRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  
  	"Overflow occured if the sign bit of the low part is different from the high part."
  	self machineCodeAt: 0 put: (self multR: leftReg R: rightReg).
  	self machineCodeAt: 4 put: (self mfloR: destReg).
  	self machineCodeAt: 8 put: (self sraR: OverflowTemp1 R: destReg C: 31).
  	self machineCodeAt: 12 put: (self mfhiR: OverflowTemp2).
+ 	^16!
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeNegateR (in category 'generate machine code - concretize') -----
  concretizeNegateR
  	| reg |
  	reg := operands at: 0.
  	self machineCodeAt: 0 put: (self subuR: reg R: ZR R: reg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeNop (in category 'generate machine code - concretize') -----
  concretizeNop
  	self machineCodeAt: 0 put: self nop.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeOrCqR (in category 'generate machine code - concretize') -----
  concretizeOrCqR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  
  	(rightImm between: 0 and: 16rFFFF) ifFalse: [^self concretizeOrCwR].
  	
  	self machineCodeAt: 0 put: (self oriR: destReg R: leftReg C: rightImm).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeOrCwR (in category 'generate machine code - concretize') -----
  concretizeOrCwR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  	self machineCodeAt: 8 put: (self orR: destReg R: leftReg R: AT).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeOrRR (in category 'generate machine code - concretize') -----
  concretizeOrRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self orR: destReg R: leftReg R: rightReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizePopR (in category 'generate machine code - concretize') -----
  concretizePopR
  	| destReg |
  	destReg := operands at: 0.
  	self machineCodeAt: 0 put: (self lwR: destReg base: SP offset: 0).
  	self machineCodeAt: 4 put: (self addiuR: SP R: SP C: 4).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizePrefetchAw (in category 'generate machine code - concretize') -----
  concretizePrefetchAw
  	| addressOperand |
  	addressOperand := operands at: 0.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: addressOperand)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: addressOperand)).
  	self machineCodeAt: 8 put: (self prefR: AT offset: 0 hint: HintLoad).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizePushCw (in category 'generate machine code - concretize') -----
  concretizePushCw
  	| value |
  	value := operands at: 0.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self addiuR: SP R: SP C: -4).
  	self machineCodeAt: 12 put: (self swR: AT base: SP offset: 0).
+ 	^16!
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizePushR (in category 'generate machine code - concretize') -----
  concretizePushR
  	| srcReg |
  	srcReg := operands at: 0.
  	self machineCodeAt: 0 put: (self addiuR: SP R: SP C: -4).
  	self machineCodeAt: 4 put: (self swR: srcReg base: SP offset: 0).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeRetN (in category 'generate machine code - concretize') -----
  concretizeRetN
  	<var: #offset type: #sqInt>
  	| offset |
  	offset := operands at: 0.
  	self machineCodeAt: 0 put: (self jR: RA).
  	offset = 0 
  		ifTrue: [self machineCodeAt: 4 put: self nop "Delay slot"]
  		ifFalse: [self machineCodeAt: 4 put: (self addiuR: SP R: SP C: offset) "We actually get to fill a delay slot!!"].
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeStop (in category 'generate machine code - concretize') -----
  concretizeStop
  	self machineCodeAt: 0 put: self stop.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeSubCheckOverflowCqR (in category 'generate machine code - concretize') -----
  concretizeSubCheckOverflowCqR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  
  	"Save original LHS"
  	self machineCodeAt: 8 put: (self adduR: OverflowTemp1 R: leftReg R: ZR). 
  	
  	"The actual subtraction"
  	self machineCodeAt: 12 put: (self subuR: destReg R: leftReg R: AT). 
  
  	"Set sign bit of OverflowTemp2 if sign of result differs from sign of RHS."
  	self machineCodeAt: 16 put: (self xorR: OverflowTemp2 R: destReg R: AT).
  	"Set sign bit of OverflowTemp1 if sign of result differs from sign of LHS."
  	self machineCodeAt: 20 put: (self xorR: OverflowTemp1 R: destReg R: OverflowTemp1).
  	"Set sign bit of Overflow if sign of result differs from both LHS and RHS, which indicates overflow."
  	self machineCodeAt: 24 put: (self andR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^28!
- 	^machineCodeSize := 28!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeSubCheckOverflowRR (in category 'generate machine code - concretize') -----
  concretizeSubCheckOverflowRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  
  	"Save original LHS"
  	self machineCodeAt: 0 put: (self adduR: OverflowTemp1 R: leftReg R: ZR). 
  	
  	"The actual subtraction"
  	self machineCodeAt: 4 put: (self subuR: destReg R: leftReg R: rightReg). 
  
  	"Set sign bit of OverflowTemp2 if sign of result differs from sign of RHS."
  	self machineCodeAt: 8 put: (self xorR: OverflowTemp2 R: destReg R: rightReg).
  	"Set sign bit of OverflowTemp1 if sign of result differs from sign of LHS."
  	self machineCodeAt: 12 put: (self xorR: OverflowTemp1 R: destReg R: OverflowTemp1).
  	"Set sign bit of Overflow if sign of result differs from both LHS and RHS, which indicates overflow."
  	self machineCodeAt: 16 put: (self andR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^20!
- 	^machineCodeSize := 20!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeSubCqR (in category 'generate machine code - concretize') -----
  concretizeSubCqR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	
  	(rightImm negated between: -16r8000 and: 16r7FFF) ifFalse: [^self concretizeSubCwR].
  	
  	self machineCodeAt: 0 put: (self addiuR: destReg R: leftReg C: rightImm negated).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeSubCwR (in category 'generate machine code - concretize') -----
  concretizeSubCwR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  	self machineCodeAt: 8 put: (self subuR: destReg R: leftReg R: AT).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeSubRR (in category 'generate machine code - concretize') -----
  concretizeSubRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self subuR: destReg R: leftReg R: rightReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeTstCqR (in category 'generate machine code - concretize') -----
  concretizeTstCqR
  	| leftReg rightImm |
  	rightImm := operands at: 0.
  	leftReg := operands at: 1.
  	
  	(rightImm between: -16r8000 and: 16r7FFF) ifFalse: [^self concretizeTstCwR].
  	
  	self machineCodeAt: 0 put: (self andiR: Cmp R: leftReg C: rightImm).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeTstCwR (in category 'generate machine code - concretize') -----
  concretizeTstCwR
  	| leftReg rightImm |
  	rightImm := operands at: 0.
  	leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  	self machineCodeAt: 8 put: (self andR: Cmp R: leftReg R: AT).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeXorCwR (in category 'generate machine code - concretize') -----
  concretizeXorCwR
  	| destReg leftReg rightImm |
  	rightImm := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: rightImm)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: rightImm)).
  	self machineCodeAt: 8 put: (self xorR: destReg R: leftReg R: AT).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeXorRR (in category 'generate machine code - concretize') -----
  concretizeXorRR
  	| destReg leftReg rightReg |
  	rightReg := operands at: 0.
  	destReg := leftReg := operands at: 1.
  	self machineCodeAt: 0 put: (self xorR: destReg R: leftReg R: rightReg).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
+ 	 bytecode set."		 
- 	 bytecode set."
- 	<returnTypeC: #void>		 
  	opcode caseOf: {
  		[BrEqualRR]						-> [^self concretizeBrEqualRR].
  		[BrNotEqualRR]					-> [^self concretizeBrNotEqualRR].
  		[BrUnsignedLessRR]			-> [^self concretizeBrUnsignedLessRR].
  		[BrUnsignedLessEqualRR]		-> [^self concretizeBrUnsignedLessEqualRR].
  		[BrUnsignedGreaterRR]			-> [^self concretizeBrUnsignedGreaterRR].
  		[BrUnsignedGreaterEqualRR]	-> [^self concretizeBrUnsignedGreaterEqualRR].
  		[BrSignedLessRR]				-> [^self concretizeBrSignedLessRR].
  		[BrSignedLessEqualRR]			-> [^self concretizeBrSignedLessEqualRR].
  		[BrSignedGreaterRR]			-> [^self concretizeBrSignedGreaterRR].
  		[BrSignedGreaterEqualRR]		-> [^self concretizeBrSignedGreaterEqualRR].	
  		[BrLongEqualRR]				-> [^self concretizeBrLongEqualRR].
  		[BrLongNotEqualRR]				-> [^self concretizeBrLongNotEqualRR].
  		[MulRR]				-> [^self concretizeUnimplemented].
  		[DivRR]				-> [^self concretizeDivRR].
  		[MoveLowR]		-> [^self concretizeMoveLowR].
  		[MoveHighR]		-> [^self concretizeMoveHighR].
  
  										
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill32]					-> [^self concretizeFill32].
  		[Nop]					-> [^self concretizeNop].
  		"Control"
  		[Call]						-> [^self concretizeCall]. "call code within code space"
  		[CallFull]					-> [^self concretizeCallFull]. "call code anywhere in address space"
  		[JumpR]						-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeJumpFull]."jump within address space"
  		[JumpLong]					-> [^self concretizeJumpLong]."jumps witihn code space"
  		[JumpLongZero]			-> [^self concretizeJumpLongZero].
  		[JumpLongNonZero]		-> [^self concretizeJumpLongNonZero].
  		[Jump]						-> [^self concretizeJump].
  		[JumpZero]					-> [^self concretizeJumpZero].
  		[JumpNonZero]				-> [^self concretizeJumpNonZero].
  		[JumpNegative]				-> [^self concretizeUnimplemented].
  		[JumpNonNegative]			-> [^self concretizeUnimplemented].
  		[JumpOverflow]				-> [^self concretizeJumpOverflow].
  		[JumpNoOverflow]			-> [^self concretizeJumpNoOverflow].
  		[JumpCarry]				-> [^self concretizeUnimplemented].
  		[JumpNoCarry]				-> [^self concretizeUnimplemented].
  		[JumpLess]					-> [^self concretizeJumpSignedLessThan].
  		[JumpGreaterOrEqual]		-> [^self concretizeJumpSignedGreaterEqual].
  		[JumpGreater]				-> [^self concretizeJumpSignedGreaterThan].
  		[JumpLessOrEqual]			-> [^self concretizeJumpSignedLessEqual].
  		[JumpBelow]				-> [^self concretizeJumpUnsignedLessThan].
  		[JumpAboveOrEqual]		-> [^self concretizeJumpUnsignedGreaterEqual].
  		[JumpAbove]				-> [^self concretizeJumpUnsignedGreaterThan].
  		[JumpBelowOrEqual]		-> [^self concretizeJumpUnsignedLessEqual].
  		[JumpFPEqual]				-> [^self concretizeUnimplemented].
  		[JumpFPNotEqual]			-> [^self concretizeUnimplemented].
  		[JumpFPLess]				-> [^self concretizeUnimplemented].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeUnimplemented].
  		[JumpFPGreater]			-> [^self concretizeUnimplemented].
  		[JumpFPLessOrEqual]		-> [^self concretizeUnimplemented].
  		[JumpFPOrdered]			-> [^self concretizeUnimplemented].
  		[JumpFPUnordered]			-> [^self concretizeUnimplemented].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCqRR]					-> [^self concretizeAndCqRR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[OrCqR]						-> [^self concretizeOrCqR].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[XorCqR]					-> [^self concretizeUnimplemented].
  		[AddCwR]					-> [^self concretizeAddCwR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[XorCwR]					-> [^self concretizeXorCwR].
  		[AddRR]						-> [^self concretizeAddRR].
  		[AndRR]						-> [^self concretizeAndRR].
  		[CmpRR]					-> [^self concretizeCmpRR].
  		[OrRR]						-> [^self concretizeOrRR].
  		[SubRR]						-> [^self concretizeSubRR].
  		[XorRR]						-> [^self concretizeXorRR].
  		[AddRdRd]					-> [^self concretizeUnimplemented].
  		[CmpRdRd]					-> [^self concretizeUnimplemented].
  		[DivRdRd]					-> [^self concretizeUnimplemented].
  		[MulRdRd]					-> [^self concretizeUnimplemented].
  		[SubRdRd]					-> [^self concretizeUnimplemented].
  		[SqrtRd]					-> [^self concretizeUnimplemented].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		[ClzRR]						-> [^self concretizeClzRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeUnimplemented].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM64rRd]		-> [^self concretizeUnimplemented].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeUnimplemented].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		[AddCheckOverflowCqR] -> [^self concretizeAddCheckOverflowCqR].
  		[AddCheckOverflowRR] -> [^self concretizeAddCheckOverflowRR].
  		[SubCheckOverflowCqR] -> [^self concretizeSubCheckOverflowCqR].
  		[SubCheckOverflowRR] -> [^self concretizeSubCheckOverflowRR].
  		[MulCheckOverflowRR] -> [^self concretizeMulCheckOverflowRR].
  		"Conversion"
+ 		[ConvertRRd]		-> [^self concretizeUnimplemented]}.
+ 
+ 	^0 "keep Slang happy"!
- 		[ConvertRRd]		-> [^self concretizeUnimplemented]}!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>concretizeLiteral (in category 'generate machine code') -----
  concretizeLiteral
  	"Generate an out-of-line literal.  Copy the value and any annotation from the stand-in in the literals manager."
  	| literalAsInstruction literal |
  	literalAsInstruction := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	literal := (self isAnInstruction: literalAsInstruction)
  				ifTrue: [literalAsInstruction address]
  				ifFalse: [self cCode: [literalAsInstruction asUnsignedInteger]
  							inSmalltalk: [literalAsInstruction]].
  	self assert: (dependent notNil and: [dependent opcode = Literal]).
  	dependent annotation ifNotNil:
  		[self assert: annotation isNil.
  		 annotation := dependent annotation].
  	dependent address ifNotNil: [self assert: dependent address = address].
  	dependent address: address.
  	self machineCodeAt: 0 put: literal.
+ 	^4!
- 	machineCodeSize := 4!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>moveCw:intoR: (in category 'generate machine code - support') -----
  moveCw: constant intoR: destReg
  	"Emit a load of aWord into destReg.  Answer the number of bytes of machine code generated.
  	 Literals are stored out-of-line; emit a LDR with the relevant offset."
  	 <var: 'constant' type: #usqInt>
  	<inline: true>
  	self assert: (cogit addressIsInCurrentCompilation: dependent address).
  	self assert: (dependent address - (address + 8)) abs < (1<<12).
  	self machineCodeAt: 0
  		put: (self
  				ldr: destReg
  				rn: PC
  				plus: (dependent address >= (address + 8) ifTrue: [1] ifFalse: [0])
  				imm: (dependent address - (address + 8)) abs).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeAlignmentNops (in category 'generate machine code') -----
  concretizeAlignmentNops
  	<inline: true>
  	self flag: 'if performance is an issue generate longer nops'.
  	0 to: machineCodeSize - 1 do:
  		[:i|
+ 		machineCode at: i put: 16r90].
+ 	^machineCodeSize!
- 		machineCode at: i put: 16r90]!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeArithCqRWithRO:raxOpcode: (in category 'generate machine code') -----
  concretizeArithCqRWithRO: regOpcode raxOpcode: raxOpcode
  	"Will get inlined into concretizeAt: switch."
  	<inline: false>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: reg).
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 1 put: 16r83;
  			at: 2 put: (self mod: ModReg RM: reg RO: regOpcode);
  			at: 3 put: (value bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	(self is32BitSignedImmediate: value) ifTrue:
  		[reg = RAX ifTrue:
  			[machineCode
  				at: 1 put: raxOpcode;
  				at: 2 put: (value bitAnd: 16rFF);
  				at: 3 put: (value >> 8 bitAnd: 16rFF);
  				at: 4 put: (value >> 16 bitAnd: 16rFF);
  				at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 			 ^6].
- 			 ^machineCodeSize := 6].
  		machineCode
  			at: 1 put: 16r81;
  			at: 2 put: (self mod: ModReg RM: reg RO: regOpcode);
  			at: 3 put: (value bitAnd: 16rFF);
  			at: 4 put: (value >> 8 bitAnd: 16rFF);
  			at: 5 put: (value >> 16 bitAnd: 16rFF);
  			at: 6 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^7].
- 		 ^machineCodeSize := 7].
  	^self concretizeArithCwR: (raxOpcode = 16r3D "Cmp" ifTrue: [16r39] ifFalse: [raxOpcode - 2])!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeBSR (in category 'generate machine code') -----
  concretizeBSR
  	"Bit Scan Reverse
  	First operand is output register (dest)
  	Second operand is input register (mask)"
  	"BSR"
  	<inline: true>
  	| dest mask |
  	dest := operands at: 0.
  	mask := operands at: 1.
  	(dest <= 7 and: [mask <= 7])
  		ifTrue: [machineCode at: 0 put: (self rexw: true r: 0 x: 0 b: 0)]
  		ifFalse: ["Beware: operation is on 32bits for R8-15"machineCode at: 0 put: (self rexw: false r: 0 x: 0 b: 0)].
  
  	machineCode
  		at: 1 put: 16r0F;
  		at: 2 put: 16rBD;
  		at: 3 put: (self mod: ModReg RM: dest RO: mask).
+ 	 ^4!
- 	 ^machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCDQ (in category 'generate machine code') -----
  concretizeCDQ
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	machineCode
  		at: 0 put: 16r48;
  		at: 1 put: 16r99.
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCLD (in category 'generate machine code') -----
  concretizeCLD
  	<inline: true>
  	machineCode at: 0 put: 16rFC.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCPUID (in category 'generate machine code') -----
  concretizeCPUID
  	<inline: true>
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rA2.
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCall (in category 'generate machine code') -----
  concretizeCall
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset |
  	self assert: (operands at: 0) ~= 0.
  	offset := (operands at: 0) signedIntFromLong - (address + 5) signedIntFromLong.
  	machineCode
  		at: 0 put: 16rE8;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8 bitAnd: 16rFF);
  		at: 3 put: (offset >> 16 bitAnd: 16rFF);
  		at: 4 put: (offset >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCallFull (in category 'generate machine code') -----
  concretizeCallFull
  	"Since CallFull (and JumpFull) is used to invoke code in dynamically-loaded plugins it shouldn't
  	 assume that code will be loaded within 2Gb of the code zone.  Hence generate a full 64-bit call,
  	 movabsq $0x123456789abcdef0, %rax; callq *%rax."
  	<inline: true>
  	| operand |
  	operand := operands at: 0.
  	machineCode
  		at: 0 put: 16r48;
  		at: 1 put: 16rB8;
  		at: 2 put: (operand bitAnd: 16rFF);
  		at: 3 put: (operand >> 8 bitAnd: 16rFF);
  		at: 4 put: (operand >> 16 bitAnd: 16rFF);
  		at: 5 put: (operand >> 24 bitAnd: 16rFF);
  		at: 6 put: (operand >> 32 bitAnd: 16rFF);
  		at: 7 put: (operand >> 40 bitAnd: 16rFF);
  		at: 8 put: (operand >> 48 bitAnd: 16rFF);
  		at: 9 put: (operand >> 56 bitAnd: 16rFF);
  		at: 10 put: 16rFF;
  		at: 11 put: (self mod: ModReg RM: RAX RO: 2).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCallR (in category 'generate machine code') -----
  concretizeCallR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: reg);
  		at: 1 put: 16rFF;
  		at: 2 put: (self mod: ModReg RM: reg RO: 2).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeClzRR (in category 'generate machine code') -----
  concretizeClzRR
  	"Count leading zeros
  	First operand is output (dest)
  	Second operand is input (mask)"
  	"LZCNT"
  	<inline: true>
  	| dest mask |
  	dest := operands at: 0.
  	mask := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3.
  	(dest <= 7 and: [mask <= 7])
  		ifTrue: [machineCode at: 1 put: (self rexw: true r: 0 x: 0 b: 0)]
  		ifFalse: [machineCode at: 1 put: (self rexw: false r: 0 x: 0 b: 0)].
  
  	machineCode
  		at: 2 put: 16r0F;
  		at: 3 put: 16rBD;
  		at: 4 put: (self mod: ModReg RM: dest RO: mask).
+ 	 ^5!
- 	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCmpC32R (in category 'generate machine code') -----
  concretizeCmpC32R
  	"Will get inlined into concretizeAt: switch."
  	"N.B. This use of 32-bit comparss allows us to squeak by and use a short jump
  	 in PIC case dispatch, where a jump to the abort is 126 bytes (!!!!)."
  	<inline: true>
  	| value reg skip |
  	value := operands at: 0.
  	reg := operands at: 1.
  	reg = RAX
  		ifTrue:
  			[machineCode at: 0 put: 16r3D.
  			 skip := 0]
  		ifFalse:
  			[reg > 7
  				ifTrue:
  					[machineCode at: 0 put: 16r41.
  					 skip := 2]
  				ifFalse:
  					[skip := 1].
  			 machineCode
  				at: skip - 1 put: 16r81;
  				at: skip put:  (self mod: ModReg RM: reg RO: 7)].
  	machineCode		
  		at: skip + 1 put: (value bitAnd: 16rFF);
  		at: skip + 2 put: (value >> 8 bitAnd: 16rFF);
  		at: skip + 3 put: (value >> 16 bitAnd: 16rFF);
  		at: skip + 4 put: (value >> 24 bitAnd: 16rFF).
+ 	 ^5 + skip!
- 	 ^machineCodeSize := 5 + skip!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCmpRdRd (in category 'generate machine code') -----
  concretizeCmpRdRd
  	"Will get inlined into concretizeAt: switch.
  	 We use UCOMISD (see p 4-260 [2])"
  	<inline: true>
  	| regLHS regRHS skip |
  	"CmpRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	
  	machineCode
  		at: 0 put: 16r66.
  	(regLHS <= 7 and: [regRHS <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: regLHS x: 0 b: regRHS)].	
  	
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r2E;
  		at: skip + 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeCmpRsRs (in category 'generate machine code') -----
  concretizeCmpRsRs
  	"Will get inlined into concretizeAt: switch.
  	 We use UCOMISS"
  	<inline: true>
  	| regLHS regRHS skip |
  	"CmpRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	
  	(regLHS <= 7 and: [regRHS <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: regLHS x: 0 b: regRHS)].
  		
  	machineCode
  		at: skip + 0 put: 16r0F;
  		at: skip + 1 put: 16r2E;
  		at: skip + 2 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^skip + 3!
- 	^machineCodeSize := skip + 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConditionalJump: (in category 'generate machine code') -----
  concretizeConditionalJump: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| offset |
  	offset := self computeJumpTargetOffsetPlus: 2.
  	(machineCodeSize = 0 "size not determined because no sizeJump pass; generating initial trampolines"
  		ifTrue: [self isQuick: offset]
  		ifFalse: [machineCodeSize = 2]) ifTrue:
  		[machineCode
  			at: 0 put: 16r70 + conditionCode;
  			at: 1 put: (offset bitAnd: 16rFF).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	^self concretizeConditionalJumpLong: conditionCode!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConditionalJumpLong: (in category 'generate machine code') -----
  concretizeConditionalJumpLong: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| offset |
  	offset := self computeJumpTargetOffsetPlus: 6.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16r80 + conditionCode;
  		at: 2 put: (offset bitAnd: 16rFF);
  		at: 3 put: (offset >> 8 bitAnd: 16rFF);
  		at: 4 put: (offset >> 16 bitAnd: 16rFF);
  		at: 5 put: (offset >> 24 bitAnd: 16rFF).
+ 	^6!
- 	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConvertRRd (in category 'generate machine code') -----
  concretizeConvertRRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at:0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 2 put: 16r0F;
  		at: 3 put: 16r2A;
  		at: 4 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^5!
- 	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConvertRRs (in category 'generate machine code') -----
  concretizeConvertRRs
  	"Will get inlined into concretizeAt: switch."
  	"CVTSI2SS"
  	<inline: true>
  	| srcReg destReg skip |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: destReg x: 0 b: srcReg)].
  		
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r2A;
  		at: skip + 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^skip + 4!
- 	 ^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConvertRdR (in category 'generate machine code') -----
  concretizeConvertRdR
  	"Will get inlined into concretizeAt: switch."
  	"CVTSD2SI"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at:0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2;
  		at: 1 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 2 put: 16r0F;
  		at: 3 put: 16r2D;
  		at: 4 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^5!
- 	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConvertRdRs (in category 'generate machine code') -----
  concretizeConvertRdRs
  	"Will get inlined into concretizeAt: switch."
  	"CVTSD2SS"
  	<inline: true>
  	| srcReg destReg skip |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: destReg x: 0 b: srcReg)].
  		
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r5A;
  		at: skip + 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^skip + 4!
- 	 ^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConvertRsR (in category 'generate machine code') -----
  concretizeConvertRsR
  	"Will get inlined into concretizeAt: switch."
  	"CVTSS2SI"
  	<inline: true>
  	| srcReg destReg skip |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: destReg x: 0 b: srcReg)].
  		
  	machineCode 
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r2D;
  		at: skip + 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^skip + 4!
- 	 ^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeConvertRsRd (in category 'generate machine code') -----
  concretizeConvertRsRd
  	"Will get inlined into concretizeAt: switch."
  	"CVTSS2SD"
  	<inline: true>
  	| srcReg destReg skip |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: destReg x: 0 b: srcReg)].
  		
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r5A;
  		at: skip + 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^skip + 4!
- 	 ^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeFill32 (in category 'generate machine code') -----
  concretizeFill32
  	<inline: true>
  	| word |
  	<var: #word type: #'usqIntptr_t'>
  	word := operands at: 0.
  	machineCode at: 0 put: (word bitAnd: 16rFF).
  	machineCode at: 1 put: (word >> 8 bitAnd: 16rFF).
  	machineCode at: 2 put: (word >> 16 bitAnd: 16rFF).
  	machineCode at: 3 put: (word >> 24 bitAnd: 16rFF).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeIDIVR (in category 'generate machine code') -----
  concretizeIDIVR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regDivisor |
  	regDivisor := operands at: 0.
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: regDivisor);
  		at: 1 put: 16rF7;
  		at: 2 put: (self mod: ModReg RM: regDivisor RO: 7).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeJump (in category 'generate machine code') -----
  concretizeJump
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| jumpTarget offset |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	cogit assertSaneJumpTarget: jumpTarget.
  	(self isAnInstruction: jumpTarget) ifTrue:
  		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
  	self assert: jumpTarget ~= 0.
  	offset := jumpTarget signedIntFromLong - (address + 2) signedIntFromLong.
  	(machineCodeSize = 0 "size not determined because no sizeJump pass; generating initial trampolines"
  		ifTrue: [self isQuick: offset]
  		ifFalse: [machineCodeSize = 2]) ifTrue:
  		[machineCode
  			at: 0 put: 16rEB;
  			at: 1 put: (offset bitAnd: 16rFF).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	offset := jumpTarget signedIntFromLong - (address + 5) signedIntFromLong.
  	machineCode
  		at: 0 put: 16rE9;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8 bitAnd: 16rFF);
  		at: 3 put: (offset >> 16 bitAnd: 16rFF);
  		at: 4 put: (offset >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeJumpFull (in category 'generate machine code') -----
  concretizeJumpFull
  	"Since JumpFull (and CallFull) is used to invoke code in dynamically-loaded plugins it shouldn't
  	 assume that code will be loaded within 2Gb of the code zone.  Hence generate a full 64-bit call,
  	 movabsq 0x123456789abcdef0, %rax; jmpq *%rax."
  	<inline: true>
  	| operand |
  	operand := operands at: 0.
  	machineCode
  		at: 0 put: 16r48;
  		at: 1 put: 16rB8;
  		at: 2 put: (operand bitAnd: 16rFF);
  		at: 3 put: (operand >> 8 bitAnd: 16rFF);
  		at: 4 put: (operand >> 16 bitAnd: 16rFF);
  		at: 5 put: (operand >> 24 bitAnd: 16rFF);
  		at: 6 put: (operand >> 32 bitAnd: 16rFF);
  		at: 7 put: (operand >> 40 bitAnd: 16rFF);
  		at: 8 put: (operand >> 48 bitAnd: 16rFF);
  		at: 9 put: (operand >> 56 bitAnd: 16rFF);
  		at: 10 put: 16rFF;
  		at: 11 put: (self mod: ModReg RM: RAX RO: 4).
+ 	^12!
- 	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeJumpLong (in category 'generate machine code') -----
  concretizeJumpLong
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| jumpTarget offset |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	(self isAnInstruction: jumpTarget) ifTrue:
  		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
  	self assert: jumpTarget ~= 0.
  	offset := jumpTarget signedIntFromLong - (address + 5) signedIntFromLong.
  	machineCode
  		at: 0 put: 16rE9;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8 bitAnd: 16rFF);
  		at: 3 put: (offset >> 16 bitAnd: 16rFF);
  		at: 4 put: (offset >> 24 bitAnd: 16rFF).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeJumpR (in category 'generate machine code') -----
  concretizeJumpR
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: reg);
  		at: 1 put: 16rFF;
  		at: 2 put: (self mod: ModReg RM: reg RO: 4).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code') -----
  concretizeLoadEffectiveAddressMwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 1 put: 16r8D.
  	(srcReg ~= RSP and: [srcReg ~= R12]) ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"ESP/R12:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMOVSB (in category 'generate machine code') -----
  concretizeMOVSB
  	<inline: true>
  	machineCode at: 0 put: 16rA4.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMOVSQ (in category 'generate machine code') -----
  concretizeMOVSQ
  	<inline: true>
  	machineCode
  		at: 0 put: (self rexw: true r: 0 x: 0 b: 0);
  		at: 1 put: 16rA5.
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveA32R (in category 'generate machine code') -----
  concretizeMoveA32R
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg offset |
  	addressOperand := operands at: 0.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg := operands at: 1.
  	reg = RAX
  		ifTrue: [offset := 0]
  		ifFalse:
  			[machineCode
  				at: 0 put: (self rexR: 0 x: 0 b: reg);
  				at: 1 put: 16r90 + (reg \\ 8).
  			 offset := 2].
  	machineCode
  		at: 0 + offset put: 16rA1;
  		at: 1 + offset put: (addressOperand bitAnd: 16rFF);
  		at: 2 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 3 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 4 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
  		at: 5 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
  		at: 6 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
  		at: 7 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
  		at: 8 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
  	reg = RAX ifTrue:
+ 		[^9].
- 		[^machineCodeSize := 9].
  	machineCode
  		at: 11 put: (machineCode at: 0);
  		at: 12 put: (machineCode at: 1).
+ 	^13!
- 	^machineCodeSize := 13!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveAbR (in category 'generate machine code') -----
  concretizeMoveAbR
  	"N.B. The Cogit makes no assumption about the upper bits being set to zero because we
  	 deny byteReadsZeroExtend.  The cogit will clear the register before hand if necessary."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| addressOperand reg offset save0 save1 savedSize |
- 	| addressOperand reg offset save0 save1 |
  	addressOperand := operands at: 0.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
  		[save0 := operands at: 0.
  		 save1 := operands at: 1.
  		 operands
  			at: 0 put: addressOperand - cogit varBaseAddress;
  			at: 1 put: RBX;
  			at: 2 put: save1.
+ 		 savedSize := self concretizeMoveMbrR.
- 		 self concretizeMoveMbrR.
  		 operands
  			at: 0 put: save0;
  			at: 1 put: save1;
  			at: 2 put: 0.
+ 		^savedSize].
- 		^machineCodeSize].
  	reg := operands at: 1.
  	reg = RAX
  		ifTrue: [offset := 0]
  		ifFalse:
  			[machineCode
  				at: 0 put: (self rexR: 0 x: 0 b: reg);
  				at: 1 put: 16r90 + (reg \\ 8).
  			 offset := 2].
  	machineCode
  		at: 0 + offset put: 16r48;
  		at: 1 + offset put: 16rA0;
  		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
  		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
  		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
  		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
  		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
  		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
  	reg = RAX ifTrue:
+ 		[^10].
- 		[^machineCodeSize := 10].
  	machineCode
  		at: 12 put: (machineCode at: 0);
  		at: 13 put: (machineCode at: 1).
+ 	^14!
- 	^machineCodeSize := 14!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveAwR (in category 'generate machine code') -----
  concretizeMoveAwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| addressOperand reg offset save0 save1 savedSize |
- 	| addressOperand reg offset save0 save1 |
  	addressOperand := operands at: 0.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
  		[save0 := operands at: 0.
  		 save1 := operands at: 1.
  		 operands
  			at: 0 put: addressOperand - cogit varBaseAddress;
  			at: 1 put: RBX;
  			at: 2 put: save1.
+ 		 savedSize := self concretizeMoveMwrR.
- 		 self concretizeMoveMwrR.
  		 operands
  			at: 0 put: save0;
  			at: 1 put: save1;
  			at: 2 put: 0.
+ 		^savedSize].
- 		^machineCodeSize].
  	reg := operands at: 1.
  	"If fetching RAX, fetch directly, otherwise, because of instruction encoding limitations, the register
  	 _must_ be fetched through RAX.  If reg = RBP or RSP simply fetch directly, otherwise swap RAX with
  	 the register before and after the fetch through RAX.  We avoid swapping before hand with RBP
  	 and RSP because setting RSP to whatever the contents of RAX is can cause disastrous results if
  	 an interrupt is delivered immediately after that point.  See mail threads beginning with
  		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-September/031428.html
  		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-October/031499.html"
  	(reg = RAX or: [reg = RBP or: [reg = RSP]])
  		ifTrue: [offset := 0]
  		ifFalse:
  			[machineCode
  				at: 0 put: (self rexR: 0 x: 0 b: reg);
  				at: 1 put: 16r90 + (reg \\ 8).
  			 offset := 2].
  	machineCode
  		at: 0 + offset put: 16r48;
  		at: 1 + offset put: 16rA1;
  		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
  		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
  		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
  		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
  		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
  		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
  	reg = RAX ifTrue:
+ 		[^10].
- 		[^machineCodeSize := 10].
  	"Now effect the assignment via xchg, which saves a byte over a move"
  	(reg = RBP or: [reg = RSP]) ifTrue:
  		[machineCode
  			at: 10 put: (self rexR: RAX x: 0 b: reg);
  			at: 11 put: 16r90 + (reg \\ 8).
+ 		^12].
- 		^machineCodeSize := 12].
  	machineCode
  		at: 12 put: (machineCode at: 0);
  		at: 13 put: (machineCode at: 1).
+ 	^14!
- 	^machineCodeSize := 14!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveC32R (in category 'generate machine code') -----
  concretizeMoveC32R
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: reg);
  		at: 1 put: 16rC7;
  		at: 2 put: (self mod: ModReg RM: reg RO: 0);
  		at: 3 put: (value bitAnd: 16rFF);
  		at: 4 put: (value >> 8 bitAnd: 16rFF);
  		at: 5 put: (value >> 16 bitAnd: 16rFF);
  		at: 6 put: (value >> 24 bitAnd: 16rFF).
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveCqR (in category 'generate machine code') -----
  concretizeMoveCqR
  	"Will get inlined into concretizeAt: switch.
  	 On x64 we can short-cut mov 0, reg using xor, and use signed 32-bit displacement, if possible."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	(self is32BitSignedImmediate: value) ifTrue:
  		[value = 0 ifTrue:
  			[machineCode
  				at: 0 put: (self rexR: reg x: 0 b: reg);
  				at: 1 put: 16r31;
  				at: 2 put: (self mod: ModReg RM: reg RO: reg).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		 machineCode
  			at: 0 put: (self rexR: 0 x: 0 b: reg);
  			at: 1 put: 16rC7;
  			at: 2 put: (self mod: ModReg RM: reg RO: 0);
  			at: 3 put: (value bitAnd: 16rFF);
  			at: 4 put: (value >> 8 bitAnd: 16rFF);
  			at: 5 put: (value >> 16 bitAnd: 16rFF);
  			at: 6 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^7].
- 		 ^machineCodeSize := 7].
  
  	machineCode
  		at:  0 put: (self rexR: 0 x: 0 b: reg);
  		at:  1 put: 16rB8 + (reg bitAnd: 7);
  		at:  2 put: (value bitAnd: 16rFF);
  		at:  3 put: (value >> 8 bitAnd: 16rFF);
  		at:  4 put: (value >> 16 bitAnd: 16rFF);
  		at:  5 put: (value >> 24 bitAnd: 16rFF);
  		at:  6 put: (value >> 32 bitAnd: 16rFF);
  		at:  7 put: (value >> 40 bitAnd: 16rFF);
  		at:  8 put: (value >> 48 bitAnd: 16rFF);
  		at:  9 put: (value >> 56 bitAnd: 16rFF).
+ 	^10!
- 	^machineCodeSize := 10!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveM16rR (in category 'generate machine code') -----
  concretizeMoveM16rR
  	"N.B. The Cogit compiler makes no assumption about the upper bits being set to zero.
  	 It will clear the register before hand if necessary."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 1 put: 16r0f;
  		at: 2 put: 16rb7.
  	(srcReg ~= RSP and: [srcReg ~= R12]) ifTrue:
  		[(offset = 0 and: [srcReg ~= RBP and: [srcReg ~= R13]]) ifTrue:
  			[machineCode
  				at: 3 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		 (self isQuick: offset) ifTrue:
  			[machineCode
  				at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 4 put: (offset bitAnd: 16rFF).
+ 			 ^5].
- 			 ^machineCodeSize := 5].
  		machineCode
  			at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 4 put: (offset bitAnd: 16rFF);
  			at: 5 put: (offset >> 8 bitAnd: 16rFF);
  			at: 6 put: (offset >> 16 bitAnd: 16rFF);
  			at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 		^8].
- 		^machineCodeSize := 8].
  	"RSP & R12:"
  	(offset = 0 and: [srcReg ~= RBP and: [srcReg ~= R13]]) ifTrue:
  		[machineCode
  			at: 3 put: (self mod: ModRegInd RM: srcReg RO: destReg);
  			at: 4 put: (self s: SIB1 i: 4 b: srcReg).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 5 put: (offset bitAnd: 16rFF).
+ 		 ^6].
- 		 ^machineCodeSize := 6].
  	machineCode
  		at: 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 4 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 5 put: (offset bitAnd: 16rFF);
  		at: 6 put: (offset >> 8 bitAnd: 16rFF);
  		at: 7 put: (offset >> 16 bitAnd: 16rFF);
  		at: 8 put: (offset >> 24 bitAnd: 16rFF).
+ 	^9!
- 	^machineCodeSize := 9!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveM32rR (in category 'generate machine code') -----
  concretizeMoveM32rR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset srcReg destReg skip |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [skip := 1. machineCode at: 0 put: (self rexw: false r: destReg x: 0 b: srcReg)].
  	machineCode
  		at: skip + 0 put: 16r8b.
  	offset = 0 ifTrue:
  		[(srcReg bitAnd: 6) ~= RSP ifTrue:
  			[machineCode at: skip + 1 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^skip + 2].
- 			 ^machineCodeSize := skip + 2].
  		 (srcReg bitAnd: 7) = RSP ifTrue: "RBP & R13 fall through"
  			[machineCode
  				at: skip + 1 put: (self mod: ModRegInd RM: srcReg RO: destReg);
  				at: skip + 2 put: (self s: SIB1 i: 4 b: srcReg).
+ 			 ^skip + 3]].
- 			 ^machineCodeSize := skip + 3]].
  	(self isQuick: offset) ifTrue:
  		[(srcReg bitAnd: 7) ~= RSP ifTrue:
  			[machineCode
  				at: skip + 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: skip + 2 put: (offset bitAnd: 16rFF).
+ 			 ^skip + 3].
- 			 ^machineCodeSize := skip + 3].
  		 machineCode
  			at: skip + 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: skip + 2 put: (self s: SIB1 i: 4 b: srcReg);
  			at: skip + 3 put: (offset bitAnd: 16rFF).
+ 		 ^skip + 4].
- 		 ^machineCodeSize := skip + 4].
  	machineCode at: skip + 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg).
  	(srcReg bitAnd: 7) = RSP ifTrue:
  		[machineCode at: skip + 2 put: (self s: SIB1 i: 4 b: srcReg).
  		 skip := skip + 1].
  	machineCode
  		at: skip + 2 put: (offset bitAnd: 16rFF);
  		at: skip + 3 put: (offset >> 8 bitAnd: 16rFF);
  		at: skip + 4 put: (offset >> 16 bitAnd: 16rFF);
  		at: skip + 5 put: (offset >> 24 bitAnd: 16rFF).
+ 	^skip + 6!
- 	^machineCodeSize := skip + 6!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveM32rRs (in category 'generate machine code') -----
  concretizeMoveM32rRs
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset srcReg destReg skip |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode at: 0 put: 16r66.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: destReg x: 0 b: srcReg)].
  	machineCode
  		at: skip + 1 put: 16r0f;
  		at: skip + 2 put: 16r6e.
  	offset = 0 ifTrue:
  		[(srcReg bitAnd: 6) ~= RSP ifTrue:
  			[machineCode at: skip + 3 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^skip + 4].
- 			 ^machineCodeSize := skip + 4].
  		 (srcReg bitAnd: 7) = RSP ifTrue: "RBP & R13 fall through"
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegInd RM: srcReg RO: destReg);
  				at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg).
+ 			 ^skip + 5]].
- 			 ^machineCodeSize := skip + 5]].
  	(self isQuick: offset) ifTrue:
  		[(srcReg bitAnd: 7) ~= RSP ifTrue:
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: skip + 4 put: (offset bitAnd: 16rFF).
+ 			 ^skip + 5].
- 			 ^machineCodeSize := skip + 5].
  		 machineCode
  			at: skip + 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg);
  			at: skip + 5 put: (offset bitAnd: 16rFF).
+ 		 ^skip + 6].
- 		 ^machineCodeSize := skip + 6].
  	machineCode at: skip + 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg).
  	(srcReg bitAnd: 7) = RSP ifTrue:
  		[machineCode at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg).
  		 skip := skip + 1].
  	machineCode
  		at: skip + 4 put: (offset bitAnd: 16rFF);
  		at: skip + 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: skip + 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: skip + 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^skip + 8!
- 	^machineCodeSize := skip + 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveM64rRd (in category 'generate machine code') -----
  concretizeMoveM64rRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset srcReg destReg skip |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode at: 0 put: 16rF3.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: destReg x: 0 b: srcReg)].
  	machineCode
  		at: skip + 1 put: 16r0f;
  		at: skip + 2 put: 16r7e.
  	offset = 0 ifTrue:
  		[(srcReg bitAnd: 6) ~= RSP ifTrue:
  			[machineCode at: skip + 3 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^skip + 4].
- 			 ^machineCodeSize := skip + 4].
  		 (srcReg bitAnd: 7) = RSP ifTrue: "RBP & R13 fall through"
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegInd RM: srcReg RO: destReg);
  				at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg).
+ 			 ^skip + 5]].
- 			 ^machineCodeSize := skip + 5]].
  	(self isQuick: offset) ifTrue:
  		[(srcReg bitAnd: 7) ~= RSP ifTrue:
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: skip + 4 put: (offset bitAnd: 16rFF).
+ 			 ^skip + 5].
- 			 ^machineCodeSize := skip + 5].
  		 machineCode
  			at: skip + 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg);
  			at: skip + 5 put: (offset bitAnd: 16rFF).
+ 		 ^skip + 6].
- 		 ^machineCodeSize := skip + 6].
  	machineCode at: skip + 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg).
  	(srcReg bitAnd: 7) = RSP ifTrue:
  		[machineCode at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg).
  		 skip := skip + 1].
  	machineCode
  		at: skip + 4 put: (offset bitAnd: 16rFF);
  		at: skip + 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: skip + 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: skip + 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^skip + 8!
- 	^machineCodeSize := skip + 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveMbrR (in category 'generate machine code') -----
  concretizeMoveMbrR
  	"N.B. The Cogit makes no assumption about the upper bits being set to zero because we
  	 deny byteReadsZeroExtend.  The cogit will clear the register before hand if necessary."
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 1 put: 16r8A.
  	(srcReg ~= RSP and: [srcReg ~= R12]) ifTrue:
  		[(offset = 0 and: [srcReg ~= RBP and: [srcReg ~= R13]]) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"RSP:"
  	offset = 0 ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegInd RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveMwrR (in category 'generate machine code') -----
  concretizeMoveMwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 1 put: 16r8B.
  	(srcReg ~= RSP and: [srcReg ~= R12]) ifTrue:
  		[(offset = 0 and: [srcReg ~= RBP and: [srcReg ~= R13]]) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"RSP:"
  	offset = 0 ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegInd RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRA32 (in category 'generate machine code') -----
  concretizeMoveRA32
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg offset |
  	reg := operands at: 0.
  	addressOperand := operands at: 1.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg = RAX
  		ifTrue: [offset := 0]
  		ifFalse:
  			[machineCode
  				at: 0 put: (self rexR: 0 x: 0 b: reg);
  				at: 1 put: 16r90 + (reg \\ 8).
  			 offset := 2].
  	machineCode
  		at: 0 + offset put: 16rA3;
  		at: 1 + offset put: (addressOperand bitAnd: 16rFF);
  		at: 2 + offset put: (addressOperand >>   8 bitAnd: 16rFF);
  		at: 3 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 4 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
  		at: 5 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
  		at: 6 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
  		at: 7 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
  		at: 8 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
  	reg = RAX ifTrue:
+ 		[^9].
- 		[^machineCodeSize := 9].
  	machineCode
  		at: 11 put: (machineCode at: 0);
  		at: 12 put: (machineCode at: 1).
+ 	^13!
- 	^machineCodeSize := 13!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRAb (in category 'generate machine code') -----
  concretizeMoveRAb
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| addressOperand reg offset save1 savedSize |
- 	| addressOperand reg offset save1 |
  	reg := operands at: 0.
  	addressOperand := operands at: 1.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
  		[save1 := operands at: 1.
  		 operands
  			at: 1 put: addressOperand - cogit varBaseAddress;
  			at: 2 put: RBX.
+ 		 savedSize := self concretizeMoveRMbr.
- 		 self concretizeMoveRMbr.
  		 operands
  			at: 1 put: save1;
  			at: 2 put: 0.
+ 		^savedSize].
- 		^machineCodeSize].
  	reg = RAX
  		ifTrue: [offset := 0]
  		ifFalse:
  			[machineCode
  				at: 0 put: (self rexR: 0 x: 0 b: reg);
  				at: 1 put: 16r90 + (reg \\ 8).
  			 offset := 2].
  	machineCode
  		at: 0 + offset put: 16r48;
  		at: 1 + offset put: 16rA2;
  		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
  		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
  		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
  		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
  		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
  		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
  	reg = RAX ifTrue:
+ 		[^10].
- 		[^machineCodeSize := 10].
  	machineCode
  		at: 12 put: (machineCode at: 0);
  		at: 13 put: (machineCode at: 1).
+ 	^14!
- 	^machineCodeSize := 14!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRAw (in category 'generate machine code') -----
  concretizeMoveRAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| addressOperand reg offset save1 savedSize |
- 	| addressOperand reg offset save1 |
  	reg := operands at: 0.
  	addressOperand := operands at: 1.
  	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	(self isAddressRelativeToVarBase: addressOperand) ifTrue:
  		[save1 := operands at: 1.
  		 operands
  			at: 1 put: addressOperand - cogit varBaseAddress;
  			at: 2 put: RBX.
+ 		 savedSize := self concretizeMoveRMwr.
- 		 self concretizeMoveRMwr.
  		 operands
  			at: 1 put: save1;
  			at: 2 put: 0.
+ 		^savedSize].
- 		^machineCodeSize].
  	"If storing RAX, store directly, otherwise, because of instruction encoding limitations, the register
  	 _must_ be stored through RAX.  If reg = RBP or RSP simply store directly, otherwise swap RAX with
  	 the register before and after the store through RAX.  We avoid sweapping before hand with RBP
  	 and RSP because setting RSP to whatever the contents of RAX is can cause disastrous results if
  	 an interrupt is delivered immediately after that point.  See mail threads beginning with
  		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-September/031428.html
  		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-October/031499.html"
  	(reg = RAX or: [reg = RBP or: [reg = RSP]])
  		ifTrue: [offset := 0]
  		ifFalse:
  			[(reg = RBP or: [reg = RSP])
  				ifTrue:
  					[machineCode
  						at: 0 put: (self rexR: reg x: 0 b: RAX);
  						at: 1 put: 16r89;
  						at: 2 put: (self mod: ModReg RM: RAX RO: reg).
  					 offset := 3]
  				ifFalse:
  					[machineCode
  						at: 0 put: (self rexR: RAX x: 0 b: reg);
  						at: 1 put: 16r90 + (reg \\ 8).
  					 offset := 2]].
  	machineCode
  		at: 0 + offset put: 16r48;
  		at: 1 + offset put: 16rA3;
  		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
  		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
  		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
  		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
  		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
  		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
  	reg = RAX ifTrue:
+ 		[^10].
- 		[^machineCodeSize := 10].
  	(reg = RBP or: [reg = RSP]) ifTrue:
+ 		[^13].
- 		[^machineCodeSize := 13].
  	"Now effect the assignment via xchg, which restores RAX"
  	machineCode
  		at: 12 put: (machineCode at: 0);
  		at: 13 put: (machineCode at: 1).
+ 	^14!
- 	^machineCodeSize := 14!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRM16r (in category 'generate machine code') -----
  concretizeMoveRM16r
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg skip |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	machineCode at: 0 put: 16r66.
  	(srcReg > 7 or: [destReg > 7])
  		ifTrue:
  			[machineCode at: 1 put: (self rexw: false r: srcReg x: 0 b: destReg).
  			 skip := 1]
  		ifFalse:
  			[skip := 0].
  	(destReg bitAnd: 7) ~= RSP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: skip + 1 put: 16r89;
  				at: skip + 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: skip + 3 put: (offset bitAnd: 16rFF).
+ 			 ^skip + 4].
- 			 ^machineCodeSize := skip + 4].
  		machineCode
  			at: skip + 1 put: 16r89;
  			at: skip + 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: skip + 3 put: (offset bitAnd: 16rFF);
  			at: skip + 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: skip + 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: skip + 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^skip + 7].
- 		^machineCodeSize := skip + 7].
  	"RSP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: skip + 1 put: 16r89;
  			at: skip + 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: skip + 3 put: (self s: SIB1 i: 4 b: destReg);
  			at: skip + 4 put: (offset bitAnd: 16rFF).
+ 		 ^skip + 5].
- 		 ^machineCodeSize := skip + 5].
  	machineCode
  		at: skip + 1 put: 16r89;
  		at: skip + 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: skip + 3 put: (self s: SIB1 i: 4 b: destReg);
  		at: skip + 4 put: (offset bitAnd: 16rFF);
  		at: skip + 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: skip + 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: skip + 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^skip + 8!
- 	^machineCodeSize := skip + 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRM32r (in category 'generate machine code') -----
  concretizeMoveRM32r
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset srcReg destReg skip |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [skip := 1. machineCode at: 0 put: (self rexw: false r: srcReg x: 0 b: destReg)].
  	machineCode
  		at: skip + 0 put: 16r89.
  	offset = 0 ifTrue:
  		[(destReg bitAnd: 6) ~= RSP ifTrue:
  			[machineCode at: skip + 1 put: (self mod: ModRegInd RM: destReg RO: srcReg).
+ 			 ^skip + 2].
- 			 ^machineCodeSize := skip + 2].
  		 (destReg bitAnd: 7) = RSP ifTrue: "RBP & R13 fall through"
  			[machineCode
  				at: skip + 1 put: (self mod: ModRegInd RM: destReg RO: srcReg);
  				at: skip + 2 put: (self s: SIB1 i: 4 b: destReg).
+ 			 ^skip + 3]].
- 			 ^machineCodeSize := skip + 3]].
  	(self isQuick: offset) ifTrue:
  		[(destReg bitAnd: 7) ~= RSP ifTrue:
  			[machineCode
  				at: skip + 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: skip + 2 put: (offset bitAnd: 16rFF).
+ 			 ^skip + 3].
- 			 ^machineCodeSize := skip + 3].
  		 machineCode
  			at: skip + 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: skip + 2 put: (self s: SIB1 i: 4 b: destReg);
  			at: skip + 3 put: (offset bitAnd: 16rFF).
+ 		 ^skip + 4].
- 		 ^machineCodeSize := skip + 4].
  	machineCode at: skip + 1 put: (self mod: ModRegRegDisp32  RM: destReg RO: srcReg).
  	(destReg bitAnd: 7) = RSP ifTrue:
  		[machineCode at: skip + 2 put: (self s: SIB1 i: 4 b: destReg).
  		 skip := skip + 1].
  	machineCode
  		at: skip + 2 put: (offset bitAnd: 16rFF);
  		at: skip + 3 put: (offset >> 8 bitAnd: 16rFF);
  		at: skip + 4 put: (offset >> 16 bitAnd: 16rFF);
  		at: skip + 5 put: (offset >> 24 bitAnd: 16rFF).
+ 	^skip + 6!
- 	^machineCodeSize := skip + 6!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRMbr (in category 'generate machine code') -----
  concretizeMoveRMbr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset baseReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	baseReg := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: srcReg x: 0 b: baseReg);
  		at: 1 put: 16r88.
  	(baseReg ~= RSP and: [baseReg ~= R12]) ifTrue:
  		[(offset = 0 and: [baseReg ~= RBP and: [baseReg ~= R13]]) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegInd RM: baseReg RO: srcReg).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		 (self isQuick: offset) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegRegDisp8 RM: baseReg RO: srcReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 2 put: (self mod: ModRegRegDisp32 RM: baseReg RO: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"RSP:"
  	offset = 0 ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegInd RM: baseReg RO: srcReg);
  			at: 3 put: (self s: SIB1 i: 4 b: baseReg).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegRegDisp8 RM: baseReg RO: srcReg);
  			at: 3 put: (self s: SIB1 i: 4 b: baseReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 2 put: (self mod: ModRegRegDisp32 RM: baseReg RO: srcReg);
  		at: 3 put: (self s: SIB1 i: 4 b: baseReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRMwr (in category 'generate machine code') -----
  concretizeMoveRMwr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: srcReg x: 0 b: destReg);
  		at: 1 put: 16r89.
  	(destReg ~= RSP and: [destReg ~= R12]) ifTrue:
  		[(offset = 0 and: [destReg ~= RBP and: [destReg ~= R13]]) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegInd RM: destReg RO: srcReg).
+ 			 ^3].
- 			 ^machineCodeSize := 3].
  		 (self isQuick: offset) ifTrue:
  			[machineCode
  				at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^4].
- 			 ^machineCodeSize := 4].
  		machineCode
  			at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^7].
- 		^machineCodeSize := 7].
  	"RSP:"
  	offset = 0 ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegInd RM: destReg RO: srcReg);
  			at: 3 put: (self s: SIB1 i: 4 b: destReg).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 3 put: (self s: SIB1 i: 4 b: destReg);
  			at: 4 put: (offset bitAnd: 16rFF).
+ 		 ^5].
- 		 ^machineCodeSize := 5].
  	machineCode
  		at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 3 put: (self s: SIB1 i: 4 b: destReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^8!
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRRd (in category 'generate machine code') -----
  concretizeMoveRRd
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16r66;
  		at: 1 put: (self rexR: destReg x: 0 b: srcReg);
  		at: 2 put: 16r0f;
  		at: 3 put: 16r6e;
  		at: 4 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRX32rR (in category 'generate machine code') -----
  concretizeMoveRX32rR
  	| index base src offset |
  	src := operands at: 0.
  	index := operands at: 1.
  	base := operands at: 2.
  	(index > 7 or: [base > 7 or: [src > 7]])
  		ifTrue:
  			[machineCode at: 0 put: (self rexw: false r: src x: index b: base).
  			 offset := 1]
  		ifFalse:
  			[offset := 0].
  	(base bitAnd: 7) ~= RBP ifTrue:
  		[machineCode
  			at: offset + 0 put: 16r89;
  			at: offset + 1 put: (self mod: ModRegInd RM: 4 RO: src);
  			at: offset + 2 put: (self s: SIB4 i: index b: base).
+ 		 ^offset + 3].
- 		 ^machineCodeSize := offset + 3].
  	machineCode
  		at: offset + 0 put: 16r89;
  		at: offset + 1 put: (self mod: ModRegRegDisp8 RM: 4 RO: src);
  		at: offset + 2 put: (self s: SIB4 i: index b: base);
  		at: offset + 3 put: 0.
+ 	 ^offset + 4!
- 	 ^machineCodeSize := offset + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRXbrR (in category 'generate machine code') -----
  concretizeMoveRXbrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| src index base offset |
  	src := operands at: 0.
  	index := operands at: 1.
  	base := operands at: 2.
  	offset := 0.
  	(src > 3 or: [base > 7 or: [index > 7]]) ifTrue:
  		[machineCode at: 0 put: (self rexR: src x: index b: base).
  		 offset := 1].
  	machineCode at: 0 + offset put: 16r88.
  	(base bitAnd: 7) ~= RBP "RBP,R13" ifTrue:
  		[machineCode
  			at: 1 + offset put: (self mod: ModRegInd RM: 4 RO: src);
  			at: 2 + offset put: (self s: SIB1 i: index b: base).
+ 		 ^3 + offset].
- 		 ^machineCodeSize := 3 + offset].
  	machineCode
  		at: 1 + offset put: (self mod: ModRegRegDisp8 RM: 4 RO: src);
  		at: 2 + offset put: (self s: SIB1 i: index b: base);
  		at: 3 + offset put: 0.
+ 	 ^4 + offset!
- 	 ^machineCodeSize := 4 + offset!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRXwrR (in category 'generate machine code') -----
  concretizeMoveRXwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| index base src |
  	src := operands at: 0.
  	index := operands at: 1.
  	base := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: src x: index b: base).
  	(base ~= RBP and: [base ~= R13]) ifTrue:
  		[machineCode
  			at: 1 put: 16r89;
  			at: 2 put: (self mod: ModRegInd RM: 4 RO: src);
  			at: 3 put: (self s: SIB8 i: index b: base).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 1 put: 16r89;
  		at: 2 put: (self mod: ModRegRegDisp8 RM: 4 RO: src);
  		at: 3 put: (self s: SIB8 i: index b: base);
  		at: 4 put: 0.
+ 	 ^5!
- 	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRdM64r (in category 'generate machine code') -----
  concretizeMoveRdM64r
  	<inline: true>
  	| offset srcReg destReg skip |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	machineCode at: 0 put: 16r66.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: srcReg x: 0 b: destReg)].
  	machineCode
  		at: skip + 1 put: 16r0f;
  		at: skip + 2 put: 16rd6.
  	offset = 0 ifTrue:
  		[(destReg bitAnd: 6) ~= RSP ifTrue:
  			[machineCode at: skip + 3 put: (self mod: ModRegInd RM: destReg RO: srcReg).
+ 			 ^skip + 4].
- 			 ^machineCodeSize := skip + 4].
  		 (destReg bitAnd: 7) = RSP ifTrue: "RBP & R13 fall through"
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegInd RM: destReg RO: srcReg);
  				at: skip + 4 put: (self s: SIB1 i: 4 b: destReg).
+ 			 ^skip + 5]].
- 			 ^machineCodeSize := skip + 5]].
  	(self isQuick: offset) ifTrue:
  		[(destReg bitAnd: 7) ~= RSP ifTrue:
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: skip + 4 put: (offset bitAnd: 16rFF).
+ 			 ^skip + 5].
- 			 ^machineCodeSize := skip + 5].
  		 machineCode
  			at: skip + 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: skip + 4 put: (self s: SIB1 i: 4 b: destReg);
  			at: skip + 5 put: (offset bitAnd: 16rFF).
+ 		 ^skip + 6].
- 		 ^machineCodeSize := skip + 6].
  	machineCode at: skip + 3 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg).
  	(destReg bitAnd: 7) = RSP ifTrue:
  		[machineCode at: skip + 4 put: (self s: SIB1 i: 4 b: destReg).
  		 skip := skip + 1].
  	machineCode
  		at: skip + 4 put: (offset bitAnd: 16rFF);
  		at: skip + 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: skip + 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: skip + 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^skip + 8!
- 	^machineCodeSize := skip + 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRdR (in category 'generate machine code') -----
  concretizeMoveRdR
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16r66;
  		at: 1 put: (self rexR: srcReg x: 0 b: destReg);
  		at: 2 put: 16r0f;
  		at: 3 put: 16r7e;
  		at: 4 put: (self mod: ModReg RM: destReg RO: srcReg).
+ 	^5!
- 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRdRd (in category 'generate machine code') -----
  concretizeMoveRdRd
  	"Will get inlined into concretizeAt: switch."
  	"MOVSD"
  	<inline: true>
  	| srcReg destReg skip |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: srcReg x: 0 b: destReg)].
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r11;
  		at: skip + 3 put: (self mod: ModReg RM: destReg RO: srcReg).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRsM32r (in category 'generate machine code') -----
  concretizeMoveRsM32r
  	<inline: true>
  	| offset srcReg destReg skip |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
  	destReg := operands at: 2.
  	machineCode at: 0 put: 16r66.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: srcReg x: 0 b: destReg)].
  	machineCode
  		at: skip + 1 put: 16r0f;
  		at: skip + 2 put: 16r7e.
  	offset = 0 ifTrue:
  		[(destReg bitAnd: 6) ~= RSP ifTrue:
  			[machineCode at: skip + 3 put: (self mod: ModRegInd RM: destReg RO: srcReg).
+ 			 ^skip + 4].
- 			 ^machineCodeSize := skip + 4].
  		 (destReg bitAnd: 7) = RSP ifTrue: "RBP & R13 fall through"
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegInd RM: destReg RO: srcReg);
  				at: skip + 4 put: (self s: SIB1 i: 4 b: destReg).
+ 			 ^skip + 5]].
- 			 ^machineCodeSize := skip + 5]].
  	(self isQuick: offset) ifTrue:
  		[(destReg bitAnd: 7) ~= RSP ifTrue:
  			[machineCode
  				at: skip + 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: skip + 4 put: (offset bitAnd: 16rFF).
+ 			 ^skip + 5].
- 			 ^machineCodeSize := skip + 5].
  		 machineCode
  			at: skip + 3 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: skip + 4 put: (self s: SIB1 i: 4 b: destReg);
  			at: skip + 5 put: (offset bitAnd: 16rFF).
+ 		 ^skip + 6].
- 		 ^machineCodeSize := skip + 6].
  	machineCode at: skip + 3 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg).
  	(destReg bitAnd: 7) = RSP ifTrue:
  		[machineCode at: skip + 4 put: (self s: SIB1 i: 4 b: destReg).
  		 skip := skip + 1].
  	machineCode
  		at: skip + 4 put: (offset bitAnd: 16rFF);
  		at: skip + 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: skip + 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: skip + 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^skip + 8!
- 	^machineCodeSize := skip + 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRsRs (in category 'generate machine code') -----
  concretizeMoveRsRs
  	"Will get inlined into concretizeAt: switch."
  	"MOVSS"
  	<inline: true>
  	| srcReg destReg skip |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: srcReg x: 0 b: destReg)].
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r11;
  		at: skip + 3 put: (self mod: ModReg RM: destReg RO: srcReg).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveX32rRR (in category 'generate machine code') -----
  concretizeMoveX32rRR
  	"MoveX32rRR is expected to zero-extend, so explicitly zero the destination."
  	| index base dest offset |
  	index := operands at: 0.
  	base := operands at: 1.
  	dest := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: dest x: 0 b: dest);
  		at: 1 put: 16r31;
  		at: 2 put: (self mod: ModReg RM: dest RO: dest).
  	(index > 7 or: [base > 7 or: [dest > 7]])
  		ifTrue:
  			[machineCode at: 3 put: (self rexw: false r: dest x: index b: base).
  			 offset := 1]
  		ifFalse:
  			[offset := 0].
  	(base bitAnd: 7) ~= RBP ifTrue:
  		[machineCode
  			at: offset + 3 put: 16r8B;
  			at: offset + 4 put: (self mod: ModRegInd RM: 4 RO: dest);
  			at: offset + 5 put: (self s: SIB4 i: index b: base).
+ 		 ^offset + 6].
- 		 ^machineCodeSize := offset + 6].
  	machineCode
  		at: offset + 3 put: 16r8B;
  		at: offset + 4 put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
  		at: offset + 5 put: (self s: SIB4 i: index b: base);
  		at: offset + 6 put: 0.
+ 	 ^offset + 7!
- 	 ^machineCodeSize := offset + 7!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveXbrRR (in category 'generate machine code') -----
  concretizeMoveXbrRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| index base dest |
  	index := operands at: 0.
  	base := operands at: 1.
  	dest := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: dest x: index b: base);
  		at: 1 put: 16r8A.
  	(base ~= RBP and: [base ~= R13]) ifTrue:
  		[machineCode
  			at: 2 put: (self mod: ModRegInd RM: 4 RO: dest);
  			at: 3 put: (self s: SIB1 i: index b: base).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 2 put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
  		at: 3 put: (self s: SIB1 i: index b: base);
  		at: 4 put: 0.
+ 	 ^5!
- 	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveXwrRR (in category 'generate machine code') -----
  concretizeMoveXwrRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| index base dest |
  	index := operands at: 0.
  	base := operands at: 1.
  	dest := operands at: 2.
  	machineCode
  		at: 0 put: (self rexR: dest x: index b: base).
  	(base ~= RBP and: [base ~= R13]) ifTrue:
  		[machineCode
  			at: 1 put: 16r8B;
  			at: 2 put: (self mod: ModRegInd RM: 4 RO: dest);
  			at: 3 put: (self s: SIB8 i: index b: base).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	machineCode
  		at: 1 put: 16r8B;
  		at: 2 put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
  		at: 3 put: (self s: SIB8 i: index b: base);
  		at: 4 put: 0.
+ 	 ^5!
- 	 ^machineCodeSize := 5!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMulRR (in category 'generate machine code') -----
  concretizeMulRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg1 reg2 |
  	reg1 := operands at: 0.
  	reg2 := operands at: 1.
  	machineCode
  		at: 0 put: (self rexR: reg2 x: 0 b: reg1);
  		at: 1 put: 16r0F;
  		at: 2 put: 16rAF;
  		at: 3 put: (self mod: ModReg RM: reg1 RO: reg2).
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeNegateR (in category 'generate machine code') -----
  concretizeNegateR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: reg);
  		at: 1 put: 16rF7;
  		at: 2 put: (self mod: ModReg RM: reg RO: 3).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeNop (in category 'generate machine code') -----
  concretizeNop
  	<inline: true>
  	machineCode at: 0 put: 16r90.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeOpRR: (in category 'generate machine code') -----
  concretizeOpRR: x64opcode
  	| regLHS regRHS |
  	regLHS := operands at: 0.
  	regRHS := operands at: 1.
  	machineCode
  		at: 0 put: (self rexR: regRHS x: 0 b: regLHS);
  		at: 1 put: x64opcode;
  		at: 2 put: (self mod: ModReg RM: regLHS RO: regRHS).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizePopR (in category 'generate machine code') -----
  concretizePopR
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	reg < 8 ifTrue:
  		[machineCode at: 0 put: 16r58 + reg.
+ 		^1].
- 		^machineCodeSize := 1].
  	machineCode
  		at: 0 put: 16r41;
  		at: 1 put: 16r58 + (reg - 8).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogX64Compiler>>concretizePrefetchAw (in category 'generate machine code') -----
  concretizePrefetchAw
  	"We support only prefetches for addresses that are variables relative to VarBase"
  	| operand offset |
  	operand := operands at: 0.
  	(self isAddressRelativeToVarBase: operand) ifFalse:
+ 		[^0].
- 		[^machineCodeSize := 0].
  	offset := operand - cogit varBaseAddress.
  	machineCode
  		at: 0 put: 16r0f;
  		at: 1 put: 16r18;
  		at: 2 put: 16r93;
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 16 bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: offset >> 24.
+ 	^7!
- 	^machineCodeSize := 7!

Item was changed:
  ----- Method: CogX64Compiler>>concretizePushCq (in category 'generate machine code') -----
  concretizePushCq
  	<inline: true>
  	| value |
  	value := operands at: 0.
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 0 put: 16r6A;
  			at: 1 put: (value bitAnd: 16rFF).
+ 		^2].
- 		^machineCodeSize := 2].
  	(self is32BitSignedImmediate: value) ifTrue:
  		[machineCode
  			at: 0 put: 16r68;
  			at: 1 put: (value bitAnd: 16rFF);
  			at: 2 put: (value >> 8 bitAnd: 16rFF);
  			at: 3 put: (value >> 16 bitAnd: 16rFF);
  			at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 		^5].
- 		^machineCodeSize := 5].
  	^self concretizePushCw!

Item was changed:
  ----- Method: CogX64Compiler>>concretizePushR (in category 'generate machine code') -----
  concretizePushR
  	<inline: true>
  	| reg |
  	reg := operands at: 0.
  	reg < 8 ifTrue:
  		[machineCode at: 0 put: 16r50 + reg.
+ 		^1].
- 		^machineCodeSize := 1].
  	machineCode
  		at: 0 put: 16r41;
  		at: 1 put: 16r50 + (reg - 8).
+ 	^2!
- 	^machineCodeSize := 2!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeREP (in category 'generate machine code') -----
  concretizeREP
  	<inline: true>
  	machineCode at: 0 put: 16rF3.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeRetN (in category 'generate machine code') -----
  concretizeRetN
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset |
  	offset := operands at: 0.
  	offset = 0 ifTrue:
  		[machineCode at: 0 put: 16rC3.
+ 		^1].
- 		^machineCodeSize := 1].
  	machineCode
  		at: 0 put: 16rC2;
  		at: 1 put: (offset bitAnd: 16rFF);
  		at: 2 put: (offset >> 8).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeReverseOpRR: (in category 'generate machine code') -----
  concretizeReverseOpRR: x64opcode
  	| regLHS regRHS |
  	"CmpRR/MoveRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode
  		at: 0 put: (self rexR: regRHS x: 0 b: regLHS);
  		at: 1 put: x64opcode;
  		at: 2 put: (self mod: ModReg RM: regLHS RO: regRHS).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeSEE2OpRdRd: (in category 'generate machine code') -----
  concretizeSEE2OpRdRd: x64opcode
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS skip |
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode
  		at: 0 put: 16rF2.
  	(regLHS <= 7 and: [regRHS <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: regLHS x: 0 b: regRHS)].
  	machineCode 
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: x64opcode;
  		at: skip + 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeSEEOpRsRs: (in category 'generate machine code') -----
  concretizeSEEOpRsRs: x64opcode
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS skip |
  	regRHS := operands at: 0.
  	regLHS := operands at: 1.
  	machineCode
  		at: 0 put: 16rF3.
  	(regLHS <= 7 and: [regRHS <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: regLHS x: 0 b: regRHS)].
  	machineCode 
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: x64opcode;
  		at: skip + 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeShiftCqRegOpcode: (in category 'generate machine code') -----
  concretizeShiftCqRegOpcode: regOpcode
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| distance reg |
  	distance := operands at: 0.
  	self assert: (distance between: 1 and: 63).
  	reg := operands at: 1.
  	machineCode at: 0 put: (self rexR: 0 x: 0 b: reg).
  	distance = 1 ifTrue:
  		[machineCode
  			at: 1 put: 16rD1;
  			at: 2 put: (self mod: ModReg RM: reg RO: regOpcode).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	machineCode
  		at: 1 put: 16rC1;
  		at: 2 put: (self mod: ModReg RM: reg RO: regOpcode);
  		at: 3 put: distance.
+ 	^4!
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeShiftRegRegOpcode: (in category 'generate machine code') -----
  concretizeShiftRegRegOpcode: regOpcode
  	"On the x64 the only instructions that shift by the value of a
  	 register require the shift count to be  in %ecx.  So we may
  	 have to use swap instructions to get the count into %ecx."
  	<inline: true>
  	| shiftCountReg destReg regToShift |
  	shiftCountReg := operands at: 0.
  	destReg := operands at: 1.
  	shiftCountReg = RCX ifTrue:
  		[machineCode
  			at: 0 put: (self rexR: 0 x: 0 b: destReg);
  			at: 1 put: 16rD3;
  			at: 2 put: (self mod: ModReg RM: destReg RO: regOpcode).
+ 		 ^3].
- 		 ^machineCodeSize := 3].
  	regToShift := destReg = shiftCountReg
  					ifTrue: [RCX]
  					ifFalse: [destReg = RCX
  								ifTrue: [shiftCountReg]
  								ifFalse: [destReg]].
  	shiftCountReg = RAX ifTrue:
  		[machineCode
  			at: 0 put: 16r48;
  			at: 1 put: 16r90 + RCX; "XCHG RAX,RCX"
  			at: 2 put: (self rexR: 0 x: 0 b: regToShift);
  			at: 3 put: 16rD3;			"SAR RCX,RAX"
  			at: 4 put: (self mod: ModReg RM: regToShift RO: regOpcode);
  			at: 5 put: 16r48;
  			at: 6 put: 16r90 + RCX. "XCHG RAX,RCX"
+ 		 ^7].
- 		 ^machineCodeSize := 7].
  	machineCode
  		at: 0 put: (self rexR: shiftCountReg x: 0 b: RCX);		"XCHG R?X,RCX"
  		at: 1 put: 16r87;
  		at: 2 put: (self mod: ModReg RM: RCX RO: shiftCountReg);
  		at: 3 put: (self rexR: 0 x: 0 b: regToShift);			"SAR RCX,R!!X"
  		at: 4 put: 16rD3;
  		at: 5 put: (self mod: ModReg RM: regToShift RO: regOpcode);
  		at: 6 put: (self rexR: shiftCountReg x: 0 b: RCX);		"XCHG R?X,RCX"
  		at: 7 put: 16r87;
  		at: 8 put: (self mod: ModReg RM: RCX RO: shiftCountReg).
+ 	^9!
- 	^machineCodeSize := 9!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeSignExtend16RR (in category 'generate machine code') -----
  concretizeSignExtend16RR
  	"Will get inlined into concretizeAt: switch."
  	"movsxwq"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexw: true r: destReg x: 0 b: srcReg);
  		at: 1 put: 16r0F;
  		at: 2 put: 16rBF;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 4!
- 	^ machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeSignExtend32RR (in category 'generate machine code') -----
  concretizeSignExtend32RR
  	"Will get inlined into concretizeAt: switch."
  	"movsxdq"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexw: true r: destReg x: 0 b: srcReg);
  		at: 1 put: 16r63;
  		at: 2 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 3!
- 	^ machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeSignExtend8RR (in category 'generate machine code') -----
  concretizeSignExtend8RR
  	"Will get inlined into concretizeAt: switch."
  	"movsxbq"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexw: true r: destReg x: 0 b: srcReg);
  		at: 1 put: 16r0F;
  		at: 2 put: 16rBE;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 4!
- 	^ machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeSqrtRd (in category 'generate machine code') -----
  concretizeSqrtRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg skip |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rF2.
  	(reg <= 7)
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: reg x: 0 b: reg)].
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r51;
  		at: skip + 3 put: (self mod: ModReg RM: reg RO: reg).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeSqrtRs (in category 'generate machine code') -----
  concretizeSqrtRs
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| reg skip |
  	reg := operands at: 0.
  	machineCode
  		at: 0 put: 16rF3.
  	(reg <= 7)
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: reg x: 0 b: reg)].
  	machineCode
  		at: skip + 1 put: 16r0F;
  		at: skip + 2 put: 16r51;
  		at: skip + 3 put: (self mod: ModReg RM: reg RO: reg).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeStop (in category 'generate machine code') -----
  concretizeStop
  	<inline: true>
  	machineCode at: 0 put: 16rCC.
+ 	^1!
- 	^machineCodeSize := 1!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeTstCqR (in category 'generate machine code') -----
  concretizeTstCqR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| value reg |
  	value := operands at: 0.
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexR: 0 x: 0 b: reg).
  	(self isQuick: value) ifTrue:
  		[machineCode
  			at: 1 put: 16rF6;
  			at: 2 put: (self mod: ModReg RM: reg RO: 0);
  			at: 3 put: (value bitAnd: 16rFF).
+ 		 ^4].
- 		 ^machineCodeSize := 4].
  	
  	(self is32BitSignedImmediate: value) ifTrue:
  		[reg = RAX ifTrue:
  			[machineCode
  				at: 1 put: 16rA9;
  				at: 2 put: (value bitAnd: 16rFF);
  				at: 3 put: (value >> 8 bitAnd: 16rFF);
  				at: 4 put: (value >> 16 bitAnd: 16rFF);
  				at: 5 put: (value >> 24 bitAnd: 16rFF).
+ 			 ^6].
- 			 ^machineCodeSize := 6].
  		machineCode
  			at: 1 put: 16rF7;
  			at: 2 put: (self mod: ModReg RM: reg RO: 0);
  			at: 3 put: (value bitAnd: 16rFF);
  			at: 4 put: (value >> 8 bitAnd: 16rFF);
  			at: 5 put: (value >> 16 bitAnd: 16rFF);
  			at: 6 put: (value >> 24 bitAnd: 16rFF).
+ 		 ^7].
- 		 ^machineCodeSize := 7].
  	^self concretizeArithCwR: 16r85!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeXCHGRR (in category 'generate machine code') -----
  concretizeXCHGRR
  	| r1 r2 |
  	r1 := operands at: 0.
  	r2 := operands at: 1.
  	r2 = RAX ifTrue:
  		[r2 := r1. r1 := RAX].
  	r1 = RAX ifTrue:
  		[machineCode
  			at: 0 put: (self rexR: 0 x: 0 b: r2);
  			at: 1 put: 16r90 + (r2 \\ 8).
+ 		 ^2].
- 		 ^machineCodeSize := 2].
  	machineCode
  		at: 0 put: (self rexR: r1 x: 0 b: r2);
  		at: 1 put: 16r87;
  		at: 2 put: (self mod: ModReg RM: r2 RO: r1).
+ 	^3!
- 	^machineCodeSize := 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeXorRdRd (in category 'generate machine code') -----
  concretizeXorRdRd
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS skip |
  	regRHS := self operands at: 0.
  	regLHS := self operands at: 1.
  	machineCode
  		at: 0 put: 16r66.
  	(regLHS <= 7 and: [regRHS <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: regLHS x: 0 b: regRHS)].
  	machineCode
  		at: skip + 1 put: 16r0f;
  		at: skip + 2 put: 16r57;
  		at: skip + 3 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^skip + 4!
- 	^machineCodeSize := skip + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeXorRsRs (in category 'generate machine code') -----
  concretizeXorRsRs
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regLHS regRHS skip |
  	regRHS := self operands at: 0.
  	regLHS := self operands at: 1.
  	machineCode
  		at: 0 put: 16r0F.
  	(regLHS <= 7 and: [regRHS <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: regLHS x: 0 b: regRHS)].
  	
  	machineCode	
  		at: skip + 1 put: 16r57;
  		at: skip + 2 put: (self mod: ModReg RM: regRHS RO: regLHS).
+ 	^skip + 3!
- 	^machineCodeSize := skip + 3!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeZeroExtend16RR (in category 'generate machine code') -----
  concretizeZeroExtend16RR
  	"Will get inlined into concretizeAt: switch."
  	"movzxwq"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexw: true r: destReg x: 0 b: srcReg);
  		at: 1 put: 16r0F;
  		at: 2 put: 16rB7;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 4!
- 	^ machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeZeroExtend32RR (in category 'generate machine code') -----
  concretizeZeroExtend32RR
  	"Will get inlined into concretizeAt: switch."
  	"movzxbq"
  	<inline: true>
  	| srcReg destReg skip |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	(srcReg <= 7 and: [destReg <= 7])
  		ifTrue: [skip := 0]
  		ifFalse: [skip := 1. machineCode at: 0 put: (self rexw: false r: destReg x: 0 b: srcReg)].
  		
  	machineCode
  		at: skip + 0 put: 16r8b;
  		at: skip + 1 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ skip + 2!
- 	^ machineCodeSize := skip + 2!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeZeroExtend8RR (in category 'generate machine code') -----
  concretizeZeroExtend8RR
  	"Will get inlined into concretizeAt: switch."
  	"movzxbq"
  	<inline: true>
  	| srcReg destReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	machineCode
  		at: 0 put: (self rexw: true r: destReg x: 0 b: srcReg);
  		at: 1 put: 16r0F;
  		at: 2 put: 16rB6;
  		at: 3 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	^ 4!
- 	^ machineCodeSize := 4!

Item was changed:
  ----- Method: CogX64Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
- 	<returnTypeC: #void>
  	opcode >= CDQ ifTrue:
  		[^self dispatchConcretizeProcessorSpecific].
+ 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill32]				-> [^self concretizeFill32].
  		[Nop]				-> [^self concretizeNop].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallR]					-> [^self concretizeCallR].
  		[CallFull]				-> [^self concretizeCallFull].
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpFull].
  		[JumpLong]				-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeArithCqRWithRO: 0 raxOpcode: 15r05].
  		[AddcCqR]					-> [^self concretizeArithCqRWithRO: 2 raxOpcode: 15r15].
  		[AddCwR]					-> [^self concretizeArithCwR: 16r03].
  		[AddRR]						-> [^self concretizeOpRR: 16r03].
  		[AddRsRs]					-> [^self concretizeSEEOpRsRs: 16r58].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeArithCqRWithRO: 4 raxOpcode: 16r25].
  		[AndCwR]					-> [^self concretizeArithCwR: 16r23].
  		[AndRR]						-> [^self concretizeOpRR: 16r23].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeArithCqRWithRO: 7 raxOpcode: 16r3D].
  		[CmpCwR]					-> [^self concretizeArithCwR: 16r39].
  		[CmpC32R]					-> [^self concretizeCmpC32R].
  		[CmpRR]					-> [^self concretizeReverseOpRR: 16r39].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[CmpRsRs]					-> [^self concretizeCmpRsRs].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[DivRsRs]					-> [^self concretizeSEEOpRsRs: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[MulRsRs]					-> [^self concretizeSEEOpRsRs: 16r59].
  		[OrCqR]						-> [^self concretizeArithCqRWithRO: 1 raxOpcode: 16r0D].
  		[OrCwR]					-> [^self concretizeArithCwR: 16r0B].
  		[OrRR]						-> [^self concretizeOpRR: 16r0B].
  		[SubCqR]					-> [^self concretizeArithCqRWithRO: 5 raxOpcode: 16r2D].
  		[SubbCqR]					-> [^self concretizeArithCqRWithRO: 3 raxOpcode: 16r1D].
  		[SubCwR]					-> [^self concretizeArithCwR: 16r2B].
  		[SubRR]						-> [^self concretizeOpRR: 16r2B].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SubRsRs]					-> [^self concretizeSEEOpRsRs: 16r5C].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[SqrtRs]					-> [^self concretizeSqrtRs].
  		[XorCwR]					-> [^self concretizeArithCwR: 16r33].
  		[XorRR]						-> [^self concretizeOpRR: 16r33].
  		[XorRdRd]						-> [^self concretizeXorRdRd].
  		[XorRsRs]						-> [^self concretizeXorRsRs].
  		[NegateR]					-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[RotateLeftCqR]				-> [^self concretizeShiftCqRegOpcode: 0].
  		[RotateRightCqR]				-> [^self concretizeShiftCqRegOpcode: 1].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeShiftCqRegOpcode: 7].
  		[LogicalShiftRightCqR]			-> [^self concretizeShiftCqRegOpcode: 5].
  		[LogicalShiftLeftCqR]			-> [^self concretizeShiftCqRegOpcode: 4].
  		[ArithmeticShiftRightRR]			-> [^self concretizeShiftRegRegOpcode: 7].
  		[LogicalShiftLeftRR]				-> [^self concretizeShiftRegRegOpcode: 4].
  		[ClzRR]						-> [^self concretizeClzRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveC32R]		-> [^self concretizeMoveC32R].
  		[MoveRR]			-> [^self concretizeReverseOpRR: 16r89].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveA32R]		-> [^self concretizeMoveA32R].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveRA32]		-> [^self concretizeMoveRA32].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM8rR]		-> [^self concretizeMoveMbrR].
  		[MoveRM8r]		-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM32rR]		-> [^self concretizeMoveM32rR].
  		[MoveM32rRs]		-> [^self concretizeMoveM32rRs].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveX32rRR]		-> [^self concretizeMoveX32rRR].
  		[MoveRX32rR]		-> [^self concretizeMoveRX32rR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRM32r]		-> [^self concretizeMoveRM32r].
  		[MoveRsM32r]		-> [^self concretizeMoveRsM32r].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[MoveRdR]			-> [^self concretizeMoveRdR].
  		[MoveRRd]			-> [^self concretizeMoveRRd].
  		[MoveRdRd]		-> [^self concretizeMoveRdRd].
  		[MoveRsRs]		-> [^self concretizeMoveRsRs].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		[ConvertRdR]		-> [^self concretizeConvertRdR].
  		[ConvertRRs]		-> [^self concretizeConvertRRs].
  		[ConvertRsR]		-> [^self concretizeConvertRsR].
  		[ConvertRsRd]	-> [^self concretizeConvertRsRd].
  		[ConvertRdRs]	-> [^self concretizeConvertRdRs].
  			
  		[SignExtend8RR]		-> [^self concretizeSignExtend8RR].
  		[SignExtend16RR]	-> [^self concretizeSignExtend16RR].
  		[SignExtend32RR]	-> [^self concretizeSignExtend32RR].
  		
  		[ZeroExtend8RR]		-> [^self concretizeZeroExtend8RR].
  		[ZeroExtend16RR]	-> [^self concretizeZeroExtend16RR].
  		[ZeroExtend32RR]	-> [^self concretizeZeroExtend32RR].
+ 		}.
+ 
+ 	^0 "keep Slang happy"!
- 		}!

Item was changed:
  ----- Method: CogX64Compiler>>dispatchConcretizeProcessorSpecific (in category 'generate machine code') -----
  dispatchConcretizeProcessorSpecific
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is part of the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the number of literals limits in the SqueakV3 (blue book derived)
  	 bytecode set."
- 	<returnTypeC: #void>
  	opcode caseOf: {
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		"[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR]."
  		"[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR]."
  		"[LFENCE]				-> [^self concretizeFENCE: 5]."
  		"[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7]."
  		"[LOCK]					-> [^self concretizeLOCK]."
  		"[XCHGAwR]				-> [^self concretizeXCHGAwR]."
  		"[XCHGMwrR]			-> [^self concretizeXCHGMwrR]."
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		[REP]					-> [^self concretizeREP].
  		[CLD]					-> [^self concretizeCLD].
  		[MOVSB]				-> [^self concretizeMOVSB].
  		[MOVSQ]				-> [^self concretizeMOVSQ].
  		[BSR]					-> [^self concretizeBSR].
  	}!

Item was changed:
  ----- Method: VMMaker>>options: (in category 'initialize') -----
  options: anArrayOfPairs
  	self assert: anArrayOfPairs size even.
  	1 to: anArrayOfPairs size by: 2 do:
  		[:i| | key |
  		key := anArrayOfPairs at: i.
  		self assert: key isSymbol.
+ 		optionsDictionary at: key put: (anArrayOfPairs at: i + 1)].
+ 	"Now clear any stale/broken options in the actual InitializationOptions variable..."
+ 	VMClass initializeWithOptions: optionsDictionary!
- 		optionsDictionary at: key put: (anArrayOfPairs at: i + 1)]!



More information about the Vm-dev mailing list