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

commits at source.squeak.org commits at source.squeak.org
Fri Jul 4 00:35:36 UTC 2014


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

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

Name: VMMaker.oscog-eem.802
Author: eem
Time: 3 July 2014, 5:33:01.026 pm
UUID: 54ee6cf7-485a-41d6-8749-9a94d6288e69
Ancestors: VMMaker.oscog-eem.801

Split the enilopmarts into those that are used in the context
of a call (entering code as if from a call) and those used in
other contexts (converting interpreted method to machine
code method in loops, returning form interpreter method
to machine code one, etc).

Implement the call enilopmarts correctly (we hope) for ARM
where pushed ret pc must be popped into LinkReg.

Add a PCReg abstract reg and use it to implement jumping
to popped top of stack by popping into PCReg (for ARM).

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

Item was changed:
  ----- Method: CoInterpreter>>activateCoggedNewMethod: (in category 'message sending') -----
  activateCoggedNewMethod: inInterpreter
  	"Activate newMethod when newMethod has been cogged, i.e. create a machine-code frame and (re)enter machine-code."
  	| methodHeader cogMethod rcvr numTemps errorCode switched |
  	<var: #cogMethod type: #'CogMethod *'>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader).
  
  	cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  	methodHeader := cogMethod methodHeader.
  	rcvr := self stackValue: cogMethod cmNumArgs. "could new rcvr be set at point of send?"
  	self push: instructionPointer.
  	cogMethod stackCheckOffset = 0 ifTrue:
  		["frameless method; nothing to activate..."
  		 cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
  			[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 				[self callRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
- 				[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
  		 self push: cogMethod asInteger + cogit noCheckEntryOffset.
  		 self push: rcvr.
+ 		 cogit ceCallCogCodePopReceiverReg.
- 		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: cogMethod asInteger.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	cogMethod cmNumArgs + 1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		[| initialPC |
  		 "Store the error code if the method starts with a long store temp.  No instructionPointer skip because we're heading for machine code."
  		 initialPC := (self initialPCForHeader: methodHeader method: newMethod) + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: initialPC) = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	stackPointer >= stackLimit ifTrue:
  		[self assert: cogMethod stackCheckOffset > cogit noCheckEntryOffset.
  		 self push: cogMethod asInteger + cogMethod stackCheckOffset.
  		 self push: rcvr.
+ 		 cogit ceCallCogCodePopReceiverReg.
- 		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	instructionPointer := cogMethod asInteger + cogMethod stackCheckOffset.
  	switched := self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was added:
+ ----- Method: CoInterpreter>>callRegisterArgCogMethod:at:receiver: (in category 'enilopmarts') -----
+ callRegisterArgCogMethod: cogMethod at: entryOffset receiver: rcvr
+ 	"convert
+ 	 		rcvr	base
+ 			arg(s)
+ 			retpc	<- sp
+ 	 to
+ 			retpc	base
+ 			entrypc
+ 			rcvr
+ 			arg(s)	<- sp
+ 	 and then enter at either the checked or the unchecked entry-point."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	self assert: (cogit numRegArgs > 0 and: [cogit numRegArgs <= 2 and: [cogMethod cmNumArgs <= cogit numRegArgs]]).
+ 	cogMethod cmNumArgs = 2 ifTrue:
+ 		[self stackValue: 3 put: self stackTop. "retpc"
+ 		 self push: (self stackValue: 1). "last arg"
+ 		 self stackValue: 1 put: (self stackValue: 3). "first arg"
+ 		 self stackValue: 2 put: rcvr.
+ 		 self stackValue: 3 put: cogMethod asInteger + entryOffset.
+ 		 cogit ceCallCogCodePopReceiverArg1Arg0Regs
+ 		"NOTREACHED"].
+ 	cogMethod cmNumArgs = 1 ifTrue:
+ 		[self stackValue: 2 put: self stackTop. "retpc"
+ 		 self push: (self stackValue: 1). "arg"
+ 		 self stackValue: 1 put: rcvr.
+ 		 self stackValue: 2 put: cogMethod asInteger + entryOffset.
+ 		 cogit ceCallCogCodePopReceiverArg0Regs
+ 		"NOTREACHED"].
+ 	self assert: cogMethod cmNumArgs = 0.
+ 	self stackValue: 1 put: self stackTop. "retpc"
+ 	self stackValue: 0 put: cogMethod asInteger + entryOffset.
+ 	self push: rcvr.
+ 	cogit ceCallCogCodePopReceiverReg
+ 	"NOTREACHED"!

Item was removed:
- ----- Method: CoInterpreter>>enterRegisterArgCogMethod:at:receiver: (in category 'enilopmarts') -----
- enterRegisterArgCogMethod: cogMethod at: entryOffset receiver: rcvr
- 	"convert
- 	 		rcvr	base
- 			arg(s)
- 			retpc	<- sp
- 	 to
- 			retpc	base
- 			entrypc
- 			rcvr
- 			arg(s)	<- sp
- 	 and then enter at either the checked or the unchecked entry-point."
- 	<var: #cogMethod type: #'CogMethod *'>
- 	self assert: (cogit numRegArgs > 0 and: [cogit numRegArgs <= 2 and: [cogMethod cmNumArgs <= cogit numRegArgs]]).
- 	cogMethod cmNumArgs = 2 ifTrue:
- 		[self stackValue: 3 put: self stackTop. "retpc"
- 		 self push: (self stackValue: 1). "last arg"
- 		 self stackValue: 1 put: (self stackValue: 3). "first arg"
- 		 self stackValue: 2 put: rcvr.
- 		 self stackValue: 3 put: cogMethod asInteger + entryOffset.
- 		 cogit ceEnterCogCodePopReceiverArg1Arg0Regs
- 		"NOTREACHED"].
- 	cogMethod cmNumArgs = 1 ifTrue:
- 		[self stackValue: 2 put: self stackTop. "retpc"
- 		 self push: (self stackValue: 1). "arg"
- 		 self stackValue: 1 put: rcvr.
- 		 self stackValue: 2 put: cogMethod asInteger + entryOffset.
- 		 cogit ceEnterCogCodePopReceiverArg0Regs
- 		"NOTREACHED"].
- 	self assert: cogMethod cmNumArgs = 0.
- 	self stackValue: 1 put: self stackTop. "retpc"
- 	self stackValue: 0 put: cogMethod asInteger + entryOffset.
- 	self push: rcvr.
- 	cogit ceEnterCogCodePopReceiverReg
- 	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>executeCogBlock:closure:mayContextSwitch: (in category 'enilopmarts') -----
  executeCogBlock: cogMethod closure: closure mayContextSwitch: mayContextSwitch
  	"Execute a block within a CogMethod.  The caller has already pushed
  	 the block and any arguments and the return pc.  First push the
  	 return-to-interpreter trampoline, then the entry-point and finally the
  	 register argument(s).  Then jump to the block entry by executing a
  	 return instruction.
  	 In the simple jit only the receiver gets passed in registers, so only the
  	 receiver gets pushed."
  	<var: #cogMethod type: #'CogMethod *'>
  	cogit assertCStackWellAligned.
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer.
  	self ensurePushedInstructionPointer.
  	self push: cogMethod asInteger
  			+ (mayContextSwitch
  				ifTrue: [cogMethod blockEntryOffset]
  				ifFalse: [cogMethod blockEntryOffset - cogit noContextSwitchBlockEntryOffset]).
  	self push: closure.
+ 	cogit ceCallCogCodePopReceiverReg
- 	cogit ceEnterCogCodePopReceiverReg
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>executeCogMethod:fromLinkedSendWithReceiver: (in category 'enilopmarts') -----
  executeCogMethod: cogMethod fromLinkedSendWithReceiver: rcvr
  	<api>
  	"Execute a CogMethod from a linked send.  The receiver,
  	 arguments and return address are on the Smalltalk stack.  First
  	 push the entry-point and finally the register argument(s).  Then write
  	 back the frame pointers and call the routine that will pop off the register
  	 argument(s) and jump to the entry by executing a return instruction.
  
  	 In the simple jit only the receiver gets passed in registers, so only the
  	 receiver gets pushed."
  	<var: #cogMethod type: #'CogMethod *'>
  	cogit assertCStackWellAligned.
  	self assert: (self isMachineCodeFrame: framePointer).
  	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
  	cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
  		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 			[self callRegisterArgCogMethod: cogMethod at: cogit entryOffset receiver: rcvr]].
- 			[self enterRegisterArgCogMethod: cogMethod at: cogit entryOffset receiver: rcvr]].
  	self
  		push: cogMethod asInteger + cogit entryOffset;
  		push: rcvr.
+ 	cogit ceCallCogCodePopReceiverReg
- 	cogit ceEnterCogCodePopReceiverReg
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>executeCogMethod:fromLinkedSendWithReceiver:andCacheTag: (in category 'enilopmarts') -----
  executeCogMethod: cogMethod fromLinkedSendWithReceiver: rcvr andCacheTag: cacheTag
  	<api>
  	"Execute a CogMethod from a linked send.  The receiver,
  	 arguments and return address are on the Smalltalk stack.  First
  	 push the entry-point and finally the register argument(s).  Then write
  	 back the frame pointers and call the routine that will pop off the register
  	 argument(s) and jump to the entry by executing a return instruction.
  
  	 In the simple jit only the receiver gets passed in registers, so only the
  	 receiver gets pushed."
  	<var: #cogMethod type: #'CogMethod *'>
  	cogit assertCStackWellAligned.
  	self assert: (self isMachineCodeFrame: framePointer).
  	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
  	self push: cogMethod asInteger + cogit entryOffset.
  	cogit numRegArgs > 0 ifTrue:"dont use and: so as to get Slang to inline cogit numRegArgs > 0"
  		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
  			[self push: cacheTag.
  			 cogMethod cmNumArgs caseOf: {
+ 				[0]	->	[cogit ceCall0ArgsPIC].
+ 				[1]	->	[cogit ceCall1ArgsPIC].
+ 				[2]	->	[cogit ceCall2ArgsPIC]
- 				[0]	->	[cogit ceEnter0ArgsPIC].
- 				[1]	->	[cogit ceEnter1ArgsPIC].
- 				[2]	->	[cogit ceEnter2ArgsPIC]
  			 	}
  				otherwise: [].
  			 self error: 'not reached']].
  	self
  		push: rcvr;
  		push: cacheTag.
+ 	cogit ceCallCogCodePopReceiverAndClassRegs
- 	cogit ceEnterCogCodePopReceiverAndClassRegs
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>executeCogMethod:fromUnlinkedSendWithReceiver: (in category 'enilopmarts') -----
  executeCogMethod: cogMethod fromUnlinkedSendWithReceiver: rcvr
  	"Execute a CogMethod from an unlinked send.  The receiver,
  	 arguments and return address are on the Smalltalk stack.  First
  	 push the entry-point and finally the register argument(s).  Then write
  	 back the frame pointers and call the routine that will pop off the register
  	 argument(s) and jump to the entry by executing a return instruction.
  
  	 In the simple jit only the receiver gets passed in registers, so only the
  	 receiver gets pushed."
  	<var: #cogMethod type: #'CogMethod *'>
  	cogit assertCStackWellAligned.
  	self assert: (self isMachineCodeFrame: framePointer).
  	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
  	cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
  		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 			[self callRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
- 			[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
  	self
  		push: cogMethod asInteger + cogit noCheckEntryOffset;
  		push: rcvr.
+ 	cogit ceCallCogCodePopReceiverReg
- 	cogit ceEnterCogCodePopReceiverReg
  	"NOTREACHED"!

Item was changed:
  ----- Method: CogARMCompiler>>concreteRegister: (in category 'encoding') -----
  concreteRegister: registerIndex
  	 "Map a possibly abstract register into a concrete one.  Abstract registers
  	  (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
+ 	  negative assume it is an abstract register."
- 	 negative assume it is an abstract register."
  	
  	"N.B. According to BSABI, R0-R3 are caller-save, R4-R12 are callee save.
+ 	 Note that R9 might be a special register for the implementation. In some slides
+ 	 it is refered to as sb. R10 can contain the stack limit (sl), R11 the fp. R12 is an
+ 	 intra-procedure scratch instruction pointer for link purposes. It can also be used.
+ 	 R10 is used as temporary inside a single abstract opcode implementation"
+ 	"R0-R3 are used when calling back to the interpreter. Using them would require
+ 	 saving and restoring their values, so they are omitted so far. R12 is the only
+ 	 unused register at the moment.."
- 	Note that R9 might be a special register for the implementation. In some slides it is refered to as sb. R10 can contain the stack limit (sl), R11 the fp. R12 is an intra-procedure scratch instruction pointer for link purposes. It can also be used.
- 	R10 is used as temporary inside a single abstract opcode implementation"
- 	"R0-R3 are used when calling back to the interpreter. Using them would require saving and restoring their values, so they are omitted so far. R12 is the only unused register at the moment.."
  	^registerIndex
  		caseOf: {
  			[TempReg]				-> [R7].
  			[ClassReg]				-> [R8].
  			[ReceiverResultReg]	-> [R9].
  			[SendNumArgsReg]		-> [R6].
  			[SPReg]					-> [SP].
  			[FPReg]					-> [R11].
  			[Arg0Reg]				-> [R4].
  			[Arg1Reg]				-> [R5].
+ 			[LinkReg]				-> [LR].
+ 			[PCReg]					-> [PC] }
- 			[LinkReg]				-> [LR]. }
  		otherwise:
  			[self assert: (registerIndex between: R0 and: PC).
  			 registerIndex]!

Item was added:
+ ----- Method: CogARMCompiler>>hasPCRegister (in category 'testing') -----
+ hasPCRegister
+ 	"Answer if the processor has a generally addressable pc register, which ARM does."
+ 	^true!

Item was added:
+ ----- Method: CogAbstractInstruction>>hasPCRegister (in category 'testing') -----
+ hasPCRegister
+ 	"Answer if the processor has a generally addressable pc register, such as the ARM.
+ 	 On such processors we can execute jumping to pop top of stack by popping into
+ 	 the pc register.  Note that this is not a generic RISC feature.  The PowerPC does not
+ 	 allow one to pop into the pc for example.  So by default, answer false."
+ 	^false!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	self assert: cogMethod cmType ~= CMFree.
  	self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader]
  			ifFalse:
  				[self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject.
  				 self cppIf: NewspeakVM ifTrue:
  					[self removeFromUnpairedMethodList: cogMethod]].
+ 		 cogit maybeFreeCountersOf: cogMethod.
  		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod.
  		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits on
  	 a 32-bit architecture or 64-bits on a 64-bit architecture.  
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a quick constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word with an absolute address
  		Ab		- memory byte with an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		XbrR	- memory word whose address is r * byte size away from an address in a register
  		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
  		XwrR	- memory word whose address is r * word size away from an address in a register
  		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	 XowrR scaled index addressing mode since it requires 4 operands.
  
  	Note that there are no generic division instructions defined, but a processor may define some."
  
  	| opcodeNames refs |
  	FPReg := -1.
  	SPReg := -2.
  	ReceiverResultReg := GPRegMax := -3.
  	TempReg := -4.
  	ClassReg := -5.
  	SendNumArgsReg := -6.
  	Arg0Reg := -7.
  	Arg1Reg := GPRegMin := -8.
  
  	DPFPReg0 := -9.
  	DPFPReg1 := -10.
  	DPFPReg2 := -11.
  	DPFPReg3 := -12.
  	DPFPReg4 := -13.
  	DPFPReg5 := -14.
  	DPFPReg6 := -15.
  	DPFPReg7 := -16.
  	
  	LinkReg := -17.
+ 	PCReg := -18.
  
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						AlignmentNops
  						FillBytesFrom	"output operand 0's worth of bytes from the address in operand 1"
  						Fill8				"output a byte's worth of bytes with operand 0"
  						Fill16			"output two byte's worth of bytes with operand 0"
  						Fill32			"output four byte's worth of bytes with operand 0"
  						FillFromWord	"output BytesPerWord's worth of bytes with operand 0 + operand 1"
  						Nop
  
  						"Control"
  						Call
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  
  						"N.B.  Jumps are contiguous.  Long jumps are contigiuous within them.  See FirstJump et al below"
  						JumpLong
  						JumpLongZero		"a.k.a. JumpLongEqual"
  						JumpLongNonZero	"a.k.a. JumpLongNotEqual"
  						Jump
  						JumpZero			"a.k.a. JumpEqual"
  						JumpNonZero		"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
  						MoveRdRd MoveM64rRd MoveRdM64r
  						PopR PushR PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR MulRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR XorCqR MulCqR
  						CmpCwR AddCwR SubCwR AndCwR OrCwR XorCwR MulCwR
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpLong.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

Item was changed:
  ----- Method: CogRTLOpcodes class>>nameForRegister: (in category 'debug printing') -----
  nameForRegister: reg "<Integer>"
  	^#(Arg0Reg Arg1Reg ClassReg FPReg ReceiverResultReg SPReg SendNumArgsReg TempReg
+ 		DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 LinkReg PCReg)
- 		DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 LinkReg)
  			detect: [:sym| (classPool at: sym) = reg]!

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent usesMethodClass primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxMethodBefore maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent usesMethodClass primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxMethodBefore maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
  	classVariableNames: 'AltBlockCreationBytecodeSize AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass ShouldNotJIT UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/13/2013 15:37' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventuakly teh total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'dynSuperEntry' 'dynSuperEntryAlignment' 'dynamicSuperSendTrampolines'
  			'ceImplicitReceiverTrampoline' 'ceExplicitReceiverTrampoline' 'cmDynSuperEntryOffset') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"cogmethod.h"';
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	aCCodeGenerator
  		var: #ceGetSP
  			declareC: 'unsigned long (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
+ 		var: #ceCallCogCodePopReceiverReg
+ 			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
+ 		var: #realCECallCogCodePopReceiverReg
+ 			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
+ 		var: #ceCallCogCodePopReceiverAndClassRegs
+ 			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
+ 		var: #realCECallCogCodePopReceiverAndClassRegs
+ 			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
- 		var: #ceEnterCogCodePopReceiverAndClassRegs
- 			declareC: 'void (*ceEnterCogCodePopReceiverAndClassRegs)(void)';
- 		var: #realCEEnterCogCodePopReceiverAndClassRegs
- 			declareC: 'void (*realCEEnterCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(unsigned long from, unsigned long to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static unsigned long (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'unsigned long (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *, void *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel';
  		var: #primInvokeLabel type: #'AbstractInstruction *'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss sendMissCall entry noCheckEntry dynSuperEntry
  					mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #annotations type: #'InstructionAnnotation *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #sendTrampolines
  			declareC: 'sqInt sendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static sqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #CFramePointer type: #'void *';
  		declareVar: #CStackPointer type: #'void *';
  		declareVar: #minValidCallAddress type: #'unsigned long';
  		declareVar: #debugPrimCallStackOffset type: #'unsigned long'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator);
  			var: #primitiveGeneratorTable
  				declareC: 'PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
  							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was added:
+ ----- Method: Cogit>>callCogCodePopReceiver (in category 'debugging') -----
+ callCogCodePopReceiver
+ 	"This is a static version of ceCallCogCodePopReceiverReg
+ 	 for break-pointing when debugging in C."
+ 	<api>
+ 	<inline: false>
+ 	"This exists only for break-pointing."
+ 	self cCode: [self realCECallCogCodePopReceiverReg]
+ 		inSmalltalk: [self ceCallCogCodePopReceiverReg].
+ 	"(and this exists only to reference Debug)"
+ 	Debug ifFalse: [self error: 'what??']!

Item was added:
+ ----- Method: Cogit>>callCogCodePopReceiverAndClassRegs (in category 'debugging') -----
+ callCogCodePopReceiverAndClassRegs
+ 	"This is a static version of ceCallCogCodePopReceiverAndClassRegs
+ 	 for break-pointing when debugging in C."
+ 	<api>
+ 	<inline: false>
+ 	"This exists only for break-pointing."
+ 	self cCode: [self realCECallCogCodePopReceiverAndClassRegs]
+ 		inSmalltalk: [self ceCallCogCodePopReceiverAndClassRegs]!

Item was added:
+ ----- Method: Cogit>>ceCallCogCodePopReceiverAndClassRegs (in category 'simulation only') -----
+ ceCallCogCodePopReceiverAndClassRegs
+ 	<api: 'extern void (*ceCallCogCodePopReceiverAndClassRegs)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceCallCogCodePopReceiverAndClassRegs numArgs: 2!

Item was added:
+ ----- Method: Cogit>>ceCallCogCodePopReceiverReg (in category 'simulation only') -----
+ ceCallCogCodePopReceiverReg
+ 	<api: 'extern void (*ceCallCogCodePopReceiverReg)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceCallCogCodePopReceiverReg numArgs: 1!

Item was removed:
- ----- Method: Cogit>>ceEnterCogCodePopReceiverAndClassRegs (in category 'simulation only') -----
- ceEnterCogCodePopReceiverAndClassRegs
- 	<api: 'extern void (*ceEnterCogCodePopReceiverAndClassRegs)()'>
- 	<doNotGenerate>
- 	self simulateEnilopmart: ceEnterCogCodePopReceiverAndClassRegs numArgs: 2!

Item was removed:
- ----- Method: Cogit>>enterCogCodePopReceiverAndClassRegs (in category 'debugging') -----
- enterCogCodePopReceiverAndClassRegs
- 	"This is a static version of ceEnterCogCodePopReceiverAndClassRegs
- 	 for break-pointing when debugging in C."
- 	<api>
- 	<inline: false>
- 	"This exists only for break-pointing."
- 	self cCode: [self realCEEnterCogCodePopReceiverAndClassRegs]
- 		inSmalltalk: [self ceEnterCogCodePopReceiverAndClassRegs]!

Item was added:
+ ----- Method: Cogit>>genCallEnilopmartFor:and:and:called: (in category 'initialization') -----
+ genCallEnilopmartFor: regArg1 and: regArg2 and: regArg3 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.  This version is for entering code as if from a call.  The desired
+ 	 arguments and entry-point are pushed on a stackPage's stack, and beneath
+ 	 them is the call's return address.  The enilopmart pops off the values to be
+ 	 loaded into registers, and on CISCs then executes a return instruction to pop
+ 	 off the entry-point and jump to it.  On RISCs the enilopmart pops off the values
+ 	 to be loaded into registers, pops the entry-point into a scratch register, pops
+ 	 the return address into the LinkReg and then jumps to the entry point.
+ 
+ 						BEFORE				AFTER			(stacks grow down)
+ 						whatever			stackPointer ->	whatever
+ 						call return pc
+ 						target address =>
+ 						reg1val				reg1 = reg1val, etc
+ 						reg2val				LinkReg = call return pc
+ 		stackPointer ->	reg3val				pc = target address
+ 
+ 	 C.F. genEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genCallEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, char *trampolineName))(void)'>
+ 	| size endAddress enilopmart |
+ 	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
+ 	self PopR: regArg3.
+ 	self PopR: regArg2.
+ 	self PopR: regArg1.
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			[self PopR: TempReg.
+ 			 self PopR: LinkReg.
+ 			 self JumpR: TempReg]
+ 		ifFalse:
+ 			[self RetN: 0].
+ 	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 added:
+ ----- Method: Cogit>>genCallEnilopmartFor:and:called: (in category 'initialization') -----
+ genCallEnilopmartFor: regArg1 and: regArg2 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.  This version is for entering code as if from a call.  The desired
+ 	 arguments and entry-point are pushed on a stackPage's stack, and beneath
+ 	 them is the call's return address.  The enilopmart pops off the values to be
+ 	 loaded into registers, and on CISCs then executes a return instruction to pop
+ 	 off the entry-point and jump to it.  On RISCs the enilopmart pops off the values
+ 	 to be loaded into registers, pops the entry-point into a scratch register, pops
+ 	 the return address into the LinkReg and then jumps to the entry point.
+ 
+ 						BEFORE				AFTER			(stacks grow down)
+ 						whatever			stackPointer ->	whatever
+ 						call return pc
+ 						target address =>	reg1 = reg1val, etc
+ 						reg1val				LinkReg = call return pc
+ 		stackPointer ->	reg2val				pc = target address
+ 
+ 	 C.F. genEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genCallEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
+ 	| size endAddress enilopmart |
+ 	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
+ 	self PopR: regArg2.
+ 	self PopR: regArg1.
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			[self PopR: TempReg.
+ 			 self PopR: LinkReg.
+ 			 self JumpR: TempReg]
+ 		ifFalse:
+ 			[self RetN: 0].
+ 	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 added:
+ ----- Method: Cogit>>genCallEnilopmartFor:called: (in category 'initialization') -----
+ genCallEnilopmartFor: regArg1 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.  This version is for entering code as if from a call.  The desired
+ 	 arguments and entry-point are pushed on a stackPage's stack, and beneath
+ 	 them is the call's return address.  The enilopmart pops off the values to be
+ 	 loaded into registers, and on CISCs then executes a return instruction to pop
+ 	 off the entry-point and jump to it.  On RISCs the enilopmart pops off the values
+ 	 to be loaded into registers, pops the entry-point into a scratch register, pops
+ 	 the return address into the LinkReg and then jumps to the entry point.
+ 
+ 						BEFORE				AFTER			(stacks grow down)
+ 						whatever			stackPointer ->	whatever
+ 						call return pc		reg1 = reg1val
+ 						target address =>	LinkReg = call return pc
+ 		stackPointer ->	reg1val				pc = target address
+ 
+ 	 C.F. genEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genCallEnilopmartForandandcalled(sqInt regArg1, char *trampolineName))(void)'>
+ 	| size endAddress enilopmart |
+ 	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
+ 	self PopR: regArg1.
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			[self PopR: TempReg.
+ 			 self PopR: LinkReg.
+ 			 self JumpR: TempReg]
+ 		ifFalse:
+ 			[self RetN: 0].
+ 	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>>genEnilopmartFor:and:and:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 and: regArg3 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
+ 
+ 	C.F. genCallEnilopmartFor:and:and:called:"
- 	 then executes a return instruction to pop off the entry-point and jump to it."
  	<returnTypeC: 'void (*genEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg3.
  	self PopR: regArg2.
  	self PopR: regArg1.
+ 	backEnd hasLinkRegister
+ 		ifTrue: [backEnd hasPCRegister
+ 					ifTrue: [self PopR: LinkReg]
+ 					ifFalse: [self PopR: LinkReg; RetN: 0]]
+ 		ifFalse: [self RetN: 0].
- 	backEnd hasLinkRegister ifTrue:
- 		[self PopR: LinkReg].
- 	self RetN: 0.
  	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>>genEnilopmartFor:and:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 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
+ 		stackPointer ->	reg2val
+ 
+ 	C.F. genCallEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
- 	 then executes a return instruction to pop off the entry-point and jump to it."
- 	<returnTypeC: 'void (*genEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg2.
  	self PopR: regArg1.
+ 	backEnd hasLinkRegister
+ 		ifTrue: [backEnd hasPCRegister
+ 					ifTrue: [self PopR: LinkReg]
+ 					ifFalse: [self PopR: LinkReg; RetN: 0]]
+ 		ifFalse: [self RetN: 0].
- 	backEnd hasLinkRegister ifTrue:
- 		[self PopR: LinkReg].
- 	self RetN: 0.
  	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>>genEnilopmartFor:called: (in category 'initialization') -----
+ genEnilopmartFor: regArg1 called: trampolineName
- genEnilopmartFor: regArg 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
+ 		stackPointer ->	reg1val				pc = target address
+ 
+ 	C.F. genCallEnilopmartFor:and:and:called:"
+ 	<returnTypeC: 'void (*genEnilopmartForandandcalled(sqInt regArg1, char *trampolineName))(void)'>
- 	 then executes a return instruction to pop off the entry-point and jump to it."
- 	<returnTypeC: 'void (*genEnilopmartForcalled(sqInt regArg, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
+ 	self PopR: regArg1.
+ 	backEnd hasLinkRegister
+ 		ifTrue: [backEnd hasPCRegister
+ 					ifTrue: [self PopR: LinkReg]
+ 					ifFalse: [self PopR: LinkReg; RetN: 0]]
+ 		ifFalse: [self RetN: 0].
- 	self PopR: regArg.
- 	backEnd hasLinkRegister ifTrue:
- 		[self PopR: LinkReg].
- 	self RetN: 0.
  	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>>generateEnilopmarts (in category 'initialization') -----
  generateEnilopmarts
  	"Enilopmarts transfer control from C into machine code (backwards trampolines)."
  	self cppIf: Debug
  		ifTrue:
  			[realCEEnterCogCodePopReceiverReg :=
  				self genEnilopmartFor: ReceiverResultReg
  					called: 'realCEEnterCogCodePopReceiverReg'.
  			 ceEnterCogCodePopReceiverReg := #enterCogCodePopReceiver.
+ 			 realCECallCogCodePopReceiverReg :=
+ 				self genCallEnilopmartFor: ReceiverResultReg
+ 					called: 'realCEEnterCogCodePopReceiverReg'.
+ 			 ceEnterCogCodePopReceiverReg := #callCogCodePopReceiver.
+ 			 realCECallCogCodePopReceiverAndClassRegs :=
+ 				self genCallEnilopmartFor: ReceiverResultReg
- 			 realCEEnterCogCodePopReceiverAndClassRegs :=
- 				self genEnilopmartFor: ReceiverResultReg
  					and: ClassReg
+ 					called: 'realCECallCogCodePopReceiverAndClassRegs'.
+ 			 ceCallCogCodePopReceiverAndClassRegs := #callCogCodePopReceiverAndClassRegs]
- 					called: 'realCEEnterCogCodePopReceiverAndClassRegs'.
- 			 ceEnterCogCodePopReceiverAndClassRegs := #enterCogCodePopReceiverAndClassRegs]
  		ifFalse:
  			[ceEnterCogCodePopReceiverReg := self genEnilopmartFor: ReceiverResultReg
  				called: 'ceEnterCogCodePopReceiverReg'.
+ 			 ceCallCogCodePopReceiverReg := self genCallEnilopmartFor: ReceiverResultReg
+ 				called: 'ceCallCogCodePopReceiverReg'.
+ 			 ceCallCogCodePopReceiverAndClassRegs :=
+ 				self genCallEnilopmartFor: ReceiverResultReg
- 			 ceEnterCogCodePopReceiverAndClassRegs :=
- 				self genEnilopmartFor: ReceiverResultReg
  					and: ClassReg
+ 					called: 'ceCallCogCodePopReceiverAndClassRegs'].
- 					called: 'ceEnterCogCodePopReceiverAndClassRegs'].
  
  	self genPrimReturnEnterCogCodeEnilopmart: false.
  	cePrimReturnEnterCogCode := methodZoneBase.
  	self outputInstructionsForGeneratedRuntimeAt: cePrimReturnEnterCogCode.
  	self recordGeneratedRunTime: 'cePrimReturnEnterCogCode' address: cePrimReturnEnterCogCode.
  
  	self genPrimReturnEnterCogCodeEnilopmart: true.
  	cePrimReturnEnterCogCodeProfiling := methodZoneBase.
  	self outputInstructionsForGeneratedRuntimeAt: cePrimReturnEnterCogCodeProfiling.
  	self recordGeneratedRunTime: 'cePrimReturnEnterCogCodeProfiling' address: cePrimReturnEnterCogCodeProfiling!

Item was added:
+ ----- Method: Cogit>>maybeFreeCountersOf: (in category 'compaction') -----
+ maybeFreeCountersOf: aCogMethod
+ 	"Sista allocates counters out-of-line that need to be freed later on.
+ 	 This is the hook Sista uses.  By default do nothing."
+ 	<inline: true>!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>maybeFreeCountersOf: (in category 'compaction') -----
+ maybeFreeCountersOf: aCogMethod
+ 	"Free any counters in the method."
+ 	<inline: true>
+ 	self shouldBeImplemented!

Item was changed:
  SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
+ 	instanceVariableNames: 'prevBCDescriptor isPushNilFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks debugBytecodePointers realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode'
- 	instanceVariableNames: 'prevBCDescriptor isPushNilFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC debugStackPointers debugFixupBreaks debugBytecodePointers realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs deadCode'
  	classVariableNames: ''
  	poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'isPushNilFunction pushNilSizeFunction'!
  
  !StackToRegisterMappingCogit commentStamp: 'eem 12/19/2010 18:12' prior: 0!
  StackToRegisterMappingCogit is an optimizing code generator that eliminates a lot of stack operations and inlines some special selector arithmetic.  It does so by a simple stack-to-register mapping scheme based on deferring the generation of code to produce operands until operand-consuming operations.  The operations that consume operands are sends, stores and returns.
  
  See methods in the class-side documentation protocol for more detail.
  
  Instance Variables
  	callerSavedRegMask:							<Integer>
  	ceEnter0ArgsPIC:								<Integer>
  	ceEnter1ArgsPIC:								<Integer>
  	ceEnter2ArgsPIC:								<Integer>
  	ceEnterCogCodePopReceiverArg0Regs:		<Integer>
  	ceEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	debugBytecodePointers:						<Set of Integer>
  	debugFixupBreaks:								<Set of Integer>
  	debugStackPointers:							<CArrayAccessor of (Integer|nil)>
  	methodAbortTrampolines:						<CArrayAccessor of Integer>
  	methodOrBlockNumTemps:						<Integer>
  	optStatus:										<Integer>
  	picAbortTrampolines:							<CArrayAccessor of Integer>
  	picMissTrampolines:							<CArrayAccessor of Integer>
  	realCEEnterCogCodePopReceiverArg0Regs:		<Integer>
  	realCEEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	regArgsHaveBeenPushed:						<Boolean>
  	simSelf:											<CogSimStackEntry>
  	simSpillBase:									<Integer>
  	simStack:										<CArrayAccessor of CogSimStackEntry>
  	simStackPtr:									<Integer>
  	traceSimStack:									<Integer>
  
  callerSavedRegMask
  	- the bitmask of the ABI's caller-saved registers
  
  ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
  	- the trampoline for entering an N-arg PIC
  
  ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
  	- teh trampoline for entering a method with N register args
  	
  debugBytecodePointers
  	- a Set of bytecode pcs for setting breakpoints (simulation only)
  
  debugFixupBreaks
  	- a Set of fixup indices for setting breakpoints (simulation only)
  
  debugStackPointers
  	- an Array of stack depths for each bytecode for code verification
  
  methodAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  methodOrBlockNumTemps
  	- the number of method or block temps (including args) in the current compilation unit (method or block)
  
  optStatus
  	- the variable used to track the status of ReceiverResultReg for avoiding reloading that register with self between adjacent inst var accesses
  
  picAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  picMissTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs
  	- the real trampolines for ebtering machine code with N reg args when in the Debug regime
  
  regArgsHaveBeenPushed
  	- whether the register args have been pushed before frame build (e.g. when an interpreter primitive is called)
  
  simSelf
  	- the simulation stack entry representing self in the current compilation unit
  
  simSpillBase
  	- the variable tracking how much of the simulation stack has been spilled to the real stack
  
  simStack
  	- the simulation stack itself
  
  simStackPtr
  	- the pointer to the top of the simulation stack
  !
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'isPushNilFunction pushNilSizeFunction'!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCodeGen
  	aCodeGen
  		var: #methodAbortTrampolines
  			declareC: 'sqInt methodAbortTrampolines[4]';
  		var: #picAbortTrampolines
  			declareC: 'sqInt picAbortTrampolines[4]';
  		var: #picMissTrampolines
  			declareC: 'sqInt picMissTrampolines[4]';
+ 		var: 'ceCall0ArgsPIC'
+ 			declareC: 'void (*ceCall0ArgsPIC)(void)';
+ 		var: 'ceCall1ArgsPIC'
+ 			declareC: 'void (*ceCall1ArgsPIC)(void)';
+ 		var: 'ceCall2ArgsPIC'
+ 			declareC: 'void (*ceCall2ArgsPIC)(void)';
+ 		var: #ceCallCogCodePopReceiverArg0Regs
+ 			declareC: 'void (*ceCallCogCodePopReceiverArg0Regs)(void)';
+ 		var: #realCECallCogCodePopReceiverArg0Regs
+ 			declareC: 'void (*realCECallCogCodePopReceiverArg0Regs)(void)';
+ 		var: #ceCallCogCodePopReceiverArg1Arg0Regs
+ 			declareC: 'void (*ceCallCogCodePopReceiverArg1Arg0Regs)(void)';
+ 		var: #realCECallCogCodePopReceiverArg1Arg0Regs
+ 			declareC: 'void (*realCECallCogCodePopReceiverArg1Arg0Regs)(void)';
- 		var: 'ceEnter0ArgsPIC'
- 			declareC: 'void (*ceEnter0ArgsPIC)(void)';
- 		var: 'ceEnter1ArgsPIC'
- 			declareC: 'void (*ceEnter1ArgsPIC)(void)';
- 		var: 'ceEnter2ArgsPIC'
- 			declareC: 'void (*ceEnter2ArgsPIC)(void)';
- 		var: #ceEnterCogCodePopReceiverArg0Regs
- 			declareC: 'void (*ceEnterCogCodePopReceiverArg0Regs)(void)';
- 		var: #realCEEnterCogCodePopReceiverArg0Regs
- 			declareC: 'void (*realCEEnterCogCodePopReceiverArg0Regs)(void)';
- 		var: #ceEnterCogCodePopReceiverArg1Arg0Regs
- 			declareC: 'void (*ceEnterCogCodePopReceiverArg1Arg0Regs)(void)';
- 		var: #realCEEnterCogCodePopReceiverArg1Arg0Regs
- 			declareC: 'void (*realCEEnterCogCodePopReceiverArg1Arg0Regs)(void)';
  		var: 'simStack'
  			declareC: 'CogSimStackEntry simStack[', ((CoInterpreter bindingOf: #LargeContextSize) value * 5 / 4 // BytesPerWord) asString, ']';
  		var: 'simSelf'
  			type: #CogSimStackEntry;
  		var: #optStatus
  			type: #CogSSOptStatus;
  		var: 'prevBCDescriptor'
  			type: #'BytecodeDescriptor *'.
  
  	self isPushNilFunction ifNotNil:
  		[aCodeGen
  			var: 'isPushNilFunction'
  				declareC: 'sqInt (* const isPushNilFunction)(struct _BytecodeDescriptor *,sqInt,sqInt,sqInt) = ', (aCodeGen cFunctionNameFor: self isPushNilFunction);
  			var: 'pushNilSizeFunction'
  				declareC: 'sqInt (* const pushNilSizeFunction)(sqInt) = ', (aCodeGen cFunctionNameFor: self pushNilSizeFunction)].
  
  	aCodeGen
  		addSelectorTranslation: #register to: (aCodeGen cFunctionNameFor: 'registerr');
  		addSelectorTranslation: #register: to: (aCodeGen cFunctionNameFor: 'registerr:')!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>callCogCodePopReceiverArg0Regs (in category 'debugging') -----
+ callCogCodePopReceiverArg0Regs
+ 	"This is a static version of ceCallCogCodePopReceiverArg0Regs
+ 	 for break-pointing when debugging in C."
+ 	<api>
+ 	<inline: false>
+ 	"This exists only for break-pointing."
+ 	self cCode: [self realCECallCogCodePopReceiverArg0Regs]
+ 		inSmalltalk: [self ceCallCogCodePopReceiverArg0Regs]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>callCogCodePopReceiverArg1Arg0Regs (in category 'debugging') -----
+ callCogCodePopReceiverArg1Arg0Regs
+ 	"This is a static version of ceCallCogCodePopReceiverArg1Arg0Regs
+ 	 for break-pointing when debugging in C."
+ 	<api>
+ 	<inline: false>
+ 	"This exists only for break-pointing."
+ 	self cCode: [self realCECallCogCodePopReceiverArg1Arg0Regs]
+ 		inSmalltalk: [self ceCallCogCodePopReceiverArg1Arg0Regs]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>ceCall0ArgsPIC (in category 'simulation only') -----
+ ceCall0ArgsPIC
+ 	<api: 'extern void (*ceCall0ArgsPIC)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceCall0ArgsPIC numArgs: 1!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>ceCall1ArgsPIC (in category 'simulation only') -----
+ ceCall1ArgsPIC
+ 	<api: 'extern void (*ceCall1ArgsPIC)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceCall1ArgsPIC numArgs: 1!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>ceCall2ArgsPIC (in category 'simulation only') -----
+ ceCall2ArgsPIC
+ 	<api: 'extern void (*ceCall2ArgsPIC)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceCall2ArgsPIC numArgs: 1!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>ceCallCogCodePopReceiverArg0Regs (in category 'simulation only') -----
+ ceCallCogCodePopReceiverArg0Regs
+ 	<api: 'extern void (*ceCallCogCodePopReceiverArg0Regs)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceCallCogCodePopReceiverArg0Regs numArgs: 2!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>ceCallCogCodePopReceiverArg1Arg0Regs (in category 'simulation only') -----
+ ceCallCogCodePopReceiverArg1Arg0Regs
+ 	<api: 'extern void (*ceCallCogCodePopReceiverArg1Arg0Regs)()'>
+ 	<doNotGenerate>
+ 	self simulateEnilopmart: ceCallCogCodePopReceiverArg1Arg0Regs numArgs: 3!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>ceEnter0ArgsPIC (in category 'simulation only') -----
- ceEnter0ArgsPIC
- 	<api: 'extern void (*ceEnter0ArgsPIC)()'>
- 	<doNotGenerate>
- 	self simulateEnilopmart: ceEnter0ArgsPIC numArgs: 1!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>ceEnter1ArgsPIC (in category 'simulation only') -----
- ceEnter1ArgsPIC
- 	<api: 'extern void (*ceEnter1ArgsPIC)()'>
- 	<doNotGenerate>
- 	self simulateEnilopmart: ceEnter1ArgsPIC numArgs: 1!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>ceEnter2ArgsPIC (in category 'simulation only') -----
- ceEnter2ArgsPIC
- 	<api: 'extern void (*ceEnter2ArgsPIC)()'>
- 	<doNotGenerate>
- 	self simulateEnilopmart: ceEnter2ArgsPIC numArgs: 1!

Item was added:
+ ----- 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 |
+ 	opcodeIndex := 0.
+ 	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' numArgs: numArgs) address: enilopmart.
+ 	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genEnterPICEnilopmartNumArgs: (in category 'initialization') -----
- genEnterPICEnilopmartNumArgs: numArgs
- 	"Generate special versions of the ceEnterCogCodePopReceiverAndClassRegs
- 	 enilopmart that also pop register args from the stack to undo the pushing of
- 	 register args in the abort/miss trampolines."
- 	<returnTypeC: 'void (*genEnterPICEnilopmartNumArgs(sqInt numArgs))(void)'>
- 	| size endAddress enilopmart |
- 	opcodeIndex := 0.
- 	backEnd genLoadStackPointers.
- 	self PopR: ClassReg. "cacheTag"
- 	self PopR: TempReg. "entry-point"
- 	self PopR: SendNumArgsReg. "retpc"
- 	numArgs > 0 ifTrue:
- 		[numArgs > 1 ifTrue:
- 			[self PopR: Arg1Reg.
- 			 self assert: self numRegArgs = 2].
- 		 self PopR: Arg0Reg].
- 	self PopR: ReceiverResultReg.
- 	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: 'ceEnterPIC' numArgs: numArgs) address: enilopmart.
- 	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateEnilopmarts (in category 'initialization') -----
  generateEnilopmarts
  	"Enilopmarts transfer control from C into machine code (backwards trampolines).
  	 Override to add version for generic and PIC-specific entry with reg args."
  	super generateEnilopmarts.
  
  	self cppIf: Debug
  		ifTrue:
+ 			[realCECallCogCodePopReceiverArg0Regs :=
- 			[realCEEnterCogCodePopReceiverArg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg
+ 					called: 'realCECallCogCodePopReceiverArg0Regs'.
+ 			 ceCallCogCodePopReceiverArg0Regs := #callCogCodePopReceiverArg0Regs.
+ 			 realCECallCogCodePopReceiverArg1Arg0Regs :=
- 					called: 'realCEEnterCogCodePopReceiverArg0Regs'.
- 			 ceEnterCogCodePopReceiverArg0Regs := #enterCogCodePopReceiverArg0Regs.
- 			 realCEEnterCogCodePopReceiverArg1Arg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg							
  					and: Arg1Reg
+ 					called: 'realCECallCogCodePopReceiverArg1Arg0Regs'.
+ 			 ceCallCogCodePopReceiverArg1Arg0Regs := #callCogCodePopReceiverArg1Arg0Regs]
- 					called: 'realCEEnterCogCodePopReceiverArg1Arg0Regs'.
- 			 ceEnterCogCodePopReceiverArg1Arg0Regs := #enterCogCodePopReceiverArg1Arg0Regs]
  		ifFalse:
+ 			[ceCallCogCodePopReceiverArg0Regs :=
- 			[ceEnterCogCodePopReceiverArg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg
+ 					called: 'ceCallCogCodePopReceiverArg0Regs'.
+ 			 ceCallCogCodePopReceiverArg1Arg0Regs :=
- 					called: 'ceEnterCogCodePopReceiverArg0Regs'.
- 			 ceEnterCogCodePopReceiverArg1Arg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg							
  					and: Arg1Reg
+ 					called: 'ceCallCogCodePopReceiverArg1Arg0Regs'].
- 					called: 'ceEnterCogCodePopReceiverArg1Arg0Regs'].
  
+ 	"These are 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."
+ 	ceCall0ArgsPIC := self genCallPICEnilopmartNumArgs: 0.
- 	"These are special versions of the ceEnterCogCodePopReceiverAndClassRegs enilopmart that also
- 	 pop register argsfrom the stack to undo the pushing of register args in the abort/miss trampolines."
- 	ceEnter0ArgsPIC := self genEnterPICEnilopmartNumArgs: 0.
  	self numRegArgs >= 1 ifTrue:
+ 		[ceCall1ArgsPIC := self genCallPICEnilopmartNumArgs: 1.
- 		[ceEnter1ArgsPIC := self genEnterPICEnilopmartNumArgs: 1.
  		 self numRegArgs >= 2 ifTrue:
+ 			[ceCall2ArgsPIC := self genCallPICEnilopmartNumArgs: 2.
- 			[ceEnter2ArgsPIC := self genEnterPICEnilopmartNumArgs: 2.
  			 self assert: self numRegArgs = 2]]!



More information about the Vm-dev mailing list