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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 14 00:59:29 UTC 2022


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

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

Name: VMMaker.oscog-eem.3138
Author: eem
Time: 13 January 2022, 4:59:18.515788 pm
UUID: 2fdd9be0-6469-4273-85a4-880cf37b04d7
Ancestors: VMMaker.oscog-eem.3137

Cog:
Fix a slip in genPrimReturnEnterCogCodeEnilopmart:.  The call to ceTakeProfileSample: should take nil as its argument; the old code passed TempReg (!!). Relatedly, better comment all users/implementors of the genMarshallNArgs:arg:arg:arg:arg: trampolineArgConstant: & trampolineArgValue: hack.
Fix varying inferrence of the type of Spur's numPointerSlotsOf: by defining the retrn type of numPointerSlotsOf:format: as usqInt.

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

Item was changed:
  ----- Method: CogARMCompiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
+ 	 The encoding for constants is defined by trampolineArgConstant: & trampolineArgValue:.
+ 	 Pass a constant as the result of trampolineArgConstant:.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to."
  	<inline: true>
  	numArgs = 0 ifTrue: [^self].
  	"Avoid arg regs being overwritten before they are read."
  	numArgs > 1 ifTrue:
  		[((cogit isTrampolineArgConstant: regOrConst1) not
  		   and: [regOrConst1 = CArg0Reg]) ifTrue:
  			[cogit MoveR: regOrConst1 R: Extra0Reg.
  			 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: Extra0Reg arg: regOrConst2 arg: regOrConst3].
  		 numArgs > 2 ifTrue:
  			[((cogit isTrampolineArgConstant: regOrConst2) not
  			   and: [regOrConst2 = CArg0Reg or: [regOrConst2 = CArg1Reg]]) ifTrue:
  				[cogit MoveR: regOrConst2 R: Extra1Reg.
  				 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: Extra1Reg arg: regOrConst3].
  			 numArgs > 3 ifTrue:
  				[((cogit isTrampolineArgConstant: regOrConst3) not
  				   and: [regOrConst3 = CArg0Reg or: [regOrConst3 = CArg1Reg or: [regOrConst3 = CArg2Reg]]]) ifTrue:
  					[cogit MoveR: regOrConst3 R: Extra2Reg.
  					 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: Extra2Reg]]]].
  	(cogit isTrampolineArgConstant: regOrConst0)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: CArg0Reg]
  		ifFalse: [regOrConst0 ~= CArg0Reg ifTrue: [cogit MoveR: regOrConst0 R: CArg0Reg]].
  	numArgs = 1 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst1)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: CArg1Reg]
  		ifFalse: [regOrConst1 ~= CArg1Reg ifTrue: [cogit MoveR: regOrConst1 R: CArg1Reg]].
  	numArgs = 2 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst2)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: CArg2Reg]
  		ifFalse: [regOrConst2 ~= CArg2Reg ifTrue: [cogit MoveR: regOrConst2 R: CArg2Reg]].
  	numArgs = 3 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst3)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: CArg3Reg]
  		ifFalse: [regOrConst3 ~= CArg3Reg ifTrue: [cogit MoveR: regOrConst3 R: CArg3Reg]]!

Item was changed:
  ----- Method: CogARMv8Compiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
+ 	 The encoding for constants is defined by trampolineArgConstant: & trampolineArgValue:.
+ 	 Pass a constant as the result of trampolineArgConstant:.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to."
  	<inline: true>
  	numArgs = 0 ifTrue: [^self].
  	"Avoid arg regs being overwritten before they are read."
  	numArgs > 1 ifTrue:
  		[((cogit isTrampolineArgConstant: regOrConst1) not
  		   and: [regOrConst1 = CArg0Reg]) ifTrue:
  			[cogit MoveR: regOrConst1 R: Extra0Reg.
  			 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: Extra0Reg arg: regOrConst2 arg: regOrConst3].
  		 numArgs > 2 ifTrue:
  			[((cogit isTrampolineArgConstant: regOrConst2) not
  			   and: [regOrConst2 = CArg0Reg or: [regOrConst2 = CArg1Reg]]) ifTrue:
  				[cogit MoveR: regOrConst2 R: Extra1Reg.
  				 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: Extra1Reg arg: regOrConst3].
  			 numArgs > 3 ifTrue:
  				[((cogit isTrampolineArgConstant: regOrConst3) not
  				   and: [regOrConst3 = CArg0Reg or: [regOrConst3 = CArg1Reg or: [regOrConst3 = CArg2Reg]]]) ifTrue:
  					[cogit MoveR: regOrConst3 R: Extra2Reg.
  					 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: Extra2Reg]]]].
  	(cogit isTrampolineArgConstant: regOrConst0)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: CArg0Reg]
  		ifFalse: [cogit MoveR: regOrConst0 R: CArg0Reg].
  	numArgs = 1 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst1)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: CArg1Reg]
  		ifFalse: [cogit MoveR: regOrConst1 R: CArg1Reg].
  	numArgs = 2 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst2)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: CArg2Reg]
  		ifFalse: [cogit MoveR: regOrConst2 R: CArg2Reg].
  	numArgs = 3 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst3)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: CArg3Reg]
  		ifFalse: [cogit MoveR: regOrConst3 R: CArg3Reg]!

Item was changed:
  ----- Method: CogAbstractInstruction>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
+ 	 The encoding for constants is defined by trampolineArgConstant: & trampolineArgValue:.
+ 	 Pass a constant as the result of trampolineArgConstant:.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract  registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to."
  	<inline: true>
  	^self subclassResponsibility!

Item was changed:
  ----- Method: CogIA32Compiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
+ 	 The encoding for constants is defined by trampolineArgConstant: & trampolineArgValue:.
+ 	 Pass a constant as the result of trampolineArgConstant:.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract  registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to."
  	<inline: true>
  	numArgs = 0 ifTrue:
  		[^self].
  	numArgs > 1 ifTrue:
  		[numArgs > 2 ifTrue:
  			[numArgs > 3 ifTrue:
  				[(cogit isTrampolineArgConstant: regOrConst3)
  					ifFalse: [cogit PushR: regOrConst3]
  					ifTrue: [cogit PushCq: (cogit trampolineArgValue: regOrConst3)]].
  			 (cogit isTrampolineArgConstant: regOrConst2)
  				ifFalse: [cogit PushR: regOrConst2]
  				ifTrue: [cogit PushCq: (cogit trampolineArgValue: regOrConst2)]].
  		(cogit isTrampolineArgConstant: regOrConst1)
  			ifFalse: [cogit PushR: regOrConst1]
  			ifTrue: [cogit PushCq: (cogit trampolineArgValue: regOrConst1)]].
  	(cogit isTrampolineArgConstant: regOrConst0)
  		ifFalse: [cogit PushR: regOrConst0]
  		ifTrue: [cogit PushCq: (cogit trampolineArgValue: regOrConst0)]!

Item was changed:
  ----- Method: CogMIPSELCompiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
+ 	 The encoding for constants is defined by trampolineArgConstant: & trampolineArgValue:.
+ 	 Pass a constant as the result of trampolineArgConstant:.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract  registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to."
  	<inline: true>
  	self flag: #OABI.
  	numArgs = 0 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst0)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: A0]
  		ifFalse: [cogit MoveR: regOrConst0 R: A0].
  	numArgs = 1 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst1)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: A1]
  		ifFalse: [cogit MoveR: regOrConst1 R: A1].
  	numArgs = 2 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst2)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: A2]
  		ifFalse: [cogit MoveR: regOrConst2 R: A2].
  	numArgs = 3 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst3)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: A3]
  		ifFalse: [cogit MoveR: regOrConst3 R: A3]!

Item was changed:
  ----- Method: CogX64Compiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is either
  	 a negative number, which encodes a positive constant, or a non-negative number, that of a register.
+ 	 The encoding for constants is defined by trampolineArgConstant: & trampolineArgValue:.
+ 	 Pass a constant as the result of trampolineArgConstant:.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM32, where in its C ABI
  	 the first four integer arguments are passed in registers, all arguments can be passed in registers.
  	 We defer to the back end to generate this code not so much that the back end knows whether it
  	 uses the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil
  	 reason. Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments
  	 in an order that allows some of the argument registers to be used for specific abstract  registers,
  	 specifically ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep
  	 using the old register assignments the original author has grown accustomed to.
  
  	 How can this possibly work?  Look at Cogit class>>runtime for a list of the run-time calls and their
  	 arguments, including which arguments are passed in which registers.  Look at CogX64Compiler's
  	 subclass implementations of initializeAbstractRegisters.  There are no calls in which ReceiverResultReg
  	 (RDX) and/or ClassReg (RCX) are passed along with Arg0Reg and Arg1Reg, and none in which the use of
  	 either ReceiverResultReg or ClassReg conflict for args 3 & 4.  So if args are assigned in order, the
  	 registers do not get overwritten.  Yes, this is evil, but it's so nice to continue to use RCX & RDX.
  
  	 Argument registers for args 0 to 3 in SysV are RDI RSI RDX RCX, and in Win64 are RCX RDX R8 R9"
  	<inline: true>
  	SysV ifFalse: "WIN64 ABI allways reserve shadow space on the stack for callee to save up to 4 register parameters"
  		[cogit SubCq: 32 R: RSP].
  	numArgs = 0 ifTrue: [^self].
  	self assert: numArgs <= 4.
  	(cogit isTrampolineArgConstant: regOrConst0)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: CArg0Reg] "a.k.a. Arg0Reg"
  		ifFalse:
  			[regOrConst0 ~= CArg0Reg ifTrue:
  				[cogit MoveR: regOrConst0 R: CArg0Reg]].
  	numArgs = 1 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst1)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: CArg1Reg] "a.k.a. Arg1Reg"
  		ifFalse:
  			[regOrConst1 ~= CArg1Reg ifTrue:
  				[cogit MoveR: regOrConst1 R: CArg1Reg]].
  	numArgs = 2 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst2)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: CArg2Reg] "a.k.a. ReceiverResultReg (SysV) ClassReg (Win64)"
  		ifFalse:
  			[regOrConst2 ~= CArg2Reg ifTrue:
  				[cogit MoveR: regOrConst2 R: CArg2Reg]].
  	 numArgs = 3 ifTrue: [^self].
  	 (cogit isTrampolineArgConstant: regOrConst3)
  			ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: CArg3Reg] "a.k.a. ClassReg (SysV) ReceiverResultReg (Win64)"
  			ifFalse:
  				[regOrConst3 ~= CArg3Reg ifTrue:
  					[cogit MoveR: regOrConst3 R: CArg3Reg]]!

Item was changed:
  ----- Method: Cogit>>compileCallFor:numArgs:arg:arg:arg:arg:floatResultReg:regsToSave: (in category 'initialization') -----
  compileCallFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 floatResultReg: resultRegOrNone regsToSave: regMask
  	"Generate a call to aRoutine with up to 4 arguments.  If resultRegOrNone is not
  	 NoReg assign the C result to resultRegOrNone.  If saveRegs, save all registers.
  	 Hack: a negative arg value indicates an abstract register, a non-negative value
+ 	 indicates a constant. The encoding for constants is defined by trampolineArgConstant:
+ 	 & trampolineArgValue:. Pass a constant as the result of trampolineArgConstant:."
- 	 indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<inline: false>
  	| regsToSave |
  	regsToSave := resultRegOrNone = NoReg
  						ifTrue: [regMask]
  						ifFalse: [regMask bitClear: (self registerMaskFor: resultRegOrNone)].
  	cStackAlignment > objectMemory wordSize ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: regsToSave
  			numArgs: numArgs
  			wordAlignment: cStackAlignment / objectMemory wordSize].
  	backEnd
  		genSaveRegs: regsToSave;
  		genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3.
  	self CallFullRT: (self cCode: [aRoutine asUnsignedInteger]
  						inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
  	resultRegOrNone ~= NoReg ifTrue:
  		[backEnd cFloatResultToRd: resultRegOrNone].
  	backEnd
  		genRemoveNArgsFromStack: numArgs;
  		genRestoreRegs: regsToSave!

Item was changed:
  ----- Method: Cogit>>compileCallFor:numArgs:arg:arg:arg:arg:resultReg:regsToSave: (in category 'initialization') -----
  compileCallFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 resultReg: resultRegOrNone regsToSave: regMask
  	"Generate a call to aRoutine with up to 4 arguments.  If resultRegOrNone is not
  	 NoReg assign the C result to resultRegOrNone.  If saveRegs, save all registers.
  	 Hack: a negative arg value indicates an abstract register, a non-negative value
+ 	 indicates a constant. The encoding for constants is defined by trampolineArgConstant:
+ 	 & trampolineArgValue:. Pass a constant as the result of trampolineArgConstant:."
- 	 indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<inline: false>
  	| regsToSave |
  	regsToSave := resultRegOrNone = NoReg
  						ifTrue: [regMask]
  						ifFalse: [regMask bitClear: (self registerMaskFor: resultRegOrNone)].
  	cStackAlignment > objectMemory wordSize ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: regsToSave
  			numArgs: numArgs
  			wordAlignment: cStackAlignment / objectMemory wordSize].
  	backEnd
  		genSaveRegs: regsToSave;
  		genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3.
  	self CallFullRT: (self cCode: [aRoutine asUnsignedInteger]
  						inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
  	backEnd
  		genWriteCResultIntoReg: resultRegOrNone;
  		genRemoveNArgsFromStack: numArgs;
  		genRestoreRegs: regsToSave!

Item was changed:
  ----- Method: Cogit>>compileCallFor:numArgs:arg:arg:arg:arg:resultReg:resultReg:regsToSave: (in category 'initialization') -----
  compileCallFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 resultReg: resultRegOrNone resultReg: resultReg2OrNone regsToSave: regMask
  	"Generate a call to aRoutine with up to 4 arguments.  If resultRegOrNone is not
  	 NoReg assign the C result to resultRegOrNone.  If saveRegs, save all registers.
  	 Hack: a negative arg value indicates an abstract register, a non-negative value
+ 	 indicates a constant. The encoding for constants is defined by trampolineArgConstant:
+ 	 & trampolineArgValue:. Pass a constant as the result of trampolineArgConstant:."
- 	 indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<inline: false>
  	| regsToSave |
  	regsToSave := resultRegOrNone = NoReg
  						ifTrue: [regMask]
  						ifFalse: [regMask bitClear: (self registerMaskFor: resultRegOrNone)].
  	cStackAlignment > objectMemory wordSize ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: regsToSave
  			numArgs: numArgs
  			wordAlignment: cStackAlignment / objectMemory wordSize].
  	backEnd
  		genSaveRegs: regsToSave;
  		genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3.
  	self CallFullRT: (self cCode: [aRoutine asUnsignedInteger]
  						inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
  	backEnd
  		genWriteCResultIntoReg: resultRegOrNone;
  		genWriteCSecondResultIntoReg: resultReg2OrNone;
  		genRemoveNArgsFromStack: numArgs;
  		genRestoreRegs: regsToSave!

Item was changed:
  ----- Method: Cogit>>trampolineArgConstant: (in category 'initialization') -----
+ trampolineArgConstant: booleanIntegerOrNil
- trampolineArgConstant: booleanOrInteger
  	"Encode true and false and 0 to N such that they can't be confused for register numbers (including NoReg)
  	 and can be tested for by isTrampolineArgConstant: and decoded by trampolineArgValue:"
  	<inline: true>
  	self cCode: []
+ 		inSmalltalk:
+ 			[booleanIntegerOrNil isInteger ifFalse:
+ 				[^self trampolineArgConstant: (booleanIntegerOrNil
+ 													ifNil: [0]
+ 													ifNotNil: [booleanIntegerOrNil ifTrue: [1] ifFalse: [0]])]].
+ 	self assert: booleanIntegerOrNil >= 0.
+ 	^-2 - booleanIntegerOrNil "0...N => -2...-(N+2)"!
- 		inSmalltalk: [booleanOrInteger isInteger ifFalse: [^self trampolineArgConstant: (booleanOrInteger ifTrue: [1] ifFalse: [0])]].
- 	self assert: booleanOrInteger >= 0.
- 	^-2 - booleanOrInteger "0...N => -2...-(N+2)"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive:flags: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine flags: flags
  	"Compile a call to an interpreter primitive.  Call the C routine with the
  	 usual stack-switching dance, test the primFailCode and then either
  	 return on success or continue to the method body."
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| jmp continueAfterProfileSample jumpToTakeSample |
  	self deny: (backEnd hasVarBaseRegister
  				and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
  
  	"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
  	self genExternalizePointersForPrimitiveCall.
  	"Switch to the C stack."
  	self genLoadCStackPointersForPrimCall.
  
  	"Old old full prim trace is in VMMaker-eem.550 and prior.
  	 Old simpler full prim trace is in VMMaker-eem.2969 and prior."
  	(coInterpreter recordPrimTraceForMethod: methodObj) ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self AddCq: methodOrBlockNumArgs R: TempReg]. "As small or smaller than move on most archs"
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  
  	"If required, set primitiveFunctionPointer and newMethod"
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[self MoveCw: primitiveRoutine asInteger R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  	(flags anyMask: PrimCallNeedsNewMethod+PrimCallMayEndureCodeCompaction) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags anyMask: PrimCallMayEndureCodeCompaction) ifTrue:
  			[needsFrame := true].
  		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		 self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter newMethodAddress].
  
  	"Invoke the primitive.  If the primitive (potentially) contains a call-back then its code
  	 may disappear and consequently we cannot return here, sicne here may evaporate.
  	 Instead sideways-call the routine, substituting cePrimReturnEnterCogCode[Profiling]
  	 as the return address, so the call always returns there."
  	self PrefetchAw: coInterpreter primFailCodeAddress.
  	(flags anyMask: PrimCallMayEndureCodeCompaction) ifTrue:
  		["On Spur ceActivateFailingPrimitiveMethod: would like to retry if forwarders
  		  are found. So insist on PrimCallNeedsPrimitiveFunction being set too."
  		 objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction)].
  		 backEnd
  			genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil;
  			genSubstituteReturnAddress:
  				((flags anyMask: PrimCallCollectsProfileSamples)
  					ifTrue: [cePrimReturnEnterCogCodeProfiling]
  					ifFalse: [cePrimReturnEnterCogCode]).
  		 self JumpFullRT: primitiveRoutine asInteger.
  		 ^0].
  
  	"Call the C primitive routine."
+ 	backEnd genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil.
+ 	"If the primitive is in the interpreter then its address won't change relative to the code zone over time,
+ 	 whereas if it is in a plugin its address could change if the module is un/re/over/loaded.
+ 	 So if in the interpreter and in range use a normal call instruction."
+ 	((flags anyMask: PrimCallIsInternalPrim)
+ 	 and: [backEnd isWithinCallRange: primitiveRoutine asInteger])
+ 		ifTrue: [self CallRT: primitiveRoutine asInteger]
+ 		ifFalse: [self CallFullRT: primitiveRoutine asInteger].
- 	backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
- 	self CallFullRT: primitiveRoutine asInteger.
  	backEnd genRemoveNArgsFromStack: 0.
  	objectRepresentation maybeCompileRetryOnPrimitiveFail: primitiveIndex.
  	"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  		success:	stackPointer ->	result (was receiver)
  									arg1
  									...
  									argN
  									return pc
  		failure:						receiver
  									arg1
  									...
  					stackPointer ->	argN
  									return pc"
  	backEnd genLoadStackPointersForPrimCall: ClassReg.
  	"genLoadStackPointersForPrimCall: leaves the stack in these states:
  			NoLinkRegister 												LinkRegister
  		success:					result (was receiver)		stackPointer ->	result (was receiver)
  					stackPointer ->	arg1										arg1
  									...											...
  									argN										argN
  									return pc
  
  		failure:						receiver									receiver
  									arg1										arg1
  									...											...
  									argN						stackPointer ->	argN
  					stackPointer ->	return pc
  	which corresponds to the stack on entry after pushRegisterArgs.
  	 In either case we can write the instructionPointer to top of stack or load it into the LinkRegister to reestablish the return pc."
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveAw: coInterpreter instructionPointerAddress R: LinkReg]
  		ifFalse:
  			[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
  			 self MoveR: ClassReg Mw: 0 r: SPReg].
  	"Test primitive failure"
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	self flag: 'ask concrete code gen if move sets condition codes?'.
  	self CmpCq: 0 R: TempReg.
  	jmp := self JumpNonZero: 0.
  	"placing the test here attributes the tick to the primitive plus any checkForAndFollowForwardedPrimitiveState
  	 scanning, but attributes all of a failing primitive to the current method (in ceStackOverflow: on frame build)."
  	(backEnd has64BitPerformanceCounter
  	 and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
  		[jumpToTakeSample := self genCheckForProfileTimerTick: (self registerMaskFor: NoReg)].
  	"Fetch result from stack"
  	continueAfterProfileSample :=
  	self MoveMw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
  		r: SPReg
  		R: ReceiverResultReg.
  	self RetN: objectMemory wordSize.	"return to caller, popping receiver"
  	(backEnd has64BitPerformanceCounter
  	 and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
  		[jumpToTakeSample jmpTarget: self Label.
  		 self genTakeProfileSample.
  		 backEnd genLoadStackPointerForPrimCall: ClassReg.
  		 backEnd hasLinkRegister
  			ifTrue:
  				[self MoveAw: coInterpreter instructionPointerAddress R: LinkReg]
  			ifFalse:
  				[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
  				 self MoveR: ClassReg Mw: 0 r: SPReg].
  		 self Jump: continueAfterProfileSample].
  
  	"Jump to restore of receiver reg and proceed to frame build for failure."
  	 jmp jmpTarget: self Label.
  	 "Restore receiver reg from stack.  If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
  	 self MoveMw: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
  		r: SPReg
  		R: ReceiverResultReg.
  	^0!

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

Item was changed:
  ----- Method: SpurMemoryManager>>numPointerSlotsOf:format: (in category 'object access') -----
  numPointerSlotsOf: objOop format: fmt
  	"Answer the number of pointer fields in the given object.
  	 Works with CompiledMethods, as well as ordinary objects."
+ 	<returnTypeC: #usqInt>
  	<inline: #always>
  	| contextSize numLiterals header |
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextNonImm: objOop]) ifTrue:
  			["contexts end at the stack pointer"
  			contextSize := coInterpreter fetchStackPointerOf: objOop.
  			^CtxtTempFrameStart + contextSize].
  		^self numSlotsOf: objOop  "all pointers"].
  	fmt = self forwardedFormat ifTrue: [^1].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
  	header := self methodHeaderOf: objOop.
  	numLiterals := self literalCountOfMethodHeader: header.
  	^numLiterals + LiteralStart!



More information about the Vm-dev mailing list