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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 16 01:25:09 UTC 2015


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

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

Name: VMMaker.oscog-eem.1199
Author: eem
Time: 15 April 2015, 6:23:33.213 pm
UUID: 87562ee0-1720-478d-a9bb-04170c151a89
Ancestors: VMMaker.oscog-tpr.1198

Fix genGetActiveContextLarge:inBlock: for ARM:
Clarify and correct Tim's comments re link reg
and reintroduce choice of bounds check depending
on link reg.
Introduce marryFrameCopiesTemps and use it to
not copy temps in Spur contect creation trampolines.

Change initial usage counts to keep more recently
jitted methods around for longer, and do *not*
throw away PICs in freeOlderMethodsForCompaction,
so that there's a better chance of Sista finding send
and branch data for the tripping method.

Provide missing V3 long64At:[put:] methods for
simulation.

=============== Diff against VMMaker.oscog-tpr.1198 ===============

Item was added:
+ ----- Method: CoInterpreter>>marryFrameCopiesTemps (in category 'frame access') -----
+ marryFrameCopiesTemps
+ 	"Answer whether marryFrame:SP: copies non-argument temporaries."
+ 	<api>
+ 	^false!

Item was changed:
  ----- Method: CogMethodZone>>freeOlderMethodsForCompaction (in category 'compaction') -----
  freeOlderMethodsForCompaction
  	"Free methods, preferring older methods for compaction, up to some fraction."
  	| zoneSize amountToFree initialFreeSpace freedSoFar freeableUsage cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	zoneSize := limitAddress - baseAddress.
  	initialFreeSpace := limitAddress - mzFreeStart + methodBytesFreedSinceLastCompaction.
  	freedSoFar := initialFreeSpace.
  	amountToFree := zoneSize // 4. "4 needs to be e.g. a start-up parameter"
  	freeableUsage := 0.
  	[self cCode: ''
  		inSmalltalk: [coInterpreter transcript nextPutAll: 'freeing methods with usage '; print: freeableUsage; cr; flush].
  	 cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	 [cogMethod asUnsignedInteger < mzFreeStart
  	  and: [freedSoFar < amountToFree]] whileTrue:
+ 		[(cogMethod cmType = CMMethod
- 		[(cogMethod cmType ~= CMFree
  		  and: [cogMethod cmUsageCount <= freeableUsage]) ifTrue:
  			[self freeMethod: cogMethod.
  			 freedSoFar := freedSoFar + cogMethod blockSize].
  		 cogMethod := self methodAfter: cogMethod].
  	 freedSoFar < amountToFree
  	 and: [(freeableUsage := freeableUsage + 1) < CMMaxUsageCount]] whileTrue.
  	self cCode: ''
  		inSmalltalk: [coInterpreter transcript
  						nextPutAll: 'Compaction freeing '; print: freedSoFar;
  						nextPutAll: ' of '; print: zoneSize;
  						nextPutAll: ' (target: '; print: amountToFree;
  						nextPutAll: ' (newly freed: '; print: freedSoFar - initialFreeSpace;
  						cr; flush]!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genGetActiveContextLarge:inBlock: (in category 'initialization') -----
  genGetActiveContextLarge: isLarge inBlock: isInBlock
  	"Create a trampoline to answer the active context that will
  	 answer it if a frame is already married, and create it otherwise.
  	 Assume numArgs is in SendNumArgsReg and ClassReg is free."
  	| header slotSize jumpSingle loopHead jumpNeedScavenge continuation exit |
  	<var: #jumpNeedScavenge type: #'AbstractInstruction *'>
  	<var: #continuation type: #'AbstractInstruction *'>
  	<var: #jumpSingle type: #'AbstractInstruction *'>
  	<var: #loopHead type: #'AbstractInstruction *'>
  	<var: #exit type: #'AbstractInstruction *'>
  	cogit "load the flag; stash it in both TempReg & ClassReg; do the compare (a prime candidated for use of AndCq:R:R:)"
  		MoveMw: FoxMethod r: FPReg R: ClassReg;
  		AndCq: MFMethodFlagHasContextFlag R: ClassReg R: TempReg.
  	jumpSingle := cogit JumpZero: 0. "jump if flag bit not set"
  	cogit "since the flag bit was set, get the context in the receiver reg and return"
  		MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
  		RetN: 0.
  	jumpSingle jmpTarget: cogit Label.
  
  	"OK, it doesn't exist; instantiate and initialize it"
  	"set the hasContext flag; See CoInterpreter class>>initializeFrameIndices"
  	cogit
  		OrCq: MFMethodFlagHasContextFlag R: ClassReg;
  		MoveR: ClassReg Mw: FoxMethod r: FPReg.
  	"now get the home CogMethod into ClassReg and save for post-instantiation."
  	isInBlock
  		ifTrue:
  			[cogit
  				SubCq: 3 R: ClassReg; "-3 is -(hasContext+isBlock) flags"
  				MoveM16: 0 r: ClassReg R: TempReg;
  				SubR: TempReg R: ClassReg]
  		ifFalse:
  			[cogit SubCq: 1 R: ClassReg]. "-1 is hasContext flag"
  
  	"instantiate the context..."
  	slotSize := isLarge ifTrue: [LargeContextSlots] ifFalse: [SmallContextSlots].
  	header := objectMemory
  					headerForSlots: slotSize
  					format: objectMemory indexablePointersFormat
  					classIndex: ClassMethodContextCompactIndex.
  	self flag: #endianness.
  	cogit
  		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
  		MoveCq: (self low32BitsOf: header) R: TempReg;
  		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
  		MoveCq: header >> 32 R: TempReg;
  		MoveR: TempReg Mw: 4 r: ReceiverResultReg;
  		MoveR: ReceiverResultReg R: TempReg;
  		AddCq: (objectMemory smallObjectBytesForSlots: slotSize) R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	jumpNeedScavenge := cogit JumpAboveOrEqual: 0.
  
  	"Now initialize the fields of the context.  See CoInterpreter>>marryFrame:SP:copyTemps:"
  	"sender gets frame pointer as a SmallInteger"
  	continuation :=
  	cogit MoveR: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (SenderIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"pc gets frame caller as a SmallInteger"
  	cogit MoveMw: FoxSavedFP r: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (InstructionPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the method field, freeing up ClassReg again, and frame's context field,"
  	cogit
  		MoveMw: (cogit offset: CogMethod of: #methodObject) r: ClassReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (MethodIndex * objectMemory wordSize) r: ReceiverResultReg;
  		MoveR: ReceiverResultReg Mw: FoxThisContext r: FPReg.
  
+ 	"Now compute stack pointer; this is stackPointer (- 1 for return pc if a CISC) - framePointer - 4 (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
- 	"Now compute stack pointer; this is stackPointer (- 1 for return pc if a CISC) - framePointer - 4 (1 each for saved pc, method, context, receiver) + 1 (1-relative)"
  	"TPR note - the code here is actually doing
  	context stackPointer := ((((fp - sp) / 4) - [3|4]) + num args) asSmallInteger"
  	cogit
  		MoveR: FPReg R: TempReg;
  		SubR: SPReg R: TempReg;
  		LogicalShiftRightCq: self log2BytesPerWord R: TempReg;
  		SubCq: (cogit backEnd hasLinkRegister ifTrue: [3] ifFalse: [4]) R: TempReg;
  		AddR: SendNumArgsReg R: TempReg.
  	self genConvertIntegerToSmallIntegerInReg: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (StackPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set closureOrNil to either the stacked receiver or nil"
  	isInBlock
  		ifTrue:
  			[cogit
  				MoveR: SendNumArgsReg R: TempReg;
+ 				AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
- 				AddCq: 2 R: TempReg; "+2 for saved fp and saved pc" "TPR note - is this a problematic place? Maybe only 1 with LR?"
  				MoveXwr: TempReg R: FPReg R: TempReg]
  		ifFalse:
  			[cogit MoveCw: objectMemory nilObject R: TempReg].
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (ClosureIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the receiver"
  	cogit
  		MoveMw: FoxMFReceiver r: FPReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (ReceiverIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Now copy the arguments.  This is tricky because of the shortage of registers,.  ClassReg ranges
  	 from 1 to numArgs (SendNumArgsReg), and from ReceiverIndex + 1 to ReceiverIndex + numArgs.
  	 1 to: numArgs do:
  		[:i|
  		temp := longAt(FPReg + ((SendNumArgs - i + 2) * BytesPerWord)). +2 for saved pc and savedfp
  		longAtput(FPReg + FoxMFReceiver + (i * BytesPerWord), temp)]"
+ 	"TPR note: this is a prime candidate for passing off to the backend to do at least faintly optimal code"
- 	"TPR note: this is a prime candidate for passing off to the backed to do at least faintly optimal code"
  	cogit MoveCq: 1 R: ClassReg.
  	loopHead := cogit CmpR: SendNumArgsReg R: ClassReg.
  	exit := cogit JumpGreater: 0.
  	cogit
  		MoveR: SendNumArgsReg R: TempReg;
  		SubR: ClassReg R: TempReg;
+ 		AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
- 		AddCq:  (cogit backEnd hasLinkRegister ifTrue: [1] ifFalse: [2]) R: TempReg; "+2 for saved fp and saved pc" "TPR note another LR problem place?"
  		MoveXwr: TempReg R: FPReg R: TempReg;
  		AddCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) R: ClassReg; "Now convert ClassReg from frame index to context index"
  		MoveR: TempReg Xwr: ClassReg R: ReceiverResultReg;
  		SubCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) - 1 R: ClassReg; "convert back adding 1 ;-)"
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
+ 	"Finally nil or copy the non-argument temps.
- 	"Finally copy the temps.
  	 ClassReg := FPReg + FoxMFReceiver.
  	 SendNumArgsReg := SendNumArgsReg+ReceiverIndex.
  	 [ClassReg := ClassReg - 4.
  	  backEnd hasLinkRegister
  			ifTrue: [ClassReg > SPReg]
  			ifFalse: [ClassReg >= SPReg]] whileTrue:
  		[receiver[SendNumArgsReg] := *ClassReg.
  		 SendNumArgsReg := SendNumArgsReg + 1]]"
+ 	coInterpreter marryFrameCopiesTemps ifFalse:
+ 		[cogit MoveCq: objectMemory nilObject R: TempReg].
  	cogit
  		MoveR: FPReg R: ClassReg;
  		AddCq: FoxMFReceiver R: ClassReg;
  		AddCq: ReceiverIndex + 1 + (objectMemory baseHeaderSize / objectMemory wordSize) R: SendNumArgsReg.
  	loopHead :=
  	cogit SubCq: objectMemory wordSize R: ClassReg.
  	cogit CmpR: SPReg R: ClassReg.
+ 	"If on a CISC there's a retpc for the trampoline call on top of stack; if on a RISC there isn't."
+ 	exit := cogit backEnd hasLinkRegister
+ 				ifTrue: [cogit JumpBelowOrEqual: 0]
+ 				ifFalse: [cogit JumpBelow: 0].
+ 	coInterpreter marryFrameCopiesTemps ifTrue:
+ 		[cogit MoveMw: 0 r: ClassReg R: TempReg].
- 	exit := cogit JumpBelow: 0.
  	cogit
- 		MoveMw: 0 r: ClassReg R: TempReg;
  		MoveR: TempReg Xwr: SendNumArgsReg R: ReceiverResultReg;
  		AddCq: 1 R: SendNumArgsReg;
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
  	cogit RetN: 0.
  	
  	jumpNeedScavenge jmpTarget:
  		(cogit backEnd saveAndRestoreLinkRegAround: [cogit CallRT: ceScheduleScavengeTrampoline]). "We need to push the LR here for ARM, and pop it back after the callRT:"
  	cogit Jump: continuation.
  	^0!

Item was changed:
  ----- Method: Cogit>>initialClosedPICUsageCount (in category 'generate machine code') -----
  initialClosedPICUsageCount
  	"Answer a usage count that reflects likely long-term usage."
+ 	^CMMaxUsageCount // 2!
- 	^2!

Item was changed:
  ----- Method: Cogit>>initialMethodUsageCount (in category 'generate machine code') -----
  initialMethodUsageCount
  	"Answer a usage count that reflects likely long-term usage.
+ 	 Answer 1 for non-primitives or quick primitives (inst var accessors),
+ 	 2 for methods with interpreter primitives, and 3 for compiled primitives."
+ 	(primitiveIndex = 1
- 	 Answer 0 for non-primitives or quick primitives (inst var accessors),
- 	 1 for methods with interpreter primitives, and 2 for compiled primitives."
- 	(primitiveIndex = 0
  	 or: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
- 		[^0].
- 	self primitiveGeneratorOrNil isNil ifTrue:
  		[^1].
+ 	self primitiveGeneratorOrNil isNil ifTrue:
+ 		[^2].
+ 	^3!
- 	^2!

Item was changed:
  ----- Method: Cogit>>initialOpenPICUsageCount (in category 'generate machine code') -----
  initialOpenPICUsageCount
  	"Answer a usage count that reflects likely long-term usage."
+ 	^CMMaxUsageCount - 1!
- 	^3!

Item was changed:
  ----- Method: Cogit>>noCogMethodsMaximallyMarked (in category 'compaction') -----
  noCogMethodsMaximallyMarked
+ 	"Check that no method is maximally marked.  A maximal mark is an indication the
- 	"Check that no metod is maximally marked.  A maximal mark is an indication the
  	 method has been scanned to increase the usage count of its referent methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType ~= CMFree
  		  and: [cogMethod cmUsageCount = CMMaxUsageCount]) ifTrue:
  			[^false].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	^true!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorLSB>>long64At: (in category 'memory access') -----
+ long64At: byteAddress
+ 	"memory is a Bitmap, a 32-bit indexable array of bits"
+ 	| hiWord loWord |
+ 	byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
+ 	loWord := memory at: byteAddress // 4 + 1.
+ 	hiWord := memory at: byteAddress // 4 + 2.
+ 	^hiWord = 0
+ 		ifTrue: [loWord]
+ 		ifFalse: [(hiWord bitShift: 32) + loWord]!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorLSB>>long64At:put: (in category 'memory access') -----
+ long64At: byteAddress put: a64BitValue
+ 	byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
+ 	self
+ 		longAt: byteAddress put: (a64BitValue bitAnd: 16rffffffff);
+ 		longAt: byteAddress + 4 put: a64BitValue >> 32.
+ 	^a64BitValue!

Item was added:
+ ----- Method: NewObjectMemorySimulatorLSB>>long64At: (in category 'memory access') -----
+ long64At: byteAddress
+ 	"memory is a Bitmap, a 32-bit indexable array of bits"
+ 	| hiWord loWord |
+ 	byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
+ 	loWord := memory at: byteAddress // 4 + 1.
+ 	hiWord := memory at: byteAddress // 4 + 2.
+ 	^hiWord = 0
+ 		ifTrue: [loWord]
+ 		ifFalse: [(hiWord bitShift: 32) + loWord]!

Item was added:
+ ----- Method: NewObjectMemorySimulatorLSB>>long64At:put: (in category 'memory access') -----
+ long64At: byteAddress put: a64BitValue
+ 	byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
+ 	self
+ 		longAt: byteAddress put: (a64BitValue bitAnd: 16rffffffff);
+ 		longAt: byteAddress + 4 put: a64BitValue >> 32.
+ 	^a64BitValue!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryConstOpVarInlinePrimitive: (in category 'inline primitive generators') -----
  genBinaryConstOpVarInlinePrimitive: prim
  	"Const op var version of binary inline primitives."
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#binaryInlinePrimitive:"
  	| ra val untaggedVal adjust |
  	ra := self allocateOneRegister.
  	self ssTop popToReg: ra.
  	self ssPop: 1.
  	val := self ssTop constant.
  	self ssPop: 1.
  	untaggedVal := val - objectMemory smallIntegerTag.
  	prim caseOf: {
  		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  		[0]	->	[self AddCq: untaggedVal R: ra].
  		[1]	->	[self MoveCq: val R: TempReg.
  				 self SubR: ra R: TempReg.
  				 objectRepresentation genAddSmallIntegerTagsTo: TempReg.
  				 self MoveR: TempReg R: ra].
  		[2]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ra.
  				 self MoveCq: (objectMemory integerValueOf: val) R: TempReg.
  				 self MulR: TempReg R: ra.
  				 objectRepresentation genAddSmallIntegerTagsTo: ra].
  
  		"2016 through 2019, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  
  		"2032	through 2037, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
  		"CmpCqR is SubRCq so everything is reversed, but because no CmpRCq things are reversed again and we invert the sense of the jumps."
  		[32] -> [ self CmpCq: val R: ra.
+ 				self genBinaryInlineComparison: JumpLess opFalse: JumpGreaterOrEqual destReg: ra ].
- 				self genBinaryInlineComparison: JumpLessOrEqual opFalse: JumpGreater destReg: ra ].
  		[33] -> [ self CmpCq: val R: ra.
+ 				self genBinaryInlineComparison: JumpGreater opFalse: JumpLessOrEqual destReg: ra ].
- 				self genBinaryInlineComparison: JumpGreaterOrEqual opFalse: JumpLess destReg: ra ].
  		[34] -> [ self CmpCq: val R: ra.
+ 				self genBinaryInlineComparison: JumpLessOrEqual opFalse: JumpGreater destReg: ra ].
- 				self genBinaryInlineComparison: JumpLess opFalse: JumpGreaterOrEqual destReg: ra ].
  		[35] -> [ self CmpCq: val R: ra.
+ 				self genBinaryInlineComparison: JumpGreaterOrEqual opFalse: JumpLess destReg: ra ].
- 				self genBinaryInlineComparison: JumpGreater opFalse: JumpLessOrEqual destReg: ra ].
  		[36] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpZero opFalse: JumpNonZero destReg: ra ].
  		[37] -> [ self CmpCq: val R: ra.
  				self genBinaryInlineComparison: JumpNonZero opFalse: JumpZero destReg: ra ].
  
  		"2064	through 2068, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
  		[64] ->	[objectRepresentation genConvertSmallIntegerToIntegerInReg: ra.
  				adjust := (objectMemory baseHeaderSize >> objectMemory shiftForWord) - 1. "shift by baseHeaderSize and then move from 1 relative to zero relative"
  				adjust ~= 0 ifTrue: [ self AddCq: adjust R: ra. ]. 
  				self annotate: (self MoveCw: val R: TempReg) objRef: val.
  				self MoveXwr: ra R: TempReg R: ra].
  		[65] ->	[objectRepresentation genConvertSmallIntegerToIntegerInReg: ra.
  				adjust := objectMemory baseHeaderSize - 1. "shift by baseHeaderSize and then move from 1 relative to zero relative"
  				self AddCq: adjust R: ra.
  				self annotate: (self MoveCw: val R: TempReg) objRef: val.
  				self MoveXbr: ra R: TempReg R: ra.
  				objectRepresentation genConvertIntegerToSmallIntegerInReg: ra]
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: ra.
  	^0!

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"
- 	"The abort sequencer has pushed the LinkReg a second time - because a stackoverflow 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. Sigh-  there has to be a simpler way.
- 	 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' 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>>genUpArrowReturn (in category 'bytecode generators') -----
  genUpArrowReturn
  	"Generate a method return from within a method or a block.
  	 Frameless method activation looks like
+ 	 CISCs (x86):
- 	for x86 - 
  				receiver
  				args
  		sp->	ret pc.
+ 	 RISCs (ARM):
- 	for ARM -
  				receiver
  				args
  				ret pc in LR.
+ 	 A fully framed activation is described in CoInterpreter class>initializeFrameIndices.
- 	A fully framed activation is described in CoInterpreter class>initializeFrameIndices.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
  	inBlock ifTrue:
  		[self assert: needsFrame. 
  		 self annotateBytecode: (self CallRT: ceNonLocalReturnTrampoline).
  		 ^0].
  	needsFrame
  		ifTrue:
  			[self MoveR: FPReg R: SPReg.
  			 self PopR: FPReg.
  			 backEnd hasLinkRegister ifTrue:
  				[self PopR: LinkReg].
  			 self RetN: methodOrBlockNumArgs + 1 * objectMemory wordSize]
  		ifFalse:
  			[self RetN: ((methodOrBlockNumArgs > self numRegArgs
  						"A method with an interpreter prim will push its register args for the prim.  If the failure
  						 body is frameless the args must still be popped, see e.g. Behavior>>nextInstance."
  						or: [regArgsHaveBeenPushed])
  							ifTrue: [methodOrBlockNumArgs + 1 * objectMemory wordSize]
  							ifFalse: [0])].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>initSimStackForFramelessMethod: (in category 'simulation stack') -----
  initSimStackForFramelessMethod: startpc
  	| desc |
  	<var: #desc type: #'CogSimStackEntry *'>
  	simSelf
  		type: SSRegister;
  		spilled: false;
  		annotateUse: false;
  		register: ReceiverResultReg.
  	optStatus
  		isReceiverResultRegLive: true;
  		ssEntry: (self addressOf: simSelf).
  	self assert: methodOrBlockNumTemps >= methodOrBlockNumArgs.
  	self assert: self numRegArgs <= 2.
  	(methodOrBlockNumArgs between: 1 and: self numRegArgs)
  		ifTrue:
  			[desc := self simStackAt: 0.
  			 desc
  				type: SSRegister;
  				spilled: false;
  				annotateUse: false;
  				register: Arg0Reg;
  				bcptr: startpc.
  			 methodOrBlockNumArgs > 1 ifTrue:
  				[desc := self simStackAt: 1.
  				 desc
  					type: SSRegister;
  					spilled: false;
  					annotateUse: false;
  					register: Arg1Reg;
  					bcptr: startpc]]
  		ifFalse:
  			[0 to: methodOrBlockNumArgs - 1 do:
  				[:i|
  				desc := self simStackAt: i.
  				desc
  					type: SSBaseOffset;
  					register: SPReg;
  					spilled: true;
  					annotateUse: false;
  					offset: ((backEnd hasLinkRegister
  								ifTrue: [methodOrBlockNumArgs - 1- i]
  								ifFalse: [methodOrBlockNumArgs - i]) * objectMemory wordSize);
  					bcptr: startpc]].
  	simSpillBase := simStackPtr := methodOrBlockNumArgs - 1!



More information about the Vm-dev mailing list