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

commits at source.squeak.org commits at source.squeak.org
Wed Jun 10 22:19:28 UTC 2015


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

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

Name: VMMaker.oscog-eem.1344
Author: eem
Time: 10 June 2015, 3:17:31.452 pm
UUID: 020ff2e2-0424-44b9-9fde-7bfbe945d1ad
Ancestors: VMMaker.oscog-cb.1343

Cogit:
Get code generation working for CogOutOfLineLiteralsARMCompiler.

Fix initialization of methodLabel in 
Introduce DumpJumpLong[Zero]: for convenient
PIC wirting where the literals need to be dumped
in consistent places to keep PIC cases the same size.

Fix isAnInstruction for labels (methodLabel) and
use it to guard addressIsInCurrentCompilation:
calls where a label is involved.

For better initialization of literal management
use zeroOpcodeIndex everywhere opcodeIndex
is initialized, and have it reset literals.  And have
computeMaximumSizes dump literals.

Move the assignment of maxSize out of
computeMaximumSize and into
computeMaximumSizes for concision.

ARM Cogit:
Introduce some more abstractions for rotateable
constants so that it is easier to relate
computeMaximumSize and dispatchConcetize in
CogARMCompiler.  Provide more opcode names and
use them, and use inverseOpcodeFor: to calculate
the inverse opcode when the inverse constant is
used.

Revise ARM getDefaultCogCodeSize given better
estimates of relative code sizes.
Simplify isPICDependent to eliminate Calls, which
are not pc-dependent (ince they always call out of
the current compilaiton).

Simulator:
Safety in instruction printing, and spotting literals
in disassembly.

Slang:
Fix ancilliaryClasses: given the deeper
CogAbstractInstruction hierarchy on ARM.

=============== Diff against VMMaker.oscog-cb.1343 ===============

Item was changed:
  ----- Method: AbstractInstructionTests>>generateInstructions (in category 'generating machine code') -----
  generateInstructions
  	"See Cogit>>computeMaximumSizes, generateInstructionsAt: & outputInstructionsAt:.
  	 This is a pure Smalltalk (non-Slang) version of that trio of methods."
  	| address pcDependentInstructions instructions |
  	address := 0.
  	pcDependentInstructions := OrderedCollection new.
  	opcodes do:
  		[:abstractInstruction|
+ 		abstractInstruction
+ 			address: address;
+ 			maxSize: abstractInstruction computeMaximumSize.
- 		abstractInstruction address: address.
- 		abstractInstruction computeMaximumSize.
  		address := address + abstractInstruction maxSize].
  	address := 0.
  	opcodes do:
  		[:abstractInstruction|
  		abstractInstruction isPCDependent
  			ifTrue:
  				[abstractInstruction sizePCDependentInstructionAt: address.
  				 pcDependentInstructions addLast: abstractInstruction.
  				 address := address + abstractInstruction machineCodeSize]
  			ifFalse:
  				[address := abstractInstruction concretizeAt: address]].
  	pcDependentInstructions do:
  		[:abstractInstruction|
  		abstractInstruction concretizeAt: abstractInstruction address].
  	instructions := ByteArray new: address.
  	address := 0.
  	opcodes do:
  		[:abstractInstruction|
  		self assert: abstractInstruction address = address.
  		0 to: abstractInstruction machineCodeSize - 1 do:
  			[:j|
  			instructions at: address + 1 put: (abstractInstruction machineCode at: j).
  			address := address + 1]].
  	^instructions!

Item was changed:
  CogAbstractInstruction subclass: #CogARMCompiler
  	instanceVariableNames: 'conditionOrNil'
+ 	classVariableNames: 'AL AddOpcode AndOpcode BicOpcode CArg0Reg CArg1Reg CArg2Reg CArg3Reg CC CMPSMULL CPSRReg CS CmpNotOpcode CmpOpcode ConcreteIPReg ConcreteVarBaseReg EQ GE GT HI LDMFD LE LR LS LT MI MRS MSR MoveNotOpcode MoveOpcode NE OrOpcode OverflowFlag PC PL R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 RsbOpcode SMLALOpcode SMULL SP STMFD SubOpcode TstOpcode VC VS XorOpcode'
- 	classVariableNames: 'AL AddOpcode AndOpcode BICCqR BicOpcode CArg0Reg CArg1Reg CArg2Reg CArg3Reg CC CMPSMULL CPSRReg CS CmpOpcode ConcreteIPReg ConcreteVarBaseReg EQ GE GT HI LDMFD LE LR LS LT MI MRS MSR MoveNotOpcode MoveOpcode NE OrOpcode OverflowFlag PC PL R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 RsbOpcode SMLALOpcode SMULL SP STMFD SubOpcode TstOpcode VC VS XorOpcode'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogARMCompiler commentStamp: 'lw 8/23/2012 19:38' prior: 0!
  I generate ARM instructions from CogAbstractInstructions.  For reference see
  http://infocenter.arm.com/help/index.jsp?topic=/com.arm.doc.set.architecture/index.html
  
  The Architecture Reference Manual used is that of version 5, which includes some version 6 instructions. Of those, only pld is used(for PrefetchAw).
  
  This class does not take any special action to flush the instruction cache on instruction-modification.!

Item was changed:
  ----- Method: CogARMCompiler class>>initialize (in category 'class initialization') -----
  initialize
  	
  	"Initialize various ARM instruction-related constants."
  	"CogARMCompiler initialize"
  	
  	| specificOpcodes refs |
  	super initialize.
  	self ~~ CogARMCompiler ifTrue: [^self].
  	
  	R0 := 0.
  	R1 := 1.
  	R2 := 2.
  	R3 := 3.
  	R4 := 4.
  	R5 := 5.
  	R6 := 6.
  	R7 := 7.
  	R8 := 8.
  	R9 := 9.
  	R10 := 10.
  	R11 := 11.
  	R12 := 12.
  	SP := 13.
  	LR := 14.
  	PC := 15.
  	
  	CArg0Reg := 0.
  	CArg1Reg := 1.
  	CArg2Reg := 2.
  	CArg3Reg := 3.
  
  	ConcreteVarBaseReg := 10.
  	ConcreteIPReg := 12. "IP, The Intra-Procedure-call scratch register."
  	
  	"Condition Codes. Note that cc=16rF is NOT ALLOWED as a condition; it specifies an extension instruction. See e.g.ARM_ARM v5 DDI01001.pdf A3.2.1"
  	EQ := 0.
  	NE := 1.
  	CS := 2.
  	CC := 3.
  	MI := 4.
  	PL := 5.
  	VS := 6.
  	VC := 7.
  	HI := 8.
  	LS := 9.
  	GE := 10.
  	LT := 11.
  	GT := 12.
  	LE := 13.
  	AL := 14.
  
+ 	"Table A3-2 in sec A3.4 Data-processing instructions of the AARM."
  	AddOpcode := 	4.
  	AndOpcode := 0.
  	BicOpcode := 14.
  	CmpOpcode := 10.
+ 	CmpNotOpcode := 11.
  	MoveOpcode := 13.
  	MoveNotOpcode := 15.
  	OrOpcode := 12.
  	RsbOpcode := 3.
  	SMLALOpcode := 7.
  	SubOpcode := 2.
  	TstOpcode := 8.
  	XorOpcode := 1.
  
  	CPSRReg := 16.
  	OverflowFlag := 1 << 28.
  
  	"Specific instructions"
  	LastRTLCode isNil ifTrue:
  		[CogRTLOpcodes initialize].
  	specificOpcodes := #(SMULL MSR MRS LDMFD STMFD CMPSMULL).
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	(classPool keys reject: [:k| (specificOpcodes includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	specificOpcodes withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value + LastRTLCode - 1]!

Item was changed:
  ----- Method: CogARMCompiler>>bics:rn:imm:ror: (in category 'ARM convenience instructions') -----
  bics: destReg rn: srcReg imm: immediate ror: rot
  "Remember the ROR is doubled by the cpu so use 30>>1 etc
  	BICS destReg, srcReg, #immediate ROR #rot"
  
+ 	^self type: 1 op: BicOpcode set: 1 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!
- 	^self type: 1 op: 14 set: 1 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

Item was changed:
  ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
+ 	"Because we don't use Thumb, each ARM instruction has 4 bytes. Many
+ 	 abstract opcodes need more than one instruction. Instructions that refer
+ 	 to constants and/or literals depend on literals being stored in-line or out-of-line.
- 	"Because we don't use Thumb, each ARM instruction has 4 bytes. Many abstract opcodes need more than one instruction.
- 	 Instructions that refer to constants and/or literals depend on literals being stored in-line or out-of-line."
  
+ 	 N.B.  The ^N forms are to get around the bytecode compiler's long branch
+ 	 limits which are exceeded when each case jumps around the otherwise."
+ 
  	opcode
  		caseOf: {
  		"Noops & Pseudo Ops"
+ 		[Label]					-> [^0].
+ 		[Literal]					-> [^4].
+ 		[AlignmentNops]		-> [^(operands at: 0) - 4].
+ 		[Fill16]					-> [^4].
+ 		[Fill32]					-> [^4].
+ 		[FillFromWord]			-> [^4].
+ 		[Nop]					-> [^4].
- 		[Label]					-> [^maxSize := 0].
- 		[Literal]					-> [^maxSize := 4].
- 		[AlignmentNops]		-> [^maxSize := (operands at: 0) - 4].
- 		[Fill16]					-> [^maxSize := 4].
- 		[Fill32]					-> [^maxSize := 4].
- 		[FillFromWord]			-> [^maxSize := 4].
- 		[Nop]					-> [^maxSize := 4].
  		"Control"
+ 		[Call]					-> [^4].
+ 		[CallFull]				-> [^self literalLoadInstructionBytes + 4].
+ 		[JumpR]					-> [^4].
+ 		[Jump]					-> [^4].
+ 		[JumpFull]				-> [^self literalLoadInstructionBytes + 4].
+ 		[JumpLong]				-> [^4].
+ 		[JumpZero]				-> [^4].
+ 		[JumpNonZero]			-> [^4].
+ 		[JumpNegative]			-> [^4].
+ 		[JumpNonNegative]		-> [^4].
+ 		[JumpOverflow]			-> [^4].
+ 		[JumpNoOverflow]		-> [^4].
+ 		[JumpCarry]			-> [^4].
+ 		[JumpNoCarry]			-> [^4].
+ 		[JumpLess]				-> [^4].
+ 		[JumpGreaterOrEqual]	-> [^4].
+ 		[JumpGreater]			-> [^4].
+ 		[JumpLessOrEqual]		-> [^4].
+ 		[JumpBelow]			-> [^4].
+ 		[JumpAboveOrEqual]	-> [^4].
+ 		[JumpAbove]			-> [^4].
+ 		[JumpBelowOrEqual]	-> [^4].
+ 		[JumpLongZero]		-> [^4].
+ 		[JumpLongNonZero]	-> [^4].
+ 		[JumpFPEqual]			-> [^8].
+ 		[JumpFPNotEqual]		-> [^8].
+ 		[JumpFPLess]			-> [^8].
+ 		[JumpFPGreaterOrEqual]-> [^8].
+ 		[JumpFPGreater]		-> [^8].
+ 		[JumpFPLessOrEqual]	-> [^8].
+ 		[JumpFPOrdered]		-> [^8].
+ 		[JumpFPUnordered]		-> [^8].
+ 		[RetN]					-> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
+ 		[Stop]					-> [^4].
- 		[Call]					-> [^maxSize := 4].
- 		[CallFull]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[JumpR]					-> [^maxSize := 4].
- 		[Jump]					-> [^maxSize := 4].
- 		[JumpFull]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[JumpLong]				-> [^maxSize := 4].
- 		[JumpZero]				-> [^maxSize := 4].
- 		[JumpNonZero]			-> [^maxSize := 4].
- 		[JumpNegative]			-> [^maxSize := 4].
- 		[JumpNonNegative]		-> [^maxSize := 4].
- 		[JumpOverflow]			-> [^maxSize := 4].
- 		[JumpNoOverflow]		-> [^maxSize := 4].
- 		[JumpCarry]			-> [^maxSize := 4].
- 		[JumpNoCarry]			-> [^maxSize := 4].
- 		[JumpLess]				-> [^maxSize := 4].
- 		[JumpGreaterOrEqual]	-> [^maxSize := 4].
- 		[JumpGreater]			-> [^maxSize := 4].
- 		[JumpLessOrEqual]		-> [^maxSize := 4].
- 		[JumpBelow]			-> [^maxSize := 4].
- 		[JumpAboveOrEqual]	-> [^maxSize := 4].
- 		[JumpAbove]			-> [^maxSize := 4].
- 		[JumpBelowOrEqual]	-> [^maxSize := 4].
- 		[JumpLongZero]		-> [^maxSize := 4].
- 		[JumpLongNonZero]	-> [^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].
- 		[RetN]					-> [^maxSize := (operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
- 		[Stop]					-> [^maxSize := 4].
  
  		"Arithmetic"
+ 		[AddCqR]				-> [^self rotateable8bitSignedImmediate: (operands at: 0)
+ 										ifTrue: [:r :i :n| 4]
+ 										ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		[AndCqR]				-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
+ 										ifTrue: [:r :i :n| 4]
+ 										ifFalse:
+ 											[self literalLoadInstructionBytes = 4
+ 												ifTrue: [8]
+ 												ifFalse:
+ 													[1 << (operands at: 0) highBit = ((operands at: 0) + 1)
+ 														ifTrue: [8]
+ 														ifFalse: [self literalLoadInstructionBytes + 4]]]].
+ 		[AndCqRR]				-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
+ 										ifTrue: [:r :i :n| 4]
+ 										ifFalse:
+ 											[self literalLoadInstructionBytes = 4
+ 												ifTrue: [8]
+ 												ifFalse:
+ 													[1 << (operands at: 0) highBit = ((operands at: 0) + 1)
+ 														ifTrue: [8]
+ 														ifFalse: [self literalLoadInstructionBytes + 4]]]].
+ 		[CmpCqR]				-> [^self rotateable8bitSignedImmediate: (operands at: 0)
+ 											ifTrue: [:r :i :n| 4]
+ 											ifFalse: [self literalLoadInstructionBytes + 4]].
- 		[AddCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse:
- 												[self rotateable8bitImmediate: (operands at: 0) negated
- 													ifTrue: [:r :i| maxSize := 4]
- 													ifFalse: [maxSize := self literalLoadInstructionBytes + 4]]].
- 		[AndCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
- 		[AndCqRR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse:
- 												[| val invVal |
- 												invVal := (val := operands at: 0) < 0 ifTrue: [-1 - val] ifFalse: [val bitInvert32].
- 												self rotateable8bitImmediate: invVal
- 													ifTrue: [:r :i| maxSize := 4]
- 													ifFalse: [maxSize := self literalLoadInstructionBytes + 4]]].
- 		[CmpCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
  		[OrCqR]					-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| 4]
+ 											ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		[SubCqR]				-> [^self rotateable8bitSignedImmediate: (operands at: 0)
+ 											ifTrue: [:r :i :n| 4]
+ 											ifFalse: [self literalLoadInstructionBytes + 4]].
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
- 		[SubCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse:
- 												[self rotateable8bitImmediate: (operands at: 0) negated
- 													ifTrue: [:r :i| maxSize := 4]
- 													ifFalse: [maxSize := self literalLoadInstructionBytes + 4]]].
  		[TstCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| 4]
+ 											ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		[XorCqR]				-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
+ 										ifTrue: [:r :i :n| 4]
+ 										ifFalse:
+ 											[self literalLoadInstructionBytes = 4
+ 												ifTrue: [8]
+ 												ifFalse:
+ 													[1 << (operands at: 0) highBit = ((operands at: 0) + 1)
+ 														ifTrue: [8]
+ 														ifFalse: [self literalLoadInstructionBytes + 4]]]].
+ 		[AddCwR]				-> [^self literalLoadInstructionBytes + 4].
+ 		[AndCwR]				-> [^self literalLoadInstructionBytes + 4].
+ 		[CmpCwR]				-> [^self literalLoadInstructionBytes + 4].
+ 		[OrCwR]				-> [^self literalLoadInstructionBytes + 4].
+ 		[SubCwR]				-> [^self literalLoadInstructionBytes + 4].
+ 		[XorCwR]				-> [^self literalLoadInstructionBytes + 4].
+ 		[AddRR]					-> [^4].
+ 		[AndRR]					-> [^4].
+ 		[CmpRR]				-> [^4].
+ 		[OrRR]					-> [^4].
+ 		[XorRR]					-> [^4].
+ 		[SubRR]					-> [^4].
+ 		[NegateR]				-> [^4].
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
- 		[XorCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
- 		[AddCwR]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[AndCwR]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[CmpCwR]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[OrCwR]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[SubCwR]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[XorCwR]				-> [^maxSize := self literalLoadInstructionBytes + 4].
- 		[AddRR]					-> [^maxSize := 4].
- 		[AndRR]					-> [^maxSize := 4].
- 		[CmpRR]				-> [^maxSize := 4].
- 		[OrRR]					-> [^maxSize := 4].
- 		[XorRR]					-> [^maxSize := 4].
- 		[SubRR]					-> [^maxSize := 4].
- 		[NegateR]				-> [^maxSize := 4].
  		[LoadEffectiveAddressMwrR]
  									-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| 4]
+ 											ifFalse: [self literalLoadInstructionBytes + 4]].
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
  
+ 		[LogicalShiftLeftCqR]		-> [^4].
+ 		[LogicalShiftRightCqR]		-> [^4].
+ 		[ArithmeticShiftRightCqR]	-> [^4].
+ 		[LogicalShiftLeftRR]			-> [^4].
+ 		[LogicalShiftRightRR]		-> [^4].
+ 		[ArithmeticShiftRightRR]		-> [^4].
+ 		[AddRdRd]					-> [^4].
+ 		[CmpRdRd]					-> [^4].
+ 		[SubRdRd]					-> [^4].
+ 		[MulRdRd]					-> [^4].
+ 		[DivRdRd]					-> [^4].
+ 		[SqrtRd]					-> [^4].
- 		[LogicalShiftLeftCqR]		-> [^maxSize := 4].
- 		[LogicalShiftRightCqR]		-> [^maxSize := 4].
- 		[ArithmeticShiftRightCqR]	-> [^maxSize := 4].
- 		[LogicalShiftLeftRR]			-> [^maxSize := 4].
- 		[LogicalShiftRightRR]		-> [^maxSize := 4].
- 		[ArithmeticShiftRightRR]		-> [^maxSize := 4].
- 		[AddRdRd]					-> [^maxSize := 4].
- 		[CmpRdRd]					-> [^maxSize := 4].
- 		[SubRdRd]					-> [^maxSize := 4].
- 		[MulRdRd]					-> [^maxSize := 4].
- 		[DivRdRd]					-> [^maxSize := 4].
- 		[SqrtRd]					-> [^maxSize := 4].
  		"ARM Specific Arithmetic"
+ 		[SMULL]				-> [^4].
+ 		[MSR]					-> [^4].
+ 		[CMPSMULL]			-> [^4]. "special compare for genMulR:R: usage"
- 		[SMULL]				-> [^maxSize := 4].
- 		[MSR]					-> [^maxSize := 4].
- 		[CMPSMULL]			-> [^maxSize := 4]. "special compare for genMulR:R: usage"
  		"Data Movement"						
  		[MoveCqR]				-> [^self literalLoadInstructionBytes = 4
+ 										ifTrue: [self literalLoadInstructionBytes]
- 										ifTrue: [maxSize := self literalLoadInstructionBytes]
  										ifFalse:
  											[self rotateable8bitImmediate: (operands at: 0)
+ 												ifTrue: [:r :i| 4]
- 												ifTrue: [:r :i| maxSize := 4]
  												ifFalse:
  													[| val invVal |
  													invVal := (val := operands at: 0) < 0 ifTrue: [-1 - val] ifFalse: [val bitInvert32].
  													self rotateable8bitImmediate: invVal
+ 														ifTrue: [:r :i| 4]
+ 														ifFalse: [self literalLoadInstructionBytes]]]].
+ 		[MoveCwR]				-> [^self literalLoadInstructionBytes = 4
+ 										ifTrue: [self literalLoadInstructionBytes]
+ 										ifFalse:
+ 											[((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definition will be in the current compilation."
+ 											   or: [cogit addressIsInCurrentCompilation: (operands at: 0)])
+ 												ifTrue: [4]
+ 												ifFalse: [self literalLoadInstructionBytes]]].
+ 		[MoveRR]				-> [^4].
+ 		[MoveRdRd]				-> [^4].
+ 		[MoveAwR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
- 														ifTrue: [:r :i| maxSize := 4]
- 														ifFalse: [maxSize := self literalLoadInstructionBytes]]]].
- 		[MoveCwR]				-> [^maxSize := self literalLoadInstructionBytes].
- 		[MoveRR]				-> [^maxSize := 4].
- 		[MoveRdRd]				-> [^maxSize := 4].
- 		[MoveAwR]				-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 0))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		[MoveRAw]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
- 		[MoveRAw]				-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 1))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRMwr]			-> [^self is12BitValue: (operands at: 1)
+ 										ifTrue: [:u :i| 4]
+ 										ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		[MoveRdM64r]			-> [^self literalLoadInstructionBytes + 4]. 
- 										ifTrue: [:u :i| maxSize := 4]
- 										ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
- 		[MoveRdM64r]			-> [^maxSize := self literalLoadInstructionBytes + 4]. 
  		[MoveMbrR]				-> [^self is12BitValue: (operands at: 0)
+ 										ifTrue: [:u :i| 4]
+ 										ifFalse: [self literalLoadInstructionBytes + 4]].
- 										ifTrue: [:u :i| maxSize := 4]
- 										ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
  		[MoveRMbr]				-> [^self is12BitValue: (operands at: 1)
+ 										ifTrue: [:u :i| 4]
+ 										ifFalse: [self literalLoadInstructionBytes + 4]].
- 										ifTrue: [:u :i| maxSize := 4]
- 										ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
  		[MoveM16rR]			-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| 4]
+ 											ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		[MoveM64rRd]			-> [^self literalLoadInstructionBytes + 4].
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
- 		[MoveM64rRd]			-> [^maxSize := self literalLoadInstructionBytes + 4].
  		[MoveMwrR]			-> [^self is12BitValue: (operands at: 0)
+ 										ifTrue: [:u :i| 4]
+ 										ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		[MoveXbrRR]			-> [^4].
+ 		[MoveRXbrR]			-> [^4].
+ 		[MoveXwrRR]			-> [^4].
+ 		[MoveRXwrR]			-> [^4].
+ 		[PopR]					-> [^4].
+ 		[PushR]					-> [^4].
+ 		[PushCw]				-> [^self literalLoadInstructionBytes = 4
+ 										ifTrue: [self literalLoadInstructionBytes + 4]
+ 										ifFalse:
+ 											[((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definition will be in the current compilation."
+ 											   or: [cogit addressIsInCurrentCompilation: (operands at: 0)])
+ 												ifTrue: [8]
+ 												ifFalse: [self literalLoadInstructionBytes + 4]]].
- 										ifTrue: [:u :i| maxSize := 4]
- 										ifFalse: [maxSize := self literalLoadInstructionBytes + 4]].
- 		[MoveXbrRR]			-> [^maxSize := 4].
- 		[MoveRXbrR]			-> [^maxSize := 4].
- 		[MoveXwrRR]			-> [^maxSize := 4].
- 		[MoveRXwrR]			-> [^maxSize := 4].
- 		[PopR]					-> [^maxSize := 4].
- 		[PushR]					-> [^maxSize := 4].
- 		[PushCw]				-> [^maxSize := self literalLoadInstructionBytes + 4].
  		[PushCq]				-> [^self literalLoadInstructionBytes = 4
+ 										ifTrue: [self literalLoadInstructionBytes + 4]
- 										ifTrue: [maxSize := self literalLoadInstructionBytes + 4]
  										ifFalse:
  											[self rotateable8bitImmediate: (operands at: 0)
+ 												ifTrue: [:r :i| 8]
- 												ifTrue: [:r :i| maxSize := 8]
  												ifFalse:
  													[| val invVal |
  													invVal := (val := operands at: 0) < 0 ifTrue: [-1 - val] ifFalse: [val bitInvert32].
  													self rotateable8bitImmediate: invVal
+ 														ifTrue: [:r :i| 8]
+ 														ifFalse: [self literalLoadInstructionBytes + 4]]]].
+ 		[PrefetchAw] 			-> [^(self isAddressRelativeToVarBase: (operands at: 0))
+ 										ifTrue: [4]
+ 										ifFalse: [self literalLoadInstructionBytes + 4]].
- 														ifTrue: [:r :i| maxSize := 8]
- 														ifFalse: [maxSize := self literalLoadInstructionBytes + 4]]]].
- 		[PrefetchAw] 			-> [^maxSize := (self isAddressRelativeToVarBase: (operands at: 1))
- 													ifTrue: [4]
- 													ifFalse: [self literalLoadInstructionBytes + 4]].
  		"Conversion"
+ 		[ConvertRRd]			-> [^4].
- 		[ConvertRRd]			-> [^maxSize := 4].
  		}.
  	^0 "to keep C compiler quiet"
  !

Item was removed:
- ----- Method: CogARMCompiler>>concretizeAddCqR (in category 'generate machine code - concretize') -----
- concretizeAddCqR
- 	"Will get inlined into concretizeAt: switch."
- 	"Try whether the quick constant is a small negative number. If it is, optimize."
- 	<inline: true>
- 	self rotateable8bitImmediate: (operands at: 0)
- 		ifTrue: [ :rot :immediate | | reg |
- 			reg := self concreteRegister: (operands at: 1).
- 			self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot).
- 			^machineCodeSize := 4]
- 		ifFalse: [
- 			self rotateable8bitImmediate: (operands at: 0) negated
- 				ifTrue: [ :rot :immediate | |reg|
- 					reg := self concreteRegister: (operands at: 1).
- 					self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot).
- 					^machineCodeSize := 4]
- 				ifFalse: [^self concretizeDataOperationCwR: AddOpcode]].
- 	^0 "to keep Slang happy"!

Item was removed:
- ----- Method: CogARMCompiler>>concretizeAndCqR (in category 'generate machine code - concretize') -----
- concretizeAndCqR
- 	"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 fast ways to make the masks"
- 	<inline: true>
- 	|val|
- 	val := operands at: 0.
- 	self rotateable8bitImmediate: val
- 		ifTrue: [ :rot :immediate | | reg |
- 			reg := self concreteRegister: (operands at: 1).
- 			self machineCodeAt: 0 put: (self ands: reg rn: reg imm: immediate ror: rot).
- 			^machineCodeSize := 4]
- 		ifFalse: [
- 			"see if the constant bit-inverted makes a quick value and if so BIC it instead
- 			If the value is -ve, we 2s complement it instead"
- 			|invVal|
- 			val <0
- 				ifTrue:[invVal := -1 - val]
- 				ifFalse:[invVal := val bitInvert32].
- 			self rotateable8bitImmediate: invVal
- 				ifTrue: [ :rot :immediate | |reg|
- 					reg := self concreteRegister: (operands at: 1).
- 					self machineCodeAt: 0 put: (self bics: reg rn: reg imm: immediate ror: rot).
- 					^machineCodeSize := 4]
- 				ifFalse: ["let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
- 					|hb reg|
- 					reg := self concreteRegister: (operands at: 1).
- 					hb := (operands at: 0) highBit.
- 					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: reg rn: reg rm: ConcreteIPReg lsr: (32-hb )).
- 							^machineCodeSize :=8]
- 						ifFalse: [^self concretizeDataOperationCwR: AndOpcode]]].
- 	^0 "to keep Slang happy"!

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"
- 	"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 fast ways to make the masks"
  	<inline: true>
  	| val srcReg dstReg |
  	val := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	dstReg := self concreteRegister: (operands at: 2).
+ 	self rotateable8bitBitwiseImmediate: val
- 	self rotateable8bitImmediate: 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]).
- 			[ :rot :immediate |
- 			self machineCodeAt: 0 put: (self ands: dstReg rn: srcReg imm: immediate ror: rot).
  			^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.
+ 			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]].
- 		ifFalse:
- 			["see if the constant bit-inverted makes a quick value and if so BIC it instead
- 			If the value is -ve, we 2s complement it instead"
- 			|invVal|
- 			invVal := val < 0
- 						ifTrue:[-1 - val]
- 						ifFalse:[val bitInvert32].
- 			self rotateable8bitImmediate: invVal
- 				ifTrue:
- 					[ :rot :immediate |
- 					self machineCodeAt: 0 put: (self bics: dstReg rn: srcReg imm: immediate ror: rot).
- 					^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.
- 					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 added:
+ ----- 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 := self concreteRegister: (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)).
+ 			^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 concretizeDataOperationCwR: armOpcode].
+ 	^0 "to keep Slang happy"!

Item was added:
+ ----- 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 := self concreteRegister: (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)).
+ 			^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>>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].
  		 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[Literal]					-> [^self concretizeLiteral].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill16]					-> [^self concretizeFill16].
  		[Fill32]					-> [^self concretizeFill32].
  		[FillFromWord]			-> [^self concretizeFillFromWord].
  		[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].
- 		[AddCqR]					-> [^self concretizeAddCqR].
- 		[AddCwR]					-> [^self concretizeDataOperationCwR: AddOpcode].
- 		[AddRR]						-> [^self concretizeDataOperationRR: AddOpcode].
- 		[AddRdRd]					-> [^self concretizeAddRdRd].
- 		[AndCqR]					-> [^self concretizeAndCqR].
  		[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].
- 		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
- 		[CmpCqR]					-> [^self concretizeDataOperationCqR: CmpOpcode].
  		[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].
- 		[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 concretizeSubRdRd].
  		[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].
  		"ARM Specific Arithmetic" 
  		[SMULL]			-> [^self concretizeSMULL]	.
  		[CMPSMULL]		-> [^self concretizeCMPSMULL].
  		[MSR]				-> [^self concretizeMSR].
  		"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: CogARMCompiler>>getDefaultCogCodeSize (in category 'accessing') -----
- getDefaultCogCodeSize
- 	"Return the default number of bytes to allocate for native code at startup.
- 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
- 	<inline: true>
- 	^1024 * 1400!

Item was added:
+ ----- Method: CogARMCompiler>>inverseOpcodeFor: (in category 'generate machine code - support') -----
+ inverseOpcodeFor: opcode
+ 	"Several of the opcodes are inverses.  Answer the inverse for an opcode if it has one.
+ 	 See Table A3-2 in sec A3.4 Data-processing instructions of the AARM."
+ 	^opcode caseOf: {
+ 			[AddOpcode]		->	[SubOpcode].
+ 			[AndOpcode]		->	[BicOpcode].
+ 			[BicOpcode]		->	[AndOpcode].
+ 			[CmpOpcode]		->	[CmpNotOpcode].
+ 			[MoveOpcode]		->	[MoveNotOpcode].
+ 			[MoveNotOpcode]	->	[MoveOpcode].
+ 			[SubOpcode]		->	[AddOpcode] }
+ 		otherwise: [self error: 'opcode has no inverse']!

Item was changed:
  ----- Method: CogARMCompiler>>loadCwInto: (in category 'generate machine code - support') -----
  loadCwInto: destReg
  	"Load the operand into the destination register, answering
  	 the size of the instructions generated to do so."
  	| operand distance |
  	operand := operands at: 0.
+ 	(self isAnInstruction: operand) ifTrue:
+ 		[operand := (cogit cCoerceSimple: operand to: #'AbstractInstruction *') address].
  	"First try and encode as a pc-relative reference..."
  	(cogit addressIsInCurrentCompilation: operand) ifTrue:
  		[distance := operand - (address + 8).
+ 		 self rotateable8bitSignedImmediate: distance
+ 		 	ifTrue:
+ 				[:rot :immediate :negate|
+ 		 		 self machineCodeAt: 0 put: (negate
+ 												ifTrue: [self sub: destReg rn: PC imm: immediate ror: rot]
+ 												ifFalse: [self add: destReg rn: PC imm: immediate ror: rot]).
- 		 self rotateable8bitImmediate: distance
- 		 	ifTrue: [ :rot :immediate |
- 		 		self machineCodeAt: 0 put: (self add: destReg rn: PC imm: immediate ror: rot).
  		 		^4]
  		 	ifFalse:
+ 		 		[self deny: (self isAnInstruction: (operands at: 0))]].
+ 	"If this fails, use the conventional literal load sequence."
- 		 		[self rotateable8bitImmediate: distance negated
- 		 			ifTrue: [ :rot :immediate |
- 		 				self machineCodeAt: 0 put: (self sub: destReg rn: PC imm: immediate ror: rot).
- 		 				^4]
- 					ifFalse: []]].
- 	"If this fails, use the conventional and painfully long 4 instruction sequence."
  	^self moveCw: operand intoR: destReg!

Item was added:
+ ----- Method: CogARMCompiler>>rotateable8bitBitwiseImmediate:ifTrue:ifFalse: (in category 'testing') -----
+ rotateable8bitBitwiseImmediate: constant ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
+ 	<inline: true>
+ 	"Invoke trueAlternativeBlock with shift, value and inverted if constant can be represented
+ 	 by a possibly rotated 8-bit constant, otherwise invoke falseAlternativeBlock. For data
+ 	 processing operands, there is the immediate shifter_operand variant,  where an 8 bit value
+ 	 is ring shifted _right_ by i. This is only suitable for quick constants (Cq), which won't change."
+ 	| value |
+ 	value := constant.
+ 	[(value bitAnd: 16rFF) = value ifTrue:
+ 		[^trueAlternativeBlock value: 0 value: value value: constant ~= value].
+ 	 2 to: 30 by: 2 do:
+ 		[:i |
+ 		(value bitAnd: ((16rFF <<i bitAnd:16rFFFFFFFF) bitOr: 16rFF>>(32-i))) = value ifTrue:
+ 			[^trueAlternativeBlock
+ 				value: 32 - i
+ 				value: ((value >> i) bitOr: (value <<(32 - i) bitAnd:16rFFFFFFFF))
+ 				value: constant ~= value]].
+ 	 value = constant]
+ 		whileTrue:
+ 			[value := constant < 0
+ 						ifTrue:[-1 - constant]
+ 						ifFalse:[constant bitInvert32]].
+ 	^falseAlternativeBlock value!

Item was added:
+ ----- Method: CogARMCompiler>>rotateable8bitSignedImmediate:ifTrue:ifFalse: (in category 'testing') -----
+ rotateable8bitSignedImmediate: constant ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
+ 	<inline: true>
+ 	"Invoke trueAlternativeBlock with shift, value and negated if constant can be represented
+ 	 by a possibly rotated 8-bit constant, otherwise invoke falseAlternativeBlock. For data
+ 	 processing operands, there is the immediate shifter_operand variant,  where an 8 bit value
+ 	 is ring shifted _right_ by i. This is only suitable for quick constants (Cq), which won't change."
+ 	| value |
+ 	value := constant.
+ 	[(value bitAnd: 16rFF) = value ifTrue:
+ 		[^trueAlternativeBlock value: 0 value: value value: constant ~= value].
+ 	 2 to: 30 by: 2 do:
+ 		[:i |
+ 		(value bitAnd: ((16rFF <<i bitAnd:16rFFFFFFFF) bitOr: 16rFF>>(32-i))) = value ifTrue:
+ 			[^trueAlternativeBlock
+ 				value: 32 - i
+ 				value: ((value >> i) bitOr: (value <<(32 - i) bitAnd:16rFFFFFFFF))
+ 				value: constant ~= value]].
+ 	 value = constant and: [constant ~= 0]]
+ 		whileTrue:
+ 			[value := constant negated].
+ 	^falseAlternativeBlock value!

Item was changed:
  ----- Method: CogARMCompiler>>tst:rn:imm:ror: (in category 'ARM convenience instructions') -----
  tst: ignored rn: srcReg imm: immediate ror: rot
  "	Remember the ROR is doubled by the cpu so use 30>>1 etc"
  "also note that TST has no destReg
  	TST srcReg, #immediate ROR rot"
  
+ 	^self type: 1 op: TstOpcode set: 1 rn: srcReg rd: 0 shifterOperand: ((rot>>1) <<8 bitOr: immediate)!
- 	^self type: 1 op: 8 set: 1 rn: srcReg rd: 0 shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

Item was changed:
  ----- Method: CogAbstractInstruction>>isAnInstruction: (in category 'testing') -----
  isAnInstruction: addressOrInstruction
  	<var: #addressOrInstruction type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	^(cogit addressIsInInstructions: addressOrInstruction)
+ 	  or: [addressOrInstruction == cogit methodLabel]!
- 	^cogit addressIsInInstructions: addressOrInstruction!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
  	opcode isNil ifTrue:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	(cogit isKindOf: Cogit) ifTrue:
  		[format := CogRTLOpcodes printFormatForOpcodeName: opcodeName].
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand notNil ifTrue:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 (format notNil and: [(format at: index ifAbsent: nil) = $r])
  				ifTrue: [aStream nextPutAll: (self nameForRegister: operand)]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
  						[(operand allMask: 16r80000000) ifTrue:
  							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize ifNotNil:
  		[(machineCodeSize between: 1 and: machineCode size) ifTrue:
  			[0 to: machineCodeSize - 1 by: self codeGranularity do:
  				[:i|
  				 aStream space.
  				 (self machineCodeAt: i)
  					ifNil: [aStream nextPut: $.]
+ 					ifNotNil:
+ 						[:mc|
+ 						mc isInteger
+ 							ifTrue: [mc printOn: aStream base: 16]
+ 							ifFalse: [mc printOn: aStream]]]]].
- 					ifNotNil: [:mc| mc printOn: aStream base: 16]]]].
  	address ifNotNil:
  		[aStream nextPut: $@.
  		 address printOn: aStream base: 16].
  	aStream nextPut: $)!

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 ^N forms are to get around the bytecode compiler's long branch
- 	"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]					-> [^0].
+ 		[AlignmentNops]		-> [^(operands at: 0) - 1].
+ 		[Fill16]					-> [^2].
+ 		[Fill32]					-> [^4].
+ 		[FillFromWord]			-> [^4].
+ 		[Nop]					-> [^1].
- 		[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]					-> [^1].
+ 		[IDIVR]					-> [^2].
+ 		[IMULRR]				-> [^3].
+ 		[CPUID]					-> [^2].
+ 		[CMPXCHGAwR]			-> [^7].
+ 		[CMPXCHGMwrR]		-> [^8].
+ 		[LFENCE]				-> [^3].
+ 		[MFENCE]				-> [^3].
+ 		[SFENCE]				-> [^3].
+ 		[LOCK]					-> [^1].
+ 		[XCHGAwR]				-> [^6].
+ 		[XCHGMwrR]			-> [^7].
+ 		[XCHGRR]				-> [^2].
- 		[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"
+ 		[CallFull]					-> [^5].
+ 		[Call]						-> [^5].
+ 		[JumpR]						-> [^2].
+ 		[JumpFull]					-> [self resolveJumpTarget. ^5].
+ 		[JumpLong]					-> [self resolveJumpTarget. ^5].
+ 		[Jump]						-> [self resolveJumpTarget. ^5].
+ 		[JumpZero]					-> [self resolveJumpTarget. ^6].
+ 		[JumpNonZero]				-> [self resolveJumpTarget. ^6].
+ 		[JumpNegative]				-> [self resolveJumpTarget. ^6].
+ 		[JumpNonNegative]			-> [self resolveJumpTarget. ^6].
+ 		[JumpOverflow]				-> [self resolveJumpTarget. ^6].
+ 		[JumpNoOverflow]			-> [self resolveJumpTarget. ^6].
+ 		[JumpCarry]				-> [self resolveJumpTarget. ^6].
+ 		[JumpNoCarry]				-> [self resolveJumpTarget. ^6].
+ 		[JumpLess]					-> [self resolveJumpTarget. ^6].
+ 		[JumpGreaterOrEqual]		-> [self resolveJumpTarget. ^6].
+ 		[JumpGreater]				-> [self resolveJumpTarget. ^6].
+ 		[JumpLessOrEqual]			-> [self resolveJumpTarget. ^6].
+ 		[JumpBelow]				-> [self resolveJumpTarget. ^6].
+ 		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^6].
+ 		[JumpAbove]				-> [self resolveJumpTarget. ^6].
+ 		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^6].
+ 		[JumpLongZero]			-> [self resolveJumpTarget. ^6].
+ 		[JumpLongNonZero]		-> [self resolveJumpTarget. ^6].
+ 		[JumpFPEqual]				-> [self resolveJumpTarget. ^6].
+ 		[JumpFPNotEqual]			-> [self resolveJumpTarget. ^6].
+ 		[JumpFPLess]				-> [self resolveJumpTarget. ^6].
+ 		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^6].
+ 		[JumpFPGreater]			-> [self resolveJumpTarget. ^6].
+ 		[JumpFPLessOrEqual]		-> [self resolveJumpTarget. ^6].
+ 		[JumpFPOrdered]			-> [self resolveJumpTarget. ^6].
+ 		[JumpFPUnordered]			-> [self resolveJumpTarget. ^6].
+ 		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [1] ifFalse: [3]].
+ 		[Stop]						-> [^1].
- 		[CallFull]				-> [^maxSize := 5].
- 		[Call]					-> [^maxSize := 5].
- 		[JumpR]					-> [^maxSize := 2].
- 		[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]		-> [^(self isQuick: (operands at: 0))
- 		[AddCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
+ 		[AndCqR]		-> [^(self isQuick: (operands at: 0))
- 		[AndCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
+ 		[CmpCqR]		-> [^(self isQuick: (operands at: 0))
- 		[CmpCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
+ 		[OrCqR]			-> [^(self isQuick: (operands at: 0))
- 		[OrCqR]			-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
+ 		[SubCqR]		-> [^(self isQuick: (operands at: 0))
- 		[SubCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
+ 		[TstCqR]		-> [^((self isQuick: (operands at: 0)) and: [(self concreteRegister: (operands at: 1)) < 4])
- 		[TstCqR]		-> [^maxSize := ((self isQuick: (operands at: 0)) and: [(self concreteRegister: (operands at: 1)) < 4])
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
+ 		[AddCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[AndCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[CmpCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[OrCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[SubCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[XorCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[AddRR]			-> [^2].
+ 		[AndRR]			-> [^2].
+ 		[CmpRR]		-> [^2].
+ 		[OrRR]			-> [^2].
+ 		[XorRR]			-> [^2].
+ 		[SubRR]			-> [^2].
+ 		[NegateR]		-> [^2].
- 		[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]
+ 						-> [^((self isQuick: (operands at: 0))
- 						-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
+ 		[LogicalShiftLeftCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
+ 		[LogicalShiftRightCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
+ 		[ArithmeticShiftRightCqR]	-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
+ 		[LogicalShiftLeftRR]			-> [^self computeShiftRRSize].
+ 		[LogicalShiftRightRR]		-> [^self computeShiftRRSize].
+ 		[ArithmeticShiftRightRR]		-> [^self computeShiftRRSize].
+ 		[AddRdRd]					-> [^4].
+ 		[CmpRdRd]					-> [^4].
+ 		[SubRdRd]					-> [^4].
+ 		[MulRdRd]					-> [^4].
+ 		[DivRdRd]					-> [^4].
+ 		[SqrtRd]					-> [^4].
- 		[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]		-> [^(operands at: 0) = 0 ifTrue: [2] ifFalse: [5]].
+ 		[MoveCwR]		-> [^5].
+ 		[MoveRR]		-> [^2].
+ 		[MoveRdRd]		-> [^4].
+ 		[MoveAwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[MoveRAw]		-> [^(self concreteRegister: (operands at: 0)) = EAX ifTrue: [5] ifFalse: [6]].
+ 		[MoveRMwr]	-> [^((self isQuick: (operands at: 1))
- 		[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]	-> [^((self isQuick: (operands at: 1))
- 		[MoveRdM64r]	-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
+ 		[MoveMbrR]		-> [^((self isQuick: (operands at: 0))
- 		[MoveMbrR]		-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
+ 		[MoveRMbr]		-> [^((self isQuick: (operands at: 1))
- 		[MoveRMbr]		-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
+ 		[MoveM16rR]	-> [^((self isQuick: (operands at: 0))
- 		[MoveM16rR]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
+ 		[MoveM64rRd]	-> [^((self isQuick: (operands at: 0))
- 		[MoveM64rRd]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
+ 		[MoveMwrR]		-> [^((self isQuick: (operands at: 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.
+ 							^(self concreteRegister: (operands at: 1)) = EBP
- 							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
+ 							^((self concreteRegister: (operands at: 2)) = EBP
- 							^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.
+ 							^(self concreteRegister: (operands at: 1)) = EBP
- 							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
+ 							^(self concreteRegister: (operands at: 2)) = EBP
- 							^maxSize := (self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
+ 		[PopR]			-> [^1].
+ 		[PushR]			-> [^1].
+ 		[PushCq]		-> [^(self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
+ 		[PushCw]		-> [^5].
+ 		[PrefetchAw]	-> [^self hasSSEInstructions ifTrue: [7] ifFalse: [0]].
- 		[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]	-> [^4] }.
- 		[ConvertRRd]	-> [^maxSize := 4] }.
  	^0 "to keep C compiler quiet"!

Item was added:
+ ----- Method: CogInLineLiteralsARMCompiler>>getDefaultCogCodeSize (in category 'accessing') -----
+ getDefaultCogCodeSize
+ 	"Return the default number of bytes to allocate for native code at startup.
+ 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
+ 	<inline: true>
+ 	^1024 * 1536!

Item was changed:
  ----- Method: CogInLineLiteralsARMCompiler>>isPCDependent (in category 'testing') -----
  isPCDependent
  	"Answer if the receiver is a pc-dependent instruction."
+ 	^self isJump or: [opcode = AlignmentNops]!
- 	^self isJump or: [opcode = AlignmentNops or: [opcode = Call]]!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>concretizeLiteral (in category 'generate machine code') -----
  concretizeLiteral
+ 	| literalAsInstruction literal |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	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 and: [dependent address = address]]).
+ 	self machineCodeAt: 0 put: literal!
- 	self machineCodeAt: 0 put: (operands at: 0)!

Item was added:
+ ----- Method: CogOutOfLineLiteralsARMCompiler>>getDefaultCogCodeSize (in category 'accessing') -----
+ getDefaultCogCodeSize
+ 	"Return the default number of bytes to allocate for native code at startup.
+ 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
+ 	<inline: true>
+ 	^1024 * 1280!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>isPCDependent (in category 'testing') -----
  isPCDependent
  	"Answer if the receiver is a pc-dependent instruction.  With out-of-line literals any instruction
  	 that refers to a literal depends on the address of the literal, so add them in addition to the jumps."
+ 	^self isJump
+ 	  or: [opcode = AlignmentNops
+ 	  or: [dependent notNil and: [dependent opcode = Literal]]]!
- 	^self isJump or: [opcode = AlignmentNops or: [opcode = Call or: [dependent notNil and: [dependent opcode = Literal]]]]!

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 machineCodeAt: 0
+ 		put: (self
+ 				ldr: destReg
+ 				rn: PC
+ 				plus: (dependent address >= (address + 8) ifTrue: [1] ifFalse: [0])
+ 				imm: (dependent address - (address + 8)) abs).
- 	self machineCodeAt: 0 put: (self ldr: destReg rn: PC plusImm: address - dependent address).
  	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogOutOfLineLiteralsARMCompiler>>outOfLineLiteralOpcodeLimit (in category 'compile abstract instructions') -----
+ outOfLineLiteralOpcodeLimit
+ 	"The maximum offset in a LDR is 1<<12.  Be conservative."
+ 	^1<<(11-2)!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>usesOutOfLineLiteral (in category 'testing') -----
  usesOutOfLineLiteral
  	"Answer if the receiver uses an out-of-line literal.  Needs only
  	 to work for the opcodes created with gen:literal:operand: et al."
  
  	opcode
  		caseOf: {
  		[CallFull]		-> [^true].
  		[JumpFull]		-> [^true].
  		"Arithmetic"
+ 		[AddCqR]		-> [^self rotateable8bitSignedImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
- 		[AddCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[AndCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[AndCqRR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[CmpCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[OrCqR]			-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[SubCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[TstCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[XorCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[AddCwR]		-> [^true].
  		[AndCwR]		-> [^true].
  		[CmpCwR]		-> [^true].
  		[OrCwR]		-> [^true].
  		[SubCwR]		-> [^true].
  		[XorCwR]		-> [^true].
  		[LoadEffectiveAddressMwrR]
  						-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		"Data Movement"						
  		[MoveCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
+ 		[MoveCwR]		-> [^((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definition will be in the current compilation."
+ 							  or: [cogit addressIsInCurrentCompilation: (operands at: 0)]) not].
- 		[MoveCwR]		-> [^true].
  		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [false] ifFalse: [true]].
  		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) ifTrue: [false] ifFalse: [true]].
  		[MoveRMwr]	-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
+ 		[MoveRdM64r]	-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]]. 
- 		[MoveRdM64r]	-> [^true]. 
  		[MoveMbrR]		-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveRMbr]		-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveM16rR]	-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
+ 		[MoveM64rRd]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
- 		[MoveM64rRd]	-> [^true].
  		[MoveMwrR]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
+ 		[PushCw]		-> [^((self isAnInstruction: (operands at: 0)) "i.e. a label, which by definiion will be in the current compilation."
+ 							  or: [cogit addressIsInCurrentCompilation: (operands at: 0)]) not].
- 		[PushCw]		-> [^true].
  		[PushCq]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [false] ifFalse: [true]].
  		}
  		otherwise: [self assert: false].
  	^false "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: Cogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	ProcessorClass ifNil:
  		[Cogit initializeMiscConstants].
  	^{	CogMethodZone.
- 		CogAbstractInstruction.
- 		self activeCompilerClass.
  		CogBlockStart.
  		CogBytecodeDescriptor.
  		CogBytecodeFixup.
  		CogInstructionAnnotation.
  		CogPrimitiveDescriptor.
  		CogBlockMethod.
  		CogMethod },
+ 	(self activeCompilerClass withAllSuperclasses copyUpThrough: CogAbstractInstruction),
  	((options at: #NewspeakVM ifAbsent: [false])
  		ifTrue: [{NewspeakCogMethod. NSSendCache}]
  		ifFalse: [#()])!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := initializationOptions at: #Debug ifAbsent: [false].
  	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
+ 			[EagerInstructionDecoration ifNil:
- 			[EagerInstructionDecoration isNil ifTrue:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
  	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [#IA32]) caseOf: {
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien]. }.
  	CogCompilerClass := self activeCompilerClass.
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was added:
+ ----- Method: Cogit>>DumpJumpLong: (in category 'abstract instructions') -----
+ DumpJumpLong: jumpTarget
+ 	"Convenience conflation of JumpLong: & dumpLiterals for PIC generation.
+ 	 Literals must be dumped early and often to keep each PIC case the same size."
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	| inst |
+ 	<var: 'inst' type: #'AbstractInstruction *'>
+ 	inst := self gen: JumpLong operand: jumpTarget asInteger.
+ 	literalsManager dumpLiterals.
+ 	^inst!

Item was added:
+ ----- Method: Cogit>>DumpJumpLongZero: (in category 'abstract instructions') -----
+ DumpJumpLongZero: jumpTarget
+ 	"Convenience conflation of JumpLongZero: & dumpLiterals for PIC generation.
+ 	 Literals must be dumped early and often to keep each PIC case the same size."
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	| inst |
+ 	<var: 'inst' type: #'AbstractInstruction *'>
+ 	inst := self gen: JumpLongZero operand: jumpTarget asInteger.
+ 	literalsManager dumpLiterals.
+ 	^inst!

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  	"Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  	 its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  	 dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  	 having the MNU case for cache flushing."
   	<var: #cPIC type: #'CogMethod *'>
  	| operand target address size end |
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	coInterpreter
  		compilationBreak: cPIC selector
  		point: (objectMemory numBytesOf: cPIC selector)
  		isMNUCase: isMNUCase.
  	self allocateOpcodes: 5 bytecodes: 0.
  	literalsManager resetLiterals: 5.
  	methodLabel address: cPIC asUnsignedInteger; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  	"Caller patches to open pic if caseNMethod is young."
  	self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  	(isMNUCase not
  	 and: [coInterpreter methodHasCogMethod: caseNMethod])
  		ifTrue:
  			[operand := 0.
  			 target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  		ifFalse:
  			[operand := caseNMethod.
  			 isMNUCase
  				ifTrue:
  					[cPIC cpicHasMNUCase: true.
  					 target := cPIC asInteger + (self sizeof: CogMethod)]
  				ifFalse:
  					[target := cPIC asInteger + self picInterpretAbortOffset]].
  	self CmpCw: caseNTag R: TempReg.
  	self MoveCw: operand R: SendNumArgsReg.
+ 	self DumpJumpLongZero: target.
- 	self JumpLongZero: target.
  	self MoveCw: cPIC asUnsignedInteger R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: cPIC cmNumArgs).
  	self computeMaximumSizes.
  	address := self addressOfEndOfCase: cPIC cPICNumCases - 1 inCPIC: cPIC.
  	size := self generateInstructionsAt: address.
  	end := self outputInstructionsAt: address.
  	processor flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
  	cPIC cPICNumCases: cPIC cPICNumCases + 1.
  	^0!

Item was changed:
  ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
  cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
  	<api>
  	"Attempt to create a one-case PIC for an MNU.
  	 The tag for the case is at the send site and so doesn't need to be generated."
  	<returnTypeC: #'CogMethod *'>
  	| startAddress size end |
  	((objectMemory isYoung: selector)
  	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  		[^0].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: true.
  	self assert: endCPICCase0 notNil.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[coInterpreter callForCogCompiledCodeCompaction.
  		 ^0].
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
+ 	self allocateOpcodes: numPICCases * 9 bytecodes: 0.
- 	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	literalsManager resetLiterals: numPICCases * 2.
  	methodLabel address: startAddress; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileMNUCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
  	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
  	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
  	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
  								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
  	| startAddress size end |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: isMNUCase.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
+ 	self allocateOpcodes: numPICCases * 9 bytecodes: 0.
- 	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	literalsManager resetLiterals: numPICCases * 2.
  	methodLabel address: startAddress; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
  	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
  	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
  	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
  								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: endCPICCase0 address = (startAddress + firstCPICCaseOffset).
  	self assert: endCPICCase1 address = (startAddress + firstCPICCaseOffset + cPICCaseSize).
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>compileCPIC:Case0:Case1Method:tag:isMNUCase:numArgs: (in category 'in-line cacheing') -----
  compileCPIC: cPIC Case0: case0CogMethod Case1Method: case1Method tag: case1Tag isMNUCase: isMNUCase numArgs: numArgs
  	"Compile the code for a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; jump to its unchecked entry-point
  		- a CompiledMethod; jump to the ceInterpretFromPIC trampoline
  		- nil; call ceMNUFromPIC"
  	<var: #cPIC type: #'CogMethod *'>
  	| operand targetEntry jumpNext |
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<var: #targetEntry type: #'void *'>
  	<var: #jumpNext type: #'AbstractInstruction *'>
  	self assert: case1Method notNil.
  	self compilePICAbort: numArgs.
  	self assert: (objectRepresentation inlineCacheTagIsYoung: case1Tag) not.
  	(isMNUCase not
  	 and: [coInterpreter methodHasCogMethod: case1Method])
  		ifTrue:
  			[operand := 0.
  			 targetEntry := ((coInterpreter cogMethodOf: case1Method) asInteger + cmNoCheckEntryOffset) asVoidPointer]
  		ifFalse: "We do not scavenge PICs, hence we cannot cache the MNU method if it is in new space."
  			[operand := (case1Method isNil or: [objectMemory isYoungObject: case1Method])
  							ifTrue: [0]
  							ifFalse: [case1Method].
  			 targetEntry := case1Method isNil ifTrue: [picMNUAbort] ifFalse: [picInterpretAbort]].
  
  	jumpNext := self compileCPICEntry.
  	self MoveCw: 0 R: SendNumArgsReg.
+ 	self DumpJumpLong: case0CogMethod asInteger + cmNoCheckEntryOffset.
- 	self JumpLong: case0CogMethod asInteger + cmNoCheckEntryOffset.
  	endCPICCase0 := self CmpCw: case1Tag R: TempReg.
  	jumpNext jmpTarget: endCPICCase0.
  	self MoveCw: operand R: SendNumArgsReg.
+ 	self DumpJumpLongZero: (isMNUCase ifTrue: [picMNUAbort] ifFalse: [targetEntry]) asInteger.
- 	self JumpLongZero: (isMNUCase ifTrue: [picMNUAbort] ifFalse: [targetEntry]) asInteger.
  	endCPICCase1 := self MoveCw: cPIC asUnsignedInteger R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: numArgs).
  	^0
  !

Item was changed:
  ----- Method: Cogit>>compileClosedPICPrototype (in category 'in-line cacheing') -----
  compileClosedPICPrototype
  	"Compile the abstract instructions for a full closed PIC used to initialize closedPICSize.
  	 The loads into SendNumArgsReg are those for optional method objects which may be
  	 used in MNU cases."
  	<inline: true>
  	| numArgs jumpNext |
  	<var: #jumpNext type: #'AbstractInstruction *'>
  	numArgs := 0.
  	self compilePICAbort: numArgs.
  	jumpNext := self compileCPICEntry.
  	self MoveCw: 16r5EAF00D R: SendNumArgsReg.
+ 	self DumpJumpLong: methodZoneBase + 16rCA5E10.
- 	self JumpLong: methodZoneBase + 16rCA5E10.
  	jumpNext jmpTarget: (endCPICCase0 := self Label).
  	1 to: numPICCases - 1 do:
  		[:h|
  		self CmpCw: 16rBABE1F15+h R: TempReg.
  		self MoveCw: 16rBADA550 + h R: SendNumArgsReg.
+ 		self DumpJumpLongZero: 16rCA5E10 + (h * 16).
- 		self JumpLongZero: 16rCA5E10 + (h * 16).
  		h = 1 ifTrue:
  			[endCPICCase1 := self Label]].
  	self MoveCw: methodLabel address R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: numArgs).
  	^0!

Item was changed:
  ----- Method: Cogit>>compileMNUCPIC:methodOperand:numArgs: (in category 'in-line cacheing') -----
  compileMNUCPIC: cPIC methodOperand: methodOperand numArgs: numArgs
  	"Compile the code for a one-case MNU PIC that calls ceMNUFromPIC for case0Tag
  	 The tag for case0 is at the send site and so doesn't need to be generated."
  	<var: #cPIC type: #'CogMethod *'>
  	| jumpNext operand |
  	<var: #jumpNext type: #'AbstractInstruction *'>
  	self compilePICAbort: numArgs.
  	jumpNext := self compileCPICEntry.
  	"We do not scavenge PICs, hence we cannot cache the MNU method if it is in new space."
  	operand := (methodOperand isNil or: [objectMemory isYoungObject: methodOperand])
  					ifTrue: [0]
  					ifFalse: [methodOperand].
  	self MoveCw: operand R: SendNumArgsReg.
+ 	self DumpJumpLong: picMNUAbort asInteger.
- 	self JumpLong: picMNUAbort asInteger.
  	jumpNext jmpTarget: (self MoveCw: cPIC asUnsignedInteger R: ClassReg).
  	self JumpLong: (self cPICMissTrampolineFor: numArgs).
  	^0
  !

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

Item was changed:
  ----- Method: Cogit>>genCheckForInterruptsTrampoline (in category 'initialization') -----
  genCheckForInterruptsTrampoline
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	"if we have a link register we will assume that it does not get automatically pushed onto the stack
  	and thus there is no need to pop it before saving to instructionPointerAddress"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceCheckForInterrupts
  		called: 'ceCheckForInterruptsTrampoline'
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:and:forCall:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 and: regArg3 forCall: forCall called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it.
  
  						BEFORE				AFTER			(stacks grow down)
  						whatever			stackPointer ->	whatever
  						target address =>	reg1 = reg1val, etc
  						reg1val				pc = target address
  						reg2val
  		stackPointer ->	reg3val"
  
  	<var: #trampolineName type: #'char *'>
  	<returnTypeC: #'void (*genEnilopmartForandandforCallcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, sqInt forCall, char *trampolineName))(void)'>
  
  	| size endAddress enilopmart |
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	backEnd maybeEstablishVarBase. "Must happen first; value may be used in genLoadStackPointers"
  	backEnd genLoadStackPointers.
  	regArg3 ifNotNil: [self PopR: regArg3].
  	regArg2 ifNotNil: [self PopR: regArg2].
  	self PopR: regArg1.
  	self genEnilopmartReturn: forCall.
- 	literalsManager dumpLiterals.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genMethodAbortTrampoline (in category 'initialization') -----
  genMethodAbortTrampoline
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
  
  	"The abort sequencer has pushed the LinkReg a second time.
  	 Overwrite it with the right one."
  	backEnd hasLinkRegister ifTrue:
  		[self MoveR: LinkReg Mw: 0 r: SPReg].
  	self compileTrampolineFor: #ceStackOverflow:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false "The LinkReg has already been set above."
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	^self genTrampolineFor: #ceSICMiss:
  		called: 'ceMethodAbort'
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true "Push the LinkReg for the ceMethodAbort call."
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genNSSendTrampolineFor:numArgs:called: (in category 'initialization') -----
  genNSSendTrampolineFor: aRoutine numArgs: numArgs called: aString
  	"ReceiverResultReg: method receiver
  	SendNumArgsReg: the NSSendCache cache"
  	<option: #NewspeakVM>
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	| jumpMiss jumpItsTheReceiverStupid |
  	<var: #jumpMiss type: #'AbstractInstruction *'>
  	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	objectRepresentation
  		genGetInlineCacheClassTagFrom: ReceiverResultReg
  		into: ClassReg
  		forEntry: false.
  	self MoveMw: NSCClassTagIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  	self CmpR: ClassReg R: TempReg.
  	jumpMiss := self JumpNonZero: 0.
  	self MoveMw: NSCEnclosingObjectIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  	self CmpCq: 0 R: TempReg.
  	jumpItsTheReceiverStupid := self JumpZero: 0.
  	self MoveR: TempReg R: ReceiverResultReg.
  	"Now set the stacked receiver, if needed.  If there are reg args this is
  	 not required; see genPushRegisterArgsForNumArgs:numArgs: below."
  	(self numRegArgs = 0 or: [numArgs > self numRegArgs]) ifTrue:
  		[numArgs >= (NumSendTrampolines - 1)
  			ifTrue: "arbitrary argument count"
  				[self MoveMw: NSCNumArgsIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  				 backEnd hasLinkRegister ifFalse:
  					[self AddCq: 1 R: TempReg]..
  				 self MoveR: ReceiverResultReg Xwr: TempReg R: SPReg]
  			ifFalse: "Known argument count"
  				[self MoveR: TempReg Mw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]) + numArgs * objectMemory wordSize r: SPReg]].
  	jumpItsTheReceiverStupid jmpTarget: self Label.
  	self MoveMw: NSCTargetIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  	self JumpR: TempReg.
  
  	jumpMiss jmpTarget: self Label.
  	objectRepresentation
  		genEnsureOopInRegNotForwarded: ReceiverResultReg
  		scratchReg: TempReg
  		updatingMw: FoxMFReceiver
  		r: FPReg.
  	self numRegArgs > 0 ifTrue:
  		[backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: TempReg].
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 2
  		arg: SendNumArgsReg "The NSSendCache"
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: ReceiverResultReg  "Never happens?"
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genNonLocalReturnTrampoline (in category 'initialization') -----
  genNonLocalReturnTrampoline
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	"write the return address to the coInterpreter instructionPointerAddress;
  	 following the CallRT to this CISCs will have pushed it on the stack, so pop it first; RISCs will have it in
  	 their link register so just write it directly."
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceNonLocalReturn:
  		called: 'ceNonLocalReturnTrampoline'
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genPICAbortTrampoline (in category 'initialization') -----
  genPICAbortTrampoline
  	"Generate the abort for a PIC.  This abort performs either a call of
  	 ceInterpretMethodFromPIC:receiver: to handle invoking an uncogged
  	 target or a call of ceMNUFromPICMNUMethod:receiver: to handle an
  	 MNU dispatch in a closed PIC.  It distinguishes the two by testing
  	 ClassReg.  If the register is zero then this is an MNU."
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	backEnd hasLinkRegister ifTrue:
  		[self PushR: LinkReg].
  	^self genInnerPICAbortTrampoline: 'cePICAbort'!

Item was changed:
  ----- Method: Cogit>>generateClosedPICPrototype (in category 'initialization') -----
  generateClosedPICPrototype
  	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
  	numPICCases := 6.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
+ 	self allocateOpcodes: numPICCases * 9 bytecodes: 0.
- 	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	literalsManager resetLiterals: numPICCases * 2.
  	methodLabel address: methodZoneBase; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileClosedPICPrototype.
  	self computeMaximumSizes.
  	closedPICSize := (self sizeof: CogMethod) + (self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod)).
  	firstCPICCaseOffset := endCPICCase0 address - methodZoneBase.
  	cPICCaseSize := endCPICCase1 address - endCPICCase0 address.
  	cPICEndSize := closedPICSize - (numPICCases - 1 * cPICCaseSize + firstCPICCaseOffset).
  	closedPICSize := methodZone roundUpLength: closedPICSize.
  	self assert: picInterpretAbort address = (methodLabel address + self picInterpretAbortOffset)
  	"self cCode: ''
  		inSmalltalk:
  			[| end |
  			 end := self outputInstructionsAt: methodZoneBase + headerSize.
  			 self disassembleFrom: methodZoneBase + headerSize to: end - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	<returnTypeC: #'CogMethod *'>
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
+ 	methodLabel address: methodZone freeStart.
- 	methodLabel address: headerSize negated.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: nil start: methodLabel address + cmNoCheckEntryOffset.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	totalSize > MaxMethodSize ifTrue:
  		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithNopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: selector.
  	postCompileHook notNil ifTrue:
  		[self perform: postCompileHook with: method with: primInvokeLabel.
  		 postCompileHook := nil].
  	^method!

Item was changed:
  ----- Method: Cogit>>generateVMOwnerLockFunctions (in category 'initialization') -----
  generateVMOwnerLockFunctions
  	| startAddress |
  	<inline: false>
  	self cppIf: COGMTVM
  		ifTrue:
  			[self allocateOpcodes: backEnd numLowLevelLockOpcodes bytecodes: 0.
+ 			self zeroOpcodeIndex.
  			initialPC := 0.
  			endPC := numAbstractOpcodes - 1.
  			startAddress := methodZoneBase.
  			backEnd generateLowLevelTryLock: coInterpreter vmOwnerLockAddress.
  			self outputInstructionsForGeneratedRuntimeAt: startAddress.
  			self recordGeneratedRunTime: 'ceTryLockVMOwner' address: startAddress.
  			ceTryLockVMOwner := self cCoerceSimple: startAddress to: #'unsigned long (*)(void)'.
  
+ 			self zeroOpcodeIndex.
- 			opcodeIndex := 0.
- 			literalsManager resetLiterals: 1.
  			initialPC := 0.
  			endPC := numAbstractOpcodes - 1.
  			startAddress := methodZoneBase.
  			backEnd generateLowLevelUnlock: coInterpreter vmOwnerLockAddress.
  			self outputInstructionsForGeneratedRuntimeAt: startAddress.
  			self recordGeneratedRunTime: 'ceUnlockVMOwner' address: startAddress.
  			ceUnlockVMOwner := self cCoerceSimple: startAddress to: #'void (*)(void)']!

Item was changed:
  ----- Method: Cogit>>outputInstructionsForGeneratedRuntimeAt: (in category 'initialization') -----
  outputInstructionsForGeneratedRuntimeAt: startAddress
  	"Output instructions generated for one of the generated run-time routines, a trampoline, etc"
  	| size endAddress |
  	<inline: false>
- 	literalsManager dumpLiterals.
  	self computeMaximumSizes.
+ 	methodLabel address: startAddress. "for addressIsInCurrentCompilation:"
  	size := self generateInstructionsAt: startAddress.
  	endAddress := self outputInstructionsAt: startAddress.
  	self assert: startAddress + size = endAddress.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self cCode: '' inSmalltalk: [methodZone freeStart: methodZoneBase].
  	^startAddress!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>mustDumpLiterals: (in category 'testing') -----
  mustDumpLiterals: opcodeIndex
  	<inline: true>
+ 	^cogit getOpcodeIndex >= firstOpcodeIndex
+ 	  and: [cogit getOpcodeIndex - firstOpcodeIndex >= cogit backEnd outOfLineLiteralOpcodeLimit]!
- 	^cogit opcodeIndex >= firstOpcodeIndex
- 	  and: [cogit opcodeIndex - firstOpcodeIndex >= cogit backEnd outOfLineLiteralOpcodeLimit]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
  genMustBeBooleanTrampolineFor: boolean called: trampolineName
  	<var: #trampolineName type: #'char *'>
  	<inline: false>
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
  	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
  	self AddCq: boolean R: TempReg.
  	^self genTrampolineFor: #ceSendMustBeBoolean:
  		called: trampolineName
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimReturnEnterCogCodeEnilopmart: (in category 'initialization') -----
  genPrimReturnEnterCogCodeEnilopmart: profiling
  	"Generate the substitute return code for an external or FFI primitive call.
  	 On success simply return, extracting numArgs from newMethod.
  	 On primitive failure call ceActivateFailingPrimitiveMethod: newMethod."
  	| jmpSample continuePostSample jmpFail |
  	<var: #jmpSample type: #'AbstractInstruction *'>
  	<var: #continuePostSample type: #'AbstractInstruction *'>
  	<var: #jmpFail type: #'AbstractInstruction *'>
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  
  	profiling ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick: if so.
  		  N.B. nextProfileTick is 64-bits so 32-bit systems need to test both halves."
  		objectMemory wordSize = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
  				 self OrR: TempReg R: ClassReg]
  			ifFalse:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self CmpCq: 0 R: TempReg].
  		"If set, jump to record sample call."
  		jmpSample := self JumpNonZero: 0.
  		continuePostSample := self Label].
  
  	self maybeCompileAllocFillerCheck.
  
  	"Test primitive failure"
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	self flag: 'ask concrete code gen if move sets condition codes?'.
  	self CmpCq: 0 R: TempReg.
  	jmpFail := self JumpNonZero: 0.
  
  	"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  		success:	stackPointer	->	result (was receiver)
  										arg1
  										...
  										argN
  										return pc
  		failure:							receiver
  										arg1
  										...
  					stackPointer	->	argN
  										return pc
  	We push the instructionPointer to reestablish the return pc in the success case,
  	but leave it to ceActivateFailingPrimitiveMethod: to do so in the failure case."
  
  	backEnd hasLinkRegister
  		ifTrue:
  			[backEnd genLoadStackPointers.											"Switch back to Smalltalk stack."
  			 backEnd hasPCRegister
  				ifTrue:
  					[self PopR: ReceiverResultReg.										"Pop result from stack"
  					 self MoveAw: coInterpreter instructionPointerAddress R: PCReg]	"Return"
  				ifFalse:
  					[self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  					 self MoveAw: coInterpreter instructionPointerAddress R: LinkReg.	"Get ret pc"
  					 self RetN: objectMemory wordSize]]								"Return, popping result from stack"
  		ifFalse:
  			[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.	"Get return pc"
  			 backEnd genLoadStackPointers.									"Switch back to Smalltalk stack."
  			 self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  			 self MoveR: ClassReg Mw: 0 r: SPReg.								"Restore return pc"
  			 self RetN: 0].														"Return, popping result from stack"
  
  	"Primitive failed.  Invoke C code to build the frame and continue."
  	jmpFail jmpTarget: (self MoveAw: coInterpreter newMethodAddress R: SendNumArgsReg).
  	"Reload sp with CStackPointer; easier than popping args of checkProfileTick."
  	self MoveAw: self cStackPointerAddress R: SPReg.
  	self 
  		compileCallFor: #ceActivateFailingPrimitiveMethod:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: nil
  		saveRegs: false.
  
  	"On Spur ceActivateFailingPrimitiveMethod: may retry the primitive and return if successful.
  	 So continue by returning to the caller.
  	 Switch back to the Smalltalk stack.  Stack should be in this state:
  				success:	stackPointer ->	result (was receiver)
  											arg1
  											...
  											argN
  											return pc
  	 We can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
  	self MoveAw: coInterpreter instructionPointerAddress
  		R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  	backEnd genLoadStackPointers.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveMw: 0 r: SPReg R: ReceiverResultReg]	"Fetch result from stack"
  		ifFalse:
  			[self MoveMw: objectMemory wordSize r: SPReg R: ReceiverResultReg.	"Fetch result from stack"
  			 self PushR: ClassReg].											"Restore return pc on CISCs"
  	self RetN: objectMemory wordSize.	"return to caller, popping receiver"
  
  	profiling ifTrue:
  		["Call ceCheckProfileTick: to record sample and then continue.  newMethod
  		 should be up-to-date.  Need to save and restore the link reg around this call."
  		 jmpSample jmpTarget: self Label.
  		 backEnd saveAndRestoreLinkRegAround:
  			[self CallFullRT: (self cCode: '(unsigned long)ceCheckProfileTick'
  						inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick])].
  		 self Jump: continuePostSample]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
  genMustBeBooleanTrampolineFor: boolean called: trampolineName
  	"This can be entered in one of two states, depending on SendNumArgsReg. See
  	 e.g. genJumpIf:to:.  If SendNumArgsReg is non-zero then this has been entered via
  	 the initial test of the counter in the jump executed count (i.e. the counter has
  	 tripped).  In this case TempReg contains the boolean to be tested and should not
  	 be offset, and ceCounterTripped should be invoked with the unoffset TempReg.
  	 If SendNumArgsReg is zero then this has been entered for must-be-boolean
  	 processing. TempReg has been offset by boolean and must be corrected and
  	 ceSendMustBeBoolean: invoked with the corrected value."
  	<var: #trampolineName type: #'char *'>
  	| jumpMBB |
  	<var: #jumpMBB type: #'AbstractInstruction *'>
  	<inline: false>
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	self CmpCq: 0 R: SendNumArgsReg.
  	jumpMBB := self JumpZero: 0.
  	"Open-code self compileTrampolineFor: #ceCounterTripped: numArgs: 1 arg: TempReg ...
  	 so we can restore ResultReceiverReg."
  	self genSmalltalkToCStackSwitch: true.
  	self
  		compileCallFor: #ceCounterTripped:
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: TempReg "(*)"
  		saveRegs: false.
  	"(*) For the case where the ceCounterTripped: call returns (e.g. because there's no callback selector
  	 installed), the call to the ceSendMustBeBooleanAddTrue/FalseTrampoline is followed by a jump
  	 back to the start of the counter/condition test sequence.  For this case copy the C result to
  	 TempReg (the register that is tested), to reload it with the boolean to be tested."
  	backEnd genLoadStackPointers.
  	backEnd hasLinkRegister ifTrue:
  		[self PopR: LinkReg].
  	"To keep ResultReceiverReg live if optStatus thiught it was, simply reload it
  	 from the frame pointer.  This avoids having to reload it in the common case
  	 (counter does not trip) if it was live."
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	self RetN: 0.
  	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
  	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
  	jumpMBB jmpTarget: (self AddCq: boolean R: TempReg).
  	^self genTrampolineFor: #ceSendMustBeBoolean:
  		called: trampolineName
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genCallPICEnilopmartNumArgs: (in category 'initialization') -----
  genCallPICEnilopmartNumArgs: numArgs
  	"Generate special versions of the ceCallCogCodePopReceiverAndClassRegs
  	 enilopmart that also pop register args from the stack to undo the pushing of
  	 register args in the abort/miss trampolines."
  	<returnTypeC: 'void (*genCallPICEnilopmartNumArgs(sqInt numArgs))(void)'>
  	| size endAddress enilopmart |
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	backEnd maybeEstablishVarBase. "Must happen first; value may be used in genLoadStackPointers"
  	backEnd genLoadStackPointers.
  	self PopR: ClassReg. "cacheTag"
  	self PopR: TempReg. "entry-point"
  	self PopR: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [SendNumArgsReg]). "retpc"
  	numArgs > 0 ifTrue:
  		[numArgs > 1 ifTrue:
  			[self PopR: Arg1Reg.
  			 self assert: self numRegArgs = 2].
  		 self PopR: Arg0Reg].
  	self PopR: ReceiverResultReg.
  	backEnd hasLinkRegister ifFalse: [self PushR: SendNumArgsReg]. "retpc"
  	self JumpR: TempReg.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: (self trampolineName: 'ceCallPIC' numRegArgs: numArgs) address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMethodAbortTrampolineFor: (in category 'initialization') -----
  genMethodAbortTrampolineFor: numArgs
  	
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
  
  	"The abort sequence has pushed the LinkReg a second time - because a stack
  	 overflow can only happen after building a frame, which pushes LinkReg anyway, and
  	 we still need to push LinkReg in case we get to this routine from a sendMissAbort.
  	 (On ARM there is a simpler way; use two separate abort calls since all instructions are 32-bits
  	  but on x86 the zero receiver reg, call methodAbort sequence is smaller; we may fix this one day).
  	 Overwrite that duplicate with the right one - the return address for the call to the abort trampoline.
  	 The only reason it matters is an assert in ceStackOverflow: uses it"
  	backEnd hasLinkRegister ifTrue:
  		[self MoveR: LinkReg Mw: 0 r: SPReg].
  	self compileTrampolineFor: #ceStackOverflow:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false "The LinkReg has already been set above."
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genTrampolineFor: #ceSICMiss:
  		called: (self trampolineName: 'ceMethodAbort' numRegArgs: numArgs)
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false "The LinkReg will have been pushed in genPushRegisterArgsForAbortMissNumArgs: above."
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPICAbortTrampolineFor: (in category 'initialization') -----
  genPICAbortTrampolineFor: numArgs
  	"Generate the abort for a PIC.  This abort performs either a call of
  	 ceInterpretMethodFromPIC:receiver: to handle invoking an uncogged
  	 target or a call of ceMNUFromPICMNUMethod:receiver: to handle an
  	 MNU dispatch in a closed PIC.  It distinguishes the two by testing
  	 ClassReg.  If the register is zero then this is an MNU."
+ 	self zeroOpcodeIndex. 
- 	opcodeIndex := 0. 
  	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genInnerPICAbortTrampoline: (self trampolineName: 'cePICAbort' numRegArgs: numArgs)!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPICMissTrampolineFor: (in category 'initialization') -----
  genPICMissTrampolineFor: numArgs
  	<inline: false>
  	| startAddress |
  	startAddress := methodZoneBase.
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	"N.B. a closed PIC jumps to the miss routine, not calls it, so there is only one retpc on the stack."
  	backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: SendNumArgsReg.
  	self genTrampolineFor: #ceCPICMiss:receiver:
  		called: (self trampolineName: 'cePICMiss' numRegArgs: numArgs)
  		numArgs: 2
  		arg: ClassReg
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendTrampolineFor:numArgs:called:arg:arg:arg: (in category 'initialization') -----
  genSendTrampolineFor: aRoutine numArgs: numArgs called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2
  	"Generate a trampoline with three arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: SendNumArgsReg.
  	self genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendTrampolineFor:numArgs:called:arg:arg:arg:arg: (in category 'initialization') -----
  genSendTrampolineFor: aRoutine numArgs: numArgs called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate a trampoline with four arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
+ 	self zeroOpcodeIndex.
- 	opcodeIndex := 0.
  	backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: SendNumArgsReg.
  	self genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 4
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		saveRegs: false
  		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!



More information about the Vm-dev mailing list