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

commits at source.squeak.org commits at source.squeak.org
Sun Apr 19 16:01:09 UTC 2015


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

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

Name: VMMaker.oscog-eem.1218
Author: eem
Time: 19 April 2015, 8:59:15.182 am
UUID: dd01c3b2-8eeb-4c53-b402-006d691908c6
Ancestors: VMMaker.oscog-eem.1217

First cut at changing ARM call/branch ranges to use
immediate call/jump for all intra-zone transfers,
and clumsy 5 instruction sequences only for
trampoline and interpreter primitive calls.

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

Item was changed:
  ----- Method: CogARMCompiler>>callInstructionByteSize (in category 'accessing') -----
  callInstructionByteSize
+ 	"ARM calls and jumps span +/- 32 mb, more than enough for intra-zone calls and jumps."
- 	"we only get to use quick B[LX] calls. We hope"
  	^4!

Item was changed:
  ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Because we don't use Thumb, each ARM instruction has 4 bytes. Some abstract opcodes need more than one instruction. We only handle those in this caseOf: and let the default return 4"
  	
- 	(opcode between: FirstShortJump and: LastJump) ifTrue:
- 		[^maxSize := 16].
- 	
  	opcode
  		caseOf: {
+ 			"Noops & Pseudo Ops"
  			[Label]					-> [^maxSize := 0].
  			[AlignmentNops]		-> [^maxSize := (operands at: 0) - 1].
+ 			"Specific Control/Data Movement"
+ 			[BICCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 			[MoveAwR]				-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 0))
- 														ifTrue: [4]
- 														ifFalse: [20]].
- 			[MoveCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			"Control"
+ 			[CallFull]				-> [^maxSize := 20].
+ 			[JumpFull]				-> [^maxSize := 20].
- 											ifFalse: [maxSize := 16]].
- 			[MoveCwR]				-> [^maxSize := 16].
- 			[MoveRAw]				-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 1))
- 														ifTrue: [4]
- 														ifFalse: [20]].
- 			[MoveRMwr]			-> [self is12BitValue: (operands at: 1)
- 											ifTrue: [ :u :i | ^maxSize := 4]
- 											ifFalse: [ ^maxSize := 20 ]].
- 			[MoveRMbr]				-> [self is12BitValue: (operands at: 1)
- 											ifTrue: [ :u :i | ^maxSize := 4]
- 											ifFalse: [ ^maxSize := 20 ]].
- 			[MoveMwrR]			-> [self is12BitValue: (operands at: 0)
- 											ifTrue: [ :u :i | ^maxSize := 4]
- 											ifFalse: [ ^maxSize := 20 ]].
- 			[MoveMbrR]				-> [self is12BitValue: (operands at: 0)
- 											ifTrue: [ :u :i | ^maxSize := 4]
- 											ifFalse: [ ^maxSize := 20 ]].
- 			[PrefetchAw] 			-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 1))
- 														ifTrue: [4]
- 														ifFalse: [20]].
- 			[Call]					-> [^maxSize := 20 "recomputed in #sizePCDependentInstruction."].
  			[RetN]					-> [^(operands at: 0) = 0 
  											ifTrue: [maxSize := 4]
  											ifFalse: [maxSize := 8]].
+ 			"Arithmetic"
  			[CmpCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
  			[AddCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
+ 			[AndCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 			[BICCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
  			[SubCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
- 			[AndCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := 20]].
  			[AndCqRR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
  			[OrCqR]					-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
  			[TstCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
  			[XorCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
- 			[CmpCwR]				-> [^maxSize := 20].
  			[AddCwR]				-> [^maxSize := 20].
- 			[SubCwR]				-> [^maxSize := 20].
  			[AndCwR]				-> [^maxSize := 20].
+ 			[CmpCwR]				-> [^maxSize := 20].
  			[OrCwR]				-> [^maxSize := 20].
+ 			[SubCwR]				-> [^maxSize := 20].
  			[XorCwR]				-> [^maxSize := 20].
- 			[JumpR]					-> [^maxSize := 4].
- 			[JumpFPEqual]			-> [^maxSize := 8].
- 			[JumpFPNotEqual]		-> [^maxSize := 8].
- 			[JumpFPLess]			-> [^maxSize := 8].
- 			[JumpFPGreaterOrEqual]-> [^maxSize := 8].
- 			[JumpFPGreater]		-> [^maxSize := 8].
- 			[JumpFPLessOrEqual]	-> [^maxSize := 8].
- 			[JumpFPOrdered]		-> [^maxSize := 8].
- 			[JumpFPUnordered]		-> [^maxSize := 8].
- 			[JumpLong]				-> [^maxSize := 20].
- 			[JumpLongZero]		-> [^maxSize := 20].
- 			[JumpLongNonZero]	-> [^maxSize := 20].
  			[LoadEffectiveAddressMwrR]
  									-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
+ 			"Data Movement"
+ 			[MoveAwR]				-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 0))
+ 														ifTrue: [4]
+ 														ifFalse: [20]].
+ 			[MoveCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 16]].
+ 			[MoveCwR]				-> [^maxSize := 16].
+ 			[MoveRAw]				-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 1))
+ 														ifTrue: [4]
+ 														ifFalse: [20]].
+ 			[MoveRMwr]			-> [self is12BitValue: (operands at: 1)
+ 											ifTrue: [ :u :i | ^maxSize := 4]
+ 											ifFalse: [ ^maxSize := 20 ]].
+ 			[MoveRMbr]				-> [self is12BitValue: (operands at: 1)
+ 											ifTrue: [ :u :i | ^maxSize := 4]
+ 											ifFalse: [ ^maxSize := 20 ]].
+ 			[MoveMwrR]			-> [self is12BitValue: (operands at: 0)
+ 											ifTrue: [ :u :i | ^maxSize := 4]
+ 											ifFalse: [ ^maxSize := 20 ]].
+ 			[MoveMbrR]				-> [self is12BitValue: (operands at: 0)
+ 											ifTrue: [ :u :i | ^maxSize := 4]
+ 											ifFalse: [ ^maxSize := 20 ]].
+ 			[PrefetchAw] 			-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 1))
+ 														ifTrue: [4]
+ 														ifFalse: [20]].
  			[PushCw]				-> [^maxSize := 20].
  			[PushCq]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 8]
  											ifFalse: [maxSize := 20]].
  		}
  		otherwise: [^maxSize := 4].
  	^4 "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: CogARMCompiler>>concretizeCall (in category 'generate machine code - concretize') -----
  concretizeCall
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"build either a
  	BL offset
  	or
  	{move offset to offsetReg}
  	BLX offsetReg
  	instruction sequence. In production VMs we expect never to have long calls within generated code"
  	| 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).
+ 	self machineCodeAt: 0 put: (self bl: offset). "BL offset"
+ 	^machineCodeSize := 4!
- 	(self isInImmediateJumpRange: offset)
- 		ifTrue: [
- 			self machineCodeAt: 0 put: (self bl: offset). "BL offset"
- 			^machineCodeSize := 4]
- 		ifFalse: [
- 			"self error: 'While we know how to generate a long distance call, we can''t update such a send site yet. Please restart with smaller cache size'."
- 			^self concretizeLongCall]!

Item was added:
+ ----- 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 at: 0 moveCw: jumpTarget intoR: ConcreteIPReg.
+ 	"blx ConcreteIPReg"
+ 	self machineCodeAt: instrOffset put: (self blx: ConcreteIPReg).
+ 	self assert: instrOffset = 16.
+ 	^machineCodeSize := instrOffset + 4!

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"
+ 	^machineCodeSize := 4!
-  	(self isInImmediateJumpRange: offset)
- 		ifTrue: [
- 			self machineCodeAt: 0 put: (self cond: conditionCode br: 0 offset: offset). "B offset"
- 			^machineCodeSize := 4]
- 		ifFalse: [
- 			^self concretizeConditionalJumpLong: conditionCode]!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeConditionalJumpFull: (in category 'generate machine code - concretize') -----
+ concretizeConditionalJumpFull: 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>
+ 	| jumpTarget instrOffset|
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	instrOffset := self at: 0 moveCw: jumpTarget intoR: ConcreteIPReg.
+ 	self assert: instrOffset = 16.
+ 	"bx RISCTempReg"
+ 	self machineCodeAt: instrOffset put: (self cond: conditionCode bx: 0 target: ConcreteIPReg).
+ 	^machineCodeSize := instrOffset + 4!

Item was removed:
- ----- Method: CogARMCompiler>>concretizeConditionalJumpLong: (in category 'generate machine code - concretize') -----
- 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>
- 	| jumpTarget instrOffset|
- 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 	jumpTarget := self longJumpTargetAddress.
- 	instrOffset := self at: 0 moveCw: jumpTarget intoR: ConcreteIPReg.
- 	"bx RISCTempReg"
- 	self machineCodeAt: instrOffset put: (self cond: conditionCode bx: 0 target: ConcreteIPReg).
- 	^machineCodeSize := instrOffset + 4!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeJumpFull (in category 'generate machine code - concretize') -----
+ concretizeJumpFull
+ 	"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 instrOffset|
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	instrOffset := self at: 0 moveCw: jumpTarget intoR: ConcreteIPReg.
+ 	"bx RISCTempReg"
+ 	self machineCodeAt: instrOffset put: (self cond: 0 bx: 0 target: ConcreteIPReg).
+ 	self assert: instrOffset = 16.
+ 	^machineCodeSize := instrOffset + 4!

Item was removed:
- ----- Method: CogARMCompiler>>concretizeLongCall (in category 'generate machine code - concretize') -----
- concretizeLongCall
- 	"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 at: 0 moveCw: jumpTarget intoR: ConcreteIPReg.
- 	"blx ConcreteIPReg"
- 	self machineCodeAt: instrOffset put: (self blx: ConcreteIPReg).
- 	^machineCodeSize := instrOffset + 4!

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>
  	cond ifNotNil:
  		[self concretizeConditionalInstruction.
  		 ^self].
  		 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill16]					-> [^self concretizeFill16].
  		[Fill32]					-> [^self concretizeFill32].
  		[FillFromWord]			-> [^self concretizeFillFromWord].
  		[Nop]					-> [^self concretizeNop].
  		"Control"
+ 		[CallFull]					-> [^self concretizeCallFull].
  		[Call]						-> [^self concretizeCall].
  		[JumpR]						-> [^self concretizeJumpR].
+ 		[JumpFull]					-> [^self concretizeJumpFull].
+ 		[JumpLong]					-> [^self concretizeConditionalJump: AL].
+ 		[JumpLongZero]			-> [^self concretizeConditionalJump: EQ].
+ 		[JumpLongNonZero]		-> [^self concretizeConditionalJump: NE].
- 		[JumpLong]					-> [^self concretizeConditionalJumpLong: AL].
- 		[JumpLongZero]			-> [^self concretizeConditionalJumpLong: EQ].
- 		[JumpLongNonZero]		-> [^self concretizeConditionalJumpLong: 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].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeDataOperationCwR: AddOpcode].
  		[AddRR]						-> [^self concretizeDataOperationRR: AddOpcode].
  		"[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58]."
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCqRR]					-> [^self concretizeAndCqRR].
  		[AndCwR]					-> [^self concretizeDataOperationCwR: AndOpcode].
  		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
  		[BICCqR]					-> [^self concretizeDataOperationCqR: BicOpcode].
  		[CmpCqR]					-> [^self concretizeDataOperationCqR: CmpOpcode].
  		[CmpCwR]					-> [^self concretizeDataOperationCwR: CmpOpcode].
  		[CmpRR]					-> [^self concretizeDataOperationRR: CmpOpcode].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		"[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59]."
  		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
  		[OrCwR]					-> [^self concretizeDataOperationCwR: OrOpcode].
  		[OrRR]						-> [^self concretizeDataOperationRR: OrOpcode].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeDataOperationCwR: SubOpcode].
  		[SubRR]						-> [^self concretizeDataOperationRR: SubOpcode].
  		"[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C]."
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[XorCqR]						-> [^self concretizeDataOperationCqR: XorOpcode].
  		[XorCwR]						-> [^self concretizeDataOperationCwR: XorOpcode].
  		[XorRR]							-> [^self concretizeDataOperationRR: XorOpcode].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		"While the two MoveMbR and MoveMwR are quite similar (off by 1 bit), they differ way more to
  		MoveM16R and MoveM64R. Because of that, they are not merged."
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[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].
  		[Stop]				-> [^self concretizeStop].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		"ARM specific opcodes" 
  		[LDMFD]			-> [^self concretizeLDMFD].
  		[STMFD]			-> [^self concretizeSTMFD].
  		[SMULL]			-> [^self concretizeSMULL]	}!

Item was changed:
  ----- Method: CogARMCompiler>>isInImmediateJumpRange: (in category 'testing') -----
  isInImmediateJumpRange: operand
+ 	"ARM calls and jumps span +/- 32 mb, more than enough for intra-zone calls and jumps."
  	<var: #operand type: #'unsigned long'>
+ 	^operand signedIntFromLong between: -16r2000000 and: 16r1FFFFFC!
- 	^operand signedIntFromLong between: -33554432 and: 33554428!

Item was changed:
  ----- Method: CogARMCompiler>>jumpLongByteSize (in category 'accessing') -----
  jumpLongByteSize
+ 	"ARM calls and jumps span +/- 32 mb, more than enough for intra-zone calls and jumps."
+ 	^4!
- 	self flag: 'for the moment the Cogit understands only a Jump vs JumpLong distinction where JumpLong spans the 32-bit address space.  But this leads to 20-byte branches.  What we need to distingush between is variable sized jumps ("short" jumps, which is what Jump means now), fixed size jumops within the code zone and fixed size jumps within the 32-bit address space.'.
- 	^20!

Item was added:
+ ----- Method: CogARMCompiler>>rewriteCallFullAt:target: (in category 'inline cacheing') -----
+ rewriteCallFullAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a full call instruction to call to a different target.  This variant
+ 	 is used to rewrite cached primitive calls.   Answer the extent of the
+ 	 code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	"cogit disassembleFrom: callSiteReturnAddress - 40 to: callSiteReturnAddress + 9"
+ 
+ 	"check that the instruction involved is actually a call BL ip (reg 12)
+ 	(CogARMCompiler new bl: 16) hex"
+ 	self assert: ((objectMemory longAt:  callSiteReturnAddress - 4) bitAnd: 16rFE000000) = 16rEB000000.
+ 	
+ 	"The callTargetAddress is loaded byte by byte."
+ 	objectMemory byteAt: callSiteReturnAddress - 20 put: (callTargetAddress >> 24 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 16 put: (callTargetAddress >> 16 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 12 put: (callTargetAddress >> 8 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 8 put: (callTargetAddress  bitAnd: 16rFF).
+ 
+ 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 20 to: callSiteReturnAddress - 1]."
+ 	^20!

Item was added:
+ ----- Method: CogARMCompiler>>rewriteJumpFullAt:target: (in category 'inline cacheing') -----
+ rewriteJumpFullAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a long jump instruction to jump to a different target.  This variant
+ 	 is used to rewrite cached primitive calls.   Answer the extent of the
+ 	 code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	"cogit disassembleFrom: callSiteReturnAddress - 40 to: callSiteReturnAddress + 9"
+ 
+ 	"check that the instruction involved is actually a long jump BX ip (reg 12)
+ 	(CogARMCompiler new bx: 12) hex"
+ 	self assert: (objectMemory longAt:  callSiteReturnAddress - 4) = 16rE12FFF1C .
+ 	
+ 	"The callTargetAddress is loaded byte by byte."
+ 	objectMemory byteAt: callSiteReturnAddress - 20 put: (callTargetAddress >> 24 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 16 put: (callTargetAddress >> 16 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 12 put: (callTargetAddress >> 8 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 8 put: (callTargetAddress  bitAnd: 16rFF).
+ 
+ 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 20 to: callSiteReturnAddress - 1]."
+ 	^20!

Item was removed:
- ----- Method: CogARMCompiler>>rewriteJumpLongAt:target: (in category 'inline cacheing') -----
- rewriteJumpLongAt: callSiteReturnAddress target: callTargetAddress
- 	"Rewrite a long jump instruction to jump to a different target.  This variant
- 	 is used to rewrite cached primitive calls.   Answer the extent of the
- 	 code change which is used to compute the range of the icache to flush."
- 	<var: #callSiteReturnAddress type: #usqInt>
- 	<var: #callTargetAddress type: #usqInt>
- 	"cogit disassembleFrom: callSiteReturnAddress - 40 to: callSiteReturnAddress + 9"
- 
- 	"check that the instruction involved is actually a long jump BX ip (reg 12)
- 	(CogARMCompiler new bx: 12) hex"
- 	self assert: (objectMemory longAt:  callSiteReturnAddress - 4) = 16rE12FFF1C .
- 	
- 	"The callTargetAddress is loaded byte by byte."
- 	objectMemory byteAt: callSiteReturnAddress - 20 put: (callTargetAddress >> 24 bitAnd: 16rFF).
- 	objectMemory byteAt: callSiteReturnAddress - 16 put: (callTargetAddress >> 16 bitAnd: 16rFF).
- 	objectMemory byteAt: callSiteReturnAddress - 12 put: (callTargetAddress >> 8 bitAnd: 16rFF).
- 	objectMemory byteAt: callSiteReturnAddress - 8 put: (callTargetAddress  bitAnd: 16rFF).
- 
- 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
- 	"self cCode: ''
- 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 20 to: callSiteReturnAddress - 1]."
- 	^20!

Item was changed:
  ----- Method: CogARMCompiler>>sizePCDependentInstructionAt: (in category 'generate machine code') -----
  sizePCDependentInstructionAt: eventualAbsoluteAddress
  	"Size a jump and set its address.  The target may be another instruction
  	 or an absolute address.  On entry the address inst var holds our virtual
  	 address. On exit address is set to eventualAbsoluteAddress, which is
  	 where this instruction will be output.  The span of a jump to a following
  	 instruction is therefore between that instruction's address and this
  	 instruction's address ((which are both still their virtual addresses), but the
  	 span of a jump to a preceeding instruction or to an absolute address is
  	 between that instruction's address (which by now is its eventual absolute
+ 	 address) or absolute address and eventualAbsoluteAddress.
- 	 address) or absolute address and eventualAbsoluteAddress."
  
+ 	 ARM is simple; the 26-bit call/jump range means no short jumps.  This routine
+ 	 only has to determine the targets of jumps, not determine sizes."
+ 
- 	| target maximumSpan abstractInstruction |
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	opcode = AlignmentNops ifTrue:
  		[| alignment |
  		 address := eventualAbsoluteAddress.
  		 alignment := operands at: 0.
  		 ^machineCodeSize := (eventualAbsoluteAddress + (alignment - 1) bitAnd: alignment negated)
  							   - eventualAbsoluteAddress].
+ 	self assert: (self isJump or: [opcode = Call or: [opcode = CallFull]]).
- 	self assert: (self isJump or: [opcode = Call]).
  	self isJump ifTrue: [self resolveJumpTarget].
- 	target := operands at: 0.
- 	abstractInstruction := cogit cCoerceSimple: target to: #'AbstractInstruction *'.
- 	"maximumSpan calculation copied from CogIA32Compiler TODO: extract method?"
- 	(self isAnInstruction: abstractInstruction)
- 		ifTrue:
- 			[maximumSpan := abstractInstruction address
- 							- (((cogit abstractInstruction: self follows: abstractInstruction)
- 								ifTrue: [eventualAbsoluteAddress]
- 								ifFalse: [address]) + 2)]
- 		ifFalse:
- 			[maximumSpan := target - (eventualAbsoluteAddress + 2)].
  	address := eventualAbsoluteAddress.
+ 	^machineCodeSize := maxSize!
- 	^machineCodeSize := opcode = Call 
- 				ifTrue: [(self isInImmediateJumpRange: maximumSpan) ifTrue: [4] ifFalse: [20]]
- 				ifFalse: [(self isLongJump not and: [self isInImmediateJumpRange: maximumSpan])
- 								ifTrue: [4]
- 								ifFalse: [20]] "load address to register, add"!

Item was changed:
  ----- Method: CogAbstractInstruction>>rewriteCallFullAt:target: (in category 'full run-time support') -----
  rewriteCallFullAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a CallFull instruction to call a different target.  This variant is used to rewrite cached primitive calls.
  	 Answer the extent of the code change which is used to compute the range of the icache to flush.
+ 	 This defaults to rewriteCallAt:target:; processors that differentiate between Call and CallFull will override."
- 	 This defaults to rewriteCallAt:target:; proessors that differentiate between Call and CallFull will override."
  	^self rewriteCallAt: callSiteReturnAddress target: callTargetAddress!

Item was changed:
  ----- Method: CogAbstractInstruction>>rewriteJumpFullAt:target: (in category 'full run-time support') -----
  rewriteJumpFullAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a JumpFull instruction to jump to a different target.  This variant is used to rewrite cached primitive calls.
  	 Answer the extent of the code change which is used to compute the range of the icache to flush.
+ 	 This defaults to rewriteJumpLongAt:target:; processors that differentiate between Jump and JumpFull will override."
- 	 This defaults to rewriteJumpLongAt:target:; proessors that differentiate between Jump and JumpFull will override."
  	^self rewriteJumpLongAt: callSiteReturnAddress target: callTargetAddress!

Item was changed:
  ----- Method: CogIA32Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^maxSize := N forms are to get around the compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^maxSize := 0].
  		[AlignmentNops]		-> [^maxSize := (operands at: 0) - 1].
  		[Fill16]					-> [^maxSize := 2].
  		[Fill32]					-> [^maxSize := 4].
  		[FillFromWord]			-> [^maxSize := 4].
  		[Nop]					-> [^maxSize := 1].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^maxSize := 1].
  		[IDIVR]					-> [^maxSize := 2].
  		[IMULRR]				-> [^maxSize := 3].
  		[CPUID]					-> [^maxSize := 2].
  		[CMPXCHGAwR]			-> [^maxSize := 7].
  		[CMPXCHGMwrR]		-> [^maxSize := 8].
  		[LFENCE]				-> [^maxSize := 3].
  		[MFENCE]				-> [^maxSize := 3].
  		[SFENCE]				-> [^maxSize := 3].
  		[LOCK]					-> [^maxSize := 1].
  		[XCHGAwR]				-> [^maxSize := 6].
  		[XCHGMwrR]			-> [^maxSize := 7].
  		[XCHGRR]				-> [^maxSize := 2].
  		"Control"
- 		[Call]					-> [^maxSize := 5].
  		[CallFull]				-> [^maxSize := 5].
+ 		[Call]					-> [^maxSize := 5].
  		[JumpR]					-> [^maxSize := 2].
- 		[Jump]					-> [self resolveJumpTarget. ^maxSize := 5].
  		[JumpFull]				-> [self resolveJumpTarget. ^maxSize := 5].
  		[JumpLong]				-> [self resolveJumpTarget. ^maxSize := 5].
+ 		[Jump]					-> [self resolveJumpTarget. ^maxSize := 5].
  		[JumpZero]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNonZero]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNegative]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNonNegative]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpOverflow]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNoOverflow]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNoCarry]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLess]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpGreaterOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpGreater]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLessOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpAbove]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPEqual]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPNotEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPLess]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPLessOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPOrdered]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPUnordered]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[RetN]					-> [^maxSize := (operands at: 0) = 0
  													ifTrue: [1]
  													ifFalse: [3]].
  		[Stop]					-> [^maxSize := 1].
  
  		"Arithmetic"
  		[AddCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AndCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[CmpCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[OrCqR]			-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[SubCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AddCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[AndCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[CmpCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[OrCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[SubCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[XorCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[AddRR]			-> [^maxSize := 2].
  		[AndRR]			-> [^maxSize := 2].
  		[CmpRR]		-> [^maxSize := 2].
  		[OrRR]			-> [^maxSize := 2].
  		[XorRR]			-> [^maxSize := 2].
  		[SubRR]			-> [^maxSize := 2].
  		[NegateR]		-> [^maxSize := 2].
  		[LoadEffectiveAddressMwrR]
  						-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[LogicalShiftLeftCqR]		-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[LogicalShiftRightCqR]	-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[ArithmeticShiftRightCqR]	-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[LogicalShiftLeftRR]		-> [self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [self computeShiftRRSize].
  		[ArithmeticShiftRightRR]	-> [self computeShiftRRSize].
  		[AddRdRd]				-> [^maxSize := 4].
  		[CmpRdRd]				-> [^maxSize := 4].
  		[SubRdRd]				-> [^maxSize := 4].
  		[MulRdRd]				-> [^maxSize := 4].
  		[DivRdRd]				-> [^maxSize := 4].
  		[SqrtRd]					-> [^maxSize := 4].
  		"Data Movement"
  		[MoveCqR]		-> [^maxSize := (operands at: 0) = 0 ifTrue: [2] ifFalse: [5]].
  		[MoveCwR]		-> [^maxSize := 5].
  		[MoveRR]		-> [^maxSize := 2].
  		[MoveRdRd]		-> [^maxSize := 4].
  		[MoveAwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  											ifTrue: [5]
  											ifFalse: [6]].
  		[MoveRAw]		-> [^maxSize := (self concreteRegister: (operands at: 0)) = EAX
  											ifTrue: [5]
  											ifFalse: [6]].
  		[MoveRMwr]		-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRdM64r]	-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMbrR]		-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRMbr]		-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM16rR]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM64rRd]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMwrR]		-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^maxSize := ((self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3])
  										+ ((self concreteRegister: (operands at: 0)) >= 4
  											ifTrue: [2]
  											ifFalse: [0])].
  		[MoveXwrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[PopR]			-> [^maxSize := 1].
  		[PushR]			-> [^maxSize := 1].
  		[PushCq]		-> [^maxSize := (self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^maxSize := 5].
  		[PrefetchAw]	-> [^maxSize := self hasSSEInstructions ifTrue: [7] ifFalse: [0]].
  		"Conversion"
  		[ConvertRRd]	-> [^maxSize := 4] }.
  	^0 "to keep C compiler quiet"!

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 caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill16]				-> [^self concretizeFill16].
  		[Fill32]				-> [^self concretizeFill32].
  		[FillFromWord]		-> [^self concretizeFillFromWord].
  		[Nop]				-> [^self concretizeNop].
  		"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].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallFull]				-> [^self concretizeCall].
  		[JumpR]					-> [^self concretizeJumpR].
+ 		[JumpFull]				-> [^self concretizeJumpFull].
+ 		[JumpLong]				-> [^self concretizeJump].
+ 		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
+ 		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
- 		[JumpFull]				-> [^self concretizeJumpLong].
- 		[JumpLong]				-> [^self concretizeJumpLong].
- 		[JumpLongZero]		-> [^self concretizeConditionalJumpLong: 16r4].
- 		[JumpLongNonZero]	-> [^self concretizeConditionalJumpLong: 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 concretizeAddRR].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[AndRR]						-> [^self concretizeAndRR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[CmpRR]					-> [^self concretizeCmpRR].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[OrCqR]						-> [^self concretizeOrCqR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[OrRR]						-> [^self concretizeOrRR].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[SubRR]						-> [^self concretizeSubRR].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[XorCwR]						-> [^self concretizeXorCwR].
  		[XorRR]							-> [^self concretizeXorRR].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[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] }!

Item was removed:
- ----- Method: Cogit>>JumpRT: (in category 'method map') -----
- JumpRT: callTarget
- 	"Big assumption here that calls and jumps look the same as regards their displacement.
- 	 This works on x86 and I think on ARM."
- 	<returnTypeC: #'AbstractInstruction *'>
- 	^self annotateCall: (self JumpLong: callTarget)!



More information about the Vm-dev mailing list