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

commits at source.squeak.org commits at source.squeak.org
Wed Jun 3 15:53:45 UTC 2015


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

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

Name: VMMaker.oscog-eem.1333
Author: eem
Time: 3 June 2015, 8:51:47.115 am
UUID: bc9001c2-8816-4b4e-bf91-8e11cad6ed6b
Ancestors: VMMaker.oscog-eem.1332

Cogit:
Fix assert-fails with absent receiver sends in
Newspeak.  Have the implicit and outer send
lookup trampolines set the stacked receiver
(when there is one) when setting the implciit
receiver.

Streamline send trampoline creation by refactoring
trampoline name generation so that the two limits,
NumSendTrampolines - 2 and numRegArgs are
treated separately, and numArgsOrSendNumArgsReg:
answers the relevant numArgs argument.  This should
clear up confusion between numRegArgs (which can be 0, 1 & 2)
and NumSendTrampolines - 2, which is always 2.

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

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

Item was changed:
  ----- Method: Cogit>>generateNewspeakSendTrampolines (in category 'initialization') -----
  generateNewspeakSendTrampolines
  	"Self send, dynamic super send, implicit receiver send, and outer send"
  	<option: #NewspeakVM>
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		selfSendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSelfSend:to:numArgs:
  					  called: (self trampolineName: 'ceSelfSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	selfSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genTrampolineFor: #ceSelfSend:to:numArgs:
- 					called: (self trampolineName: 'ceSelfSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		dynamicSuperSendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceDynamicSuperSend:to:numArgs:
  					  called: (self trampolineName: 'ceDynSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	dynamicSuperSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 					called: (self trampolineName: 'ceDynSuperSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		implicitReceiverSendTrampolines
  			at: numArgs
  			put: (self 
  				genNSSendTrampolineFor: #ceImplicitReceiverSend:receiver:
  				numArgs: numArgs
  				called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: numArgs))].
- 	implicitReceiverSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self 
- 			genNSSendTrampolineFor: #ceImplicitReceiverSend:receiver:
- 			numArgs: self numRegArgs + 1
- 			called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: -1)).
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		outerSendTrampolines
  			at: numArgs
  			put: (self 
  				genNSSendTrampolineFor: #ceOuterSend:receiver:
  				numArgs: numArgs
  				called: (self trampolineName: 'ceOuterSend' numArgs: numArgs))].
- 	outerSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self 
- 			genNSSendTrampolineFor: #ceOuterSend:receiver:
- 			numArgs: self numRegArgs + 1
- 			called: (self trampolineName: 'ceOuterSend' numArgs: -1)).
  
  !

Item was changed:
  ----- Method: Cogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 0
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	ordinarySendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genTrampolineFor: #ceSend:super:to:numArgs:
- 					called: (self trampolineName: 'ceSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: 0
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
  	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
  	self cppIf: BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[0 to: NumSendTrampolines - 1 do:
- 		[0 to: NumSendTrampolines - 2 do:
  			[:numArgs|
  			directedSuperSendTrampolines
  				at: numArgs
  				put: (self genTrampolineFor: #ceSend:above:to:numArgs:
  						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
  						  arg: ClassReg
  						  arg: TempReg
  						  arg: ReceiverResultReg
+ 						  arg: (self numArgsOrSendNumArgsReg: numArgs))]].
- 						  arg: numArgs)].
- 		directedSuperSendTrampolines
- 			at: NumSendTrampolines - 1
- 			put: (self genTrampolineFor: #ceSend:above:to:numArgs:
- 						called: (self trampolineName: 'ceDirectedSuperSend' numArgs: -1)
- 						arg: ClassReg
- 						arg: TempReg
- 						arg: ReceiverResultReg
- 						arg: SendNumArgsReg)].
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 1
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	superSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genTrampolineFor: #ceSend:super:to:numArgs:
- 					called: (self trampolineName: 'ceSuperSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: 1
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was added:
+ ----- Method: Cogit>>numArgsOrSendNumArgsReg: (in category 'initialization') -----
+ numArgsOrSendNumArgsReg: numArgs
+ 	"The send trampolines have different versions for different arg counts, with special
+ 	 cases for 0 through NumSendTrampolines - 2, and a general case for more, passing
+ 	 the arg count in SendNumArgsReg.  This computes the relevant argument."
+ 	<inline: true>
+ 	^numArgs <= (NumSendTrampolines - 2) ifTrue: [numArgs] ifFalse: [SendNumArgsReg]!

Item was changed:
  ----- Method: Cogit>>trampolineName:numArgs: (in category 'initialization') -----
  trampolineName: routinePrefix numArgs: numArgs
+ 	^self trampolineName: routinePrefix numArgs: numArgs limit: NumSendTrampolines - 2!
- 	"Malloc a string with the contents for the trampoline table"
- 	<returnTypeC: #'char *'>
- 	<var: #routinePrefix type: #'char *'>
- 	| theString |
- 	<var: #theString type: #'char *'>
- 	self cCode: '' inSmalltalk:
- 		[^routinePrefix, (numArgs >= 0 ifTrue: [numArgs printString] ifFalse: ['N']), 'Args'].
- 	theString := self malloc: (self strlen: routinePrefix) + 6.
- 	self s: theString pr: '%s%cArgs' in: routinePrefix tf: (numArgs >= 0 ifTrue: [$0 + numArgs] ifFalse: [$N]).
- 	^theString!

Item was added:
+ ----- Method: Cogit>>trampolineName:numArgs:limit: (in category 'initialization') -----
+ trampolineName: routinePrefix numArgs: numArgs limit: argsLimit
+ 	"Malloc a string with the contents for the trampoline table"
+ 	<inline: true>
+ 	<returnTypeC: #'char *'>
+ 	<var: #routinePrefix type: #'char *'>
+ 	| theString |
+ 	<var: #theString type: #'char *'>
+ 	self cCode: '' inSmalltalk:
+ 		[^routinePrefix, (numArgs <= argsLimit ifTrue: [numArgs printString] ifFalse: ['N']), 'Args'].
+ 	theString := self malloc: (self strlen: routinePrefix) + 6.
+ 	self s: theString pr: '%s%cArgs' in: routinePrefix tf: (numArgs <= argsLimit ifTrue: [$0 + numArgs] ifFalse: [$N]).
+ 	^theString!

Item was added:
+ ----- Method: Cogit>>trampolineName:numRegArgs: (in category 'initialization') -----
+ trampolineName: routinePrefix numRegArgs: numArgs
+ 	^self trampolineName: routinePrefix numArgs: numArgs limit: self numRegArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicitOrOuter:numArgs:depth:sendTable: (in category 'bytecode generators') -----
  genSendAbsentImplicitOrOuter: selector numArgs: numArgs depth: depth sendTable: sendTable
  	<var: #sendTable type: #'sqInt *'>
  	| nsSendCache |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  
  	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
  	indexOfIRC := indexOfIRC + 1.
  	self assert: (objectMemory isInOldSpace: nsSendCache).
  	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
  
+ 	"This leaves the method receiver on the stack, which might not be the implicit receiver.
+ 	 But the lookup trampoline will establish the on-stack receiver once it locates it."
- 	"This leaves the method receiver on the stack, which might not be the implicit receiver. But we care
- 	 not: the callee will use ReceiverResultReg to build its frame, not the value beneath the arguments."
  	self marshallAbsentReceiverSendArguments: numArgs.
  
  	"Load the cache last so it is a fixed distance from the call."
  	self MoveCw: nsSendCache R: SendNumArgsReg.
  	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
  
  	self PushR: ReceiverResultReg.
  	^0!

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

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

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

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

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendAbsentImplicitOrOuter:numArgs:depth:sendTable: (in category 'bytecode generators') -----
  genSendAbsentImplicitOrOuter: selector numArgs: numArgs depth: depth sendTable: sendTable
  	<var: #sendTable type: #'sqInt *'>
  	| nsSendCache |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  
  	nsSendCache := theIRCs + (NumOopsPerNSC * objectMemory bytesPerOop * indexOfIRC).
  	indexOfIRC := indexOfIRC + 1.
  	self assert: (objectMemory isInOldSpace: nsSendCache).
  	self initializeNSSendCache: nsSendCache selector: selector numArgs: numArgs depth: depth.
  
  	self ssAllocateCallReg: SendNumArgsReg.
  
+ 	"This may leave the method receiver on the stack, which might not be the implicit receiver.
+ 	 But the lookup trampoline will establish an on-stack receiver once it locates it."
- 	"This leaves the method receiver on the stack, which might not be the implicit receiver. But we care
- 	 not: the callee will use ReceiverResultReg to build its frame, not the value beneath the arguments."
  	self marshallAbsentReceiverSendArguments: numArgs.
  
  	"Load the cache last so it is a fixed distance from the call."
  	self MoveCw: nsSendCache R: SendNumArgsReg.
  	self CallNewspeakSend: (sendTable at: (numArgs min: NumSendTrampolines - 1)).
  
  	optStatus isReceiverResultRegLive: false.
  	self ssPushRegister: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateMissAbortTrampolines (in category 'initialization') -----
  generateMissAbortTrampolines
  	"Generate the run-time entries for the various method and PIC entry misses and aborts.
  	 Read the class-side method trampolines for documentation on the various trampolines"
- 
- 	"Slang needs these apparently superfluous asSymbol sends."
  	0 to: self numRegArgs + 1 do:
  		[:numArgs|
  		methodAbortTrampolines
  			at: numArgs
  			put: (self genMethodAbortTrampolineFor: numArgs)].
  	0 to: self numRegArgs + 1 do:
  		[:numArgs|
  		picAbortTrampolines
  			at: numArgs
  			put: (self genPICAbortTrampolineFor: numArgs)].
  	0 to: self numRegArgs + 1 do:
  		[:numArgs|
  		picMissTrampolines
  			at: numArgs
  			put: (self genPICMissTrampolineFor: numArgs)]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateNewspeakSendTrampolines (in category 'initialization') -----
  generateNewspeakSendTrampolines
+ 	"Self send, dynamic super send, implicit receiver send, and outer send."
- 	"Self send, dynamic super send, and implicit receiver send. TODO: outer send."
  	"Override to generate code to push the register arg(s) for <= numRegArg arity sends."
  	<option: #NewspeakVM>
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		selfSendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSelfSend:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSelfSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	selfSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genSendTrampolineFor: #ceSelfSend:to:numArgs:
- 					numArgs: self numRegArgs + 1
- 					called: (self trampolineName: 'ceSelfSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		dynamicSuperSendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceDynamicSuperSend:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceDynSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	dynamicSuperSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genSendTrampolineFor: #ceDynamicSuperSend:to:numArgs:
- 					numArgs: self numRegArgs + 1
- 					called: (self trampolineName: 'ceDynSuperSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		implicitReceiverSendTrampolines
  			at: numArgs
  			put: (self 
  				genNSSendTrampolineFor: #ceImplicitReceiverSend:receiver:
  				numArgs: numArgs
  				called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: numArgs))].
- 	implicitReceiverSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self 
- 			genNSSendTrampolineFor: #ceImplicitReceiverSend:receiver:
- 			numArgs: self numRegArgs + 1
- 			called: (self trampolineName: 'ceImplicitReceiverSend' numArgs: -1)).
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		outerSendTrampolines
  			at: numArgs
  			put: (self 
  				genNSSendTrampolineFor: #ceOuterSend:receiver:
  				numArgs: numArgs
+ 				called: (self trampolineName: 'ceOuterSend' numArgs: numArgs))]!
- 				called: (self trampolineName: 'ceOuterSend' numArgs: numArgs))].
- 	outerSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self 
- 			genNSSendTrampolineFor: #ceOuterSend:receiver:
- 			numArgs: self numRegArgs + 1
- 			called: (self trampolineName: 'ceOuterSend' numArgs: -1)).!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	"Override to generate code to push the register arg(s) for <= numRegArg arity sends."
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 0
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	ordinarySendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
- 					numArgs: self numRegArgs + 1
- 					called: (self trampolineName: 'ceSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: 0
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
  	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
  	self cppIf: BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[0 to: NumSendTrampolines - 1 do:
- 		[0 to: NumSendTrampolines - 2 do:
  			[:numArgs|
  			directedSuperSendTrampolines
  				at: numArgs
  				put: (self genSendTrampolineFor: #ceSend:above:to:numArgs:
  						  numArgs: numArgs
  						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
  						  arg: ClassReg
  						  arg: TempReg
  						  arg: ReceiverResultReg
+ 						  arg: (self numArgsOrSendNumArgsReg: numArgs))]].
- 						  arg: numArgs)].
- 		directedSuperSendTrampolines
- 			at: NumSendTrampolines - 1
- 			put: (self genSendTrampolineFor: #ceSend:above:to:numArgs:
- 						numArgs: self numRegArgs + 1
- 						called: (self trampolineName: 'ceDirectedSuperSend' numArgs: -1)
- 						arg: ClassReg
- 						arg: TempReg
- 						arg: ReceiverResultReg
- 						arg: SendNumArgsReg)].
  
+ 	0 to: NumSendTrampolines - 1 do:
- 	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 1
  					  arg: ReceiverResultReg
+ 					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
- 					  arg: numArgs)].
- 	superSendTrampolines
- 		at: NumSendTrampolines - 1
- 		put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
- 					numArgs: self numRegArgs + 1
- 					called: (self trampolineName: 'ceSuperSend' numArgs: -1)
- 					arg: ClassReg
- 					arg: 1
- 					arg: ReceiverResultReg
- 					arg: SendNumArgsReg).
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!



More information about the Vm-dev mailing list