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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 19 02:33:23 UTC 2015


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

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

Name: VMMaker.oscog-eem.1101
Author: eem
Time: 18 March 2015, 7:31:23.381 pm
UUID: bf76a676-94a9-440d-82bd-64304fc1d429
Ancestors: VMMaker.oscog-eem.1100

Refactor the enilopmart creation machinery so that
there is only one creation routine, adding a forCall:
parameter to differentiate enter and call
enilopmarts.  Allow nil to be passed for reg args
hence only one routine.  Make RISCTempReg one of
the global reg ids.  RECOMPILE!!

Fix block frame build for ARM.  The LinkReg must of
course be pushed.

Fix CogMethodZone>>whereIsMaybeCodeThing:
which was testing the wrong boundary.

Fix printStackCallStack for simulation, nilling localFP
when in machine code so that we know which frame
pointer is valid.

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

Item was added:
+ ----- Method: CoInterpreter>>nilLocalFP (in category 'simulation') -----
+ nilLocalFP
+ 	<doNotGenerate>
+ 	localFP := nil!

Item was changed:
  CogAbstractInstruction subclass: #CogARMCompiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'AL AddOpcode AndOpcode BICCqR BicOpcode CArg0Reg CArg1Reg CArg2Reg CArg3Reg CC CS CmpOpcode EQ GE GT HI LDMFD LE LR LS LT MI MoveOpcode NE OrOpcode PC PL R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 RsbOpcode SP STMFD SubOpcode VC VS XorOpcode'
- 	classVariableNames: 'AL AddOpcode AndOpcode BICCqR BicOpcode CArg0Reg CArg1Reg CArg2Reg CArg3Reg CC CS CmpOpcode EQ GE GT HI LDMFD LE LR LS LT MI MoveOpcode NE OrOpcode PC PL R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 RISCTempReg RsbOpcode SP STMFD SubOpcode 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 added:
+ ----- Method: CogARMCompiler>>riscTempReg (in category 'accessing') -----
+ riscTempReg
+ 	^RISCTempReg!

Item was changed:
  ----- Method: CogMethodZone>>whereIsMaybeCodeThing: (in category 'debug printing') -----
  whereIsMaybeCodeThing: anOop
  	<api>
  	<returnTypeC: 'char *'>
+ 	(self oop: anOop isGreaterThanOrEqualTo: cogit cogCodeBase andLessThan: limitAddress) ifTrue:
- 	(self oop: anOop isGreaterThanOrEqualTo: baseAddress andLessThan: limitAddress) ifTrue:
  		[(self oop: anOop isLessThan: cogit minCogMethodAddress) ifTrue:
  			[^' is in generated runtime'].
  		 (self oop: anOop isLessThan: mzFreeStart) ifTrue:
  			[^' is in generated methods'].
  		 (self oop: anOop isLessThan: youngReferrers) ifTrue:
  			[^' is in code zone'].
  		 ^' is in young referrers'].
  	^nil!

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 MoveRAb 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 RISCTempReg ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg TstCqR 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 MoveRAb 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 TstCqR 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 removed:
- ----- 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 removed:
- ----- 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 (*genCallEnilopmartForandcalled(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 removed:
- ----- 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 (*genCallEnilopmartForcalled(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 removed:
- ----- 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:"
- 	<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: PCReg]
- 					ifFalse: [self PopR: LinkReg; RetN: 0]]
- 		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>>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"
+ 	<returnTypeC: #'void (*)(void)'>
+ 	| size endAddress enilopmart |
+ 	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
+ 	regArg3 ifNotNil: [self PopR: regArg3].
+ 	regArg2 ifNotNil: [self PopR: regArg2].
+ 	self PopR: regArg1.
+ 	self genEnilopmartReturn: forCall.
+ 	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 removed:
- ----- 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 (*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: PCReg]
- 					ifFalse: [self PopR: LinkReg; RetN: 0]]
- 		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>>genEnilopmartFor:and:forCall:called: (in category 'initialization') -----
+ genEnilopmartFor: regArg1 and: regArg2 forCall: forCall called: trampolineName
+ 	<inline: true>
+ 	^self genEnilopmartFor: regArg1 and: regArg2 and: nil forCall: forCall called: trampolineName!

Item was removed:
- ----- Method: Cogit>>genEnilopmartFor:called: (in category 'initialization') -----
- genEnilopmartFor: 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.  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 (*genEnilopmartForcalled(sqInt regArg1, char *trampolineName))(void)'>
- 	| size endAddress enilopmart |
- 	opcodeIndex := 0.
- 	backEnd genLoadStackPointers.
- 	self PopR: regArg1.
- 	backEnd hasLinkRegister
- 		ifTrue: [backEnd hasPCRegister
- 					ifTrue: [self PopR: PCReg]
- 					ifFalse: [self PopR: LinkReg; RetN: 0]]
- 		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>>genEnilopmartFor:forCall:called: (in category 'initialization') -----
+ genEnilopmartFor: regArg1 forCall: forCall called: trampolineName
+ 	<inline: true>
+ 	^self genEnilopmartFor: regArg1 and: nil and: nil forCall: forCall called: trampolineName!

Item was added:
+ ----- Method: Cogit>>genEnilopmartReturn: (in category 'initialization') -----
+ genEnilopmartReturn: forCall
+ 	"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.  At the point the enilopmart enters machine code via a return instruction,
+ 	 any argument registers have been loaded with their values and the stack, if
+ 	 for call, looks like
+ 							ret pc
+ 			stackPointer ->	target address
+ 
+ 	 and if not for call, looks like
+ 							whatever
+ 			stackPointer ->	target address
+ 
+ 	 If forCall and running on a CISC, ret pc must be left on the stack.  If forCall and
+ 	 running on a RISC, ret pc must be popped into LinkReg.  In either case, target
+ 	 address must be removed from the stack and jumped/returned to."
+ 
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			[forCall
+ 				ifTrue:
+ 					[self PopR: RISCTempReg.
+ 					 self PopR: LinkReg.
+ 					 self JumpR: RISCTempReg]
+ 				ifFalse:
+ 					[backEnd hasPCRegister
+ 						ifTrue: [self PopR: PCReg]
+ 						ifFalse:
+ 							[self PopR: RISCTempReg.
+ 							 self JumpR: RISCTempReg]]]
+ 		ifFalse:
+ 			[self RetN: 0]!

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
+ 					forCall: false
  					called: 'realCEEnterCogCodePopReceiverReg'.
  			 ceEnterCogCodePopReceiverReg := #enterCogCodePopReceiver.
  			 realCECallCogCodePopReceiverReg :=
+ 				self genEnilopmartFor: ReceiverResultReg
+ 					forCall: true
- 				self genCallEnilopmartFor: ReceiverResultReg
  					called: 'realCEEnterCogCodePopReceiverReg'.
  			 ceCallCogCodePopReceiverReg := #callCogCodePopReceiver.
  			 realCECallCogCodePopReceiverAndClassRegs :=
+ 				self genEnilopmartFor: ReceiverResultReg
- 				self genCallEnilopmartFor: ReceiverResultReg
  					and: ClassReg
+ 					forCall: true
  					called: 'realCECallCogCodePopReceiverAndClassRegs'.
  			 ceCallCogCodePopReceiverAndClassRegs := #callCogCodePopReceiverAndClassRegs]
  		ifFalse:
  			[ceEnterCogCodePopReceiverReg := self genEnilopmartFor: ReceiverResultReg
+ 														forCall: false
+ 														called: 'ceEnterCogCodePopReceiverReg'.
+ 			 ceCallCogCodePopReceiverReg := self genEnilopmartFor: ReceiverResultReg
+ 													forCall: true
+ 													called: 'ceCallCogCodePopReceiverReg'.
- 				called: 'ceEnterCogCodePopReceiverReg'.
- 			 ceCallCogCodePopReceiverReg := self genCallEnilopmartFor: ReceiverResultReg
- 				called: 'ceCallCogCodePopReceiverReg'.
  			 ceCallCogCodePopReceiverAndClassRegs :=
+ 				self genEnilopmartFor: ReceiverResultReg
- 				self genCallEnilopmartFor: ReceiverResultReg
  					and: ClassReg
+ 					forCall: true
  					called: 'ceCallCogCodePopReceiverAndClassRegs'].
  
  	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 changed:
  ----- Method: Cogit>>simulateEnilopmart:numArgs: (in category 'simulation only') -----
  simulateEnilopmart: enilopmartAddress numArgs: n
  	<doNotGenerate>
  	"Enter Cog code, popping the class reg and receiver from the stack
  	 and then returning to the address beneath them.
  	 In the actual VM the enilopmart is a function pointer and so senders
  	 of this method end up calling the enilopmart to enter machine code.
  	 In simulation we either need to start simulating execution (if we're in
  	 the interpreter) or return to the simulation (if we're in the run-time
  	 called from machine code. We should also smash the register state
  	 since, being an abnormal entry, no saved registers will be restored."
  	self assert: (coInterpreter isOnRumpCStack: processor sp).
  	self assert: ((coInterpreter stackValue: n) between: guardPageSize and: methodZone freeStart - 1).
+ 	"As a convenience for stack printing, nil localFP so we know we're in machine code."
+ 	coInterpreter nilLocalFP.
  	(printInstructions or: [printRegisters]) ifTrue:
  		[coInterpreter printExternalHeadFrame].
  	processor
  		smashRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  		simulateLeafCallOf: enilopmartAddress
  		nextpc: 16rBADF00D
  		memory: coInterpreter memory.
  	"If we're already simulating in the context of machine code then
  	 this will take us back to handleCallSimulationTrap:.  Otherwise
  	 start executing machine code in the simulator."
  	(ReenterMachineCode new returnValue: #continueNoReturn) signal.
  	self simulateCogCodeAt: enilopmartAddress.
  	"We should either longjmp back to the interpreter or
  	 stay in machine code so control should not reach here."
  	self assert: false!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileBlockFrameBuild: (in category 'compile abstract instructions') -----
  compileBlockFrameBuild: blockStart
  	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		closure (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	Avoid use of SendNumArgsReg which is the flag determining whether
  	context switch is allowed on stack-overflow."
  	<var: #blockStart type: #'BlockStart *'>
  	<inline: false>
  	self annotateBytecode: self Label.
+ 	backEnd hasLinkRegister ifTrue:
+ 		[self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	"The block method field must have its MFMethodFlagIsBlockFlag bit set.
  	 We arrange this using a labelOffset.  A hack, but it works."
  	blockStart fakeHeader
  		addDependent: (self annotateAbsolutePCRef:
  			(self PushCw: blockStart fakeHeader asInteger)); "method"
  		setLabelOffset: MFMethodFlagIsBlockFlag.
  	self annotate: (self PushCw: objectMemory nilObject) "context"
  		objRef: objectMemory nilObject.
  	"fetch home receiver from outer context. closure is on stack and initially in ReceiverResultReg"
  	objectRepresentation
  		genLoadSlot: ClosureOuterContextIndex
  			sourceReg: ReceiverResultReg
  				destReg: TempReg;
  		genLoadSlot: ReceiverIndex
  			sourceReg: TempReg
  				destReg: ClassReg.
  	self PushR: ClassReg. "home receiver"
  	"Push copied values; bytecode initializes temporaries"
  	0 to: blockStart numCopied - 1 do:
  		[:i|
  		objectRepresentation
  			genLoadSlot: i + ClosureFirstCopiedValueIndex
  			sourceReg: ReceiverResultReg
  			destReg: TempReg.
  		self PushR: TempReg].
  	self MoveR: ClassReg R: ReceiverResultReg.
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	self JumpBelow: stackOverflowCall.
  	blockStart stackCheckLabel: (self annotateBytecode: self Label)!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>longAt:put: (in category 'memory access') -----
  longAt: byteAddress put: a32BitValue
  	"Note: Adjusted for Smalltalk's 1-based array indexing."
+ 	"(byteAddress = 16r101348 and: [a32BitValue = 16r53]) ifTrue:
- 	"(byteAddress = 16r32F600 and: [a32BitValue = 16rB31E18]) ifTrue:
  		[self halt]."
  	byteAddress \\ 4 ~= 0 ifTrue: [self unalignedAccessError].
  	^memory at: byteAddress // 4 + 1 put: a32BitValue!

Item was changed:
  ----- Method: StackInterpreter>>printStackCallStack (in category 'debug printing') -----
  printStackCallStack
  	<doNotGenerate>
+ 	self printStackCallStackOf: (localFP ifNil: [framePointer])!
- 	self printStackCallStackOf: localFP!

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 :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg
+ 					forCall: true
  					called: 'realCECallCogCodePopReceiverArg0Regs'.
  			 ceCallCogCodePopReceiverArg0Regs := #callCogCodePopReceiverArg0Regs.
  			 realCECallCogCodePopReceiverArg1Arg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
+ 					and: Arg0Reg
- 					and: Arg0Reg							
  					and: Arg1Reg
+ 					forCall: true
  					called: 'realCECallCogCodePopReceiverArg1Arg0Regs'.
  			 ceCallCogCodePopReceiverArg1Arg0Regs := #callCogCodePopReceiverArg1Arg0Regs]
  		ifFalse:
  			[ceCallCogCodePopReceiverArg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg
+ 					forCall: true
  					called: 'ceCallCogCodePopReceiverArg0Regs'.
  			 ceCallCogCodePopReceiverArg1Arg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
+ 					and: Arg0Reg
- 					and: Arg0Reg							
  					and: Arg1Reg
+ 					forCall: true
  					called: 'ceCallCogCodePopReceiverArg1Arg0Regs'].
  
  	"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.
  	self numRegArgs >= 1 ifTrue:
  		[ceCall1ArgsPIC := self genCallPICEnilopmartNumArgs: 1.
  		 self numRegArgs >= 2 ifTrue:
  			[ceCall2ArgsPIC := self genCallPICEnilopmartNumArgs: 2.
  			 self assert: self numRegArgs = 2]]!



More information about the Vm-dev mailing list