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

commits at source.squeak.org commits at source.squeak.org
Sun Jun 1 04:58:14 UTC 2014


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

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

Name: VMMaker.oscog-eem.741
Author: eem
Time: 31 May 2014, 9:54:06.933 pm
UUID: f73b1214-56e1-4dde-a466-bad10d979d17
Ancestors: VMMaker.oscog-eem.740

Refactor context creation in the Cogit, moving it to the
object representations.  In Spur allocate the context in one
of four trampolines for block vs method and large vs small
contexts.

Use smallObjectBytesForSlots: to determine byte size from
slot size in the new Spur Cogit allocators.

Fix simulation bug in whereIsMaybeStackThing:.

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

Item was added:
+ ----- Method: CoInterpreter>>methodNeedsLargeContext: (in category 'cog jit support') -----
+ methodNeedsLargeContext: methodObj
+ 	<api>
+ 	^(self headerOf: methodObj) anyMask: LargeContextBit!

Item was changed:
  ----- Method: CoInterpreterStackPages>>whereIsMaybeStackThing: (in category 'debug printing') -----
  whereIsMaybeStackThing: anOop
  	<returnTypeC: 'char *'>
  	(self oop: anOop
  		isGreaterThanOrEqualTo: (stackBasePlus1 - 1)
  		andLessThan: (self cCode: [pages]
+ 							inSmalltalk: [(self stackPageAt: 0) asUnsignedInteger])) ifTrue:
- 							inSmalltalk: [(self stackPageAt: 0)])) ifTrue:
  		[^' is in the stack zone'].
  	^nil!

Item was changed:
  CogClass subclass: #CogObjectRepresentation
  	instanceVariableNames: 'cogit methodZone objectMemory ceStoreCheckTrampoline'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
- 	poolDictionaries: 'CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices'
  	category: 'VMMaker-JIT'!
  
  !CogObjectRepresentation commentStamp: '<historical>' prior: 0!
  I am an abstract superclass for object representations whose job it is to generate abstract instructions for accessing objects.  It is hoped that this level of indirection between the Cogit code generator and object access makes it easier to adapt the code generator to different garbage collectors, object representations and languages.!

Item was added:
+ ----- Method: CogObjectRepresentation>>genGetActiveContextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
+ genGetActiveContextNumArgs: numArgs large: isLargeContext inBlock: isInBlock
+ 	"Get the active context into ReceiverResultReg, creating it if necessary."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>getActiveContextAllocatesInMachineCode (in category 'bytecode generator support') -----
+ getActiveContextAllocatesInMachineCode
+ 	"subclasses override if they want, and will have SendNumArgsReg and ClassReg
+ 	 available in addition to ReceiverResultReg and TempReg if they do."
+ 	^false!

Item was added:
+ ----- 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
+ 		MoveMw: FoxMethod r: FPReg R: TempReg;
+ 		MoveR: TempReg R: ClassReg;
+ 		AndCq: MFMethodFlagHasContextFlag R: TempReg.
+ 	jumpSingle := cogit JumpZero: 0.
+ 	cogit
+ 		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 cCoerceSimple: header to: #usqInt) 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 JumpGreaterOrEqual: 0.
+ 
+ 	"sender gets frame pointer as a SmallInteger"
+ 	continuation :=
+ 	cogit MoveR: FPReg R: TempReg.
+ 	self genSetSmallIntegerTagsIn: TempReg.
+ 	cogit MoveR: TempReg Mw: BaseHeaderSize + (SenderIndex * BytesPerOop) r: ReceiverResultReg.
+ 	"pc gets frame caller as a SmallInteger"
+ 	cogit MoveMw: FoxSavedFP r: FPReg R: TempReg.
+ 	self genSetSmallIntegerTagsIn: TempReg.
+ 	cogit MoveR: TempReg Mw: BaseHeaderSize + (InstructionPointerIndex * 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: BaseHeaderSize + (MethodIndex * BytesPerWord) 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)"
+ 	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: BaseHeaderSize + (StackPointerIndex * BytesPerOop) r: ReceiverResultReg.
+ 
+ 	"now initialize the fields of the new context, initializing stack with the current stack contents.
+ 	 See CoInterpreter>>marryFrame:SP:copyTemps:"
+ 	"Receiver[ClosureOrNil] := inBlock ifTrue: [longAt(FPReg + (SendNumArgs * BytesPerWord)] ifFalse: [nilObject].
+ 	 0 to: numArgs - 1 do:
+ 		[:i|
+ 		temp := longAt(FPReg + ((SendNumArgs - i) * BytesPerWord)).
+ 		longAtput(FPReg + FoxMFReceiver + (i * BytesPerWord), temp)]"
+ 	cogit MoveCq: 0 R: ClassReg.
+ 	isInBlock
+ 		ifTrue:
+ 			[cogit
+ 				MoveR: SendNumArgsReg R: TempReg;
+ 				AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
+ 				MoveXwr: TempReg R: FPReg R: TempReg]
+ 		ifFalse:
+ 			[cogit MoveCw: objectMemory nilObject R: TempReg].
+ 	cogit MoveR: TempReg Mw: BaseHeaderSize + (ClosureIndex * BytesPerWord) r: ReceiverResultReg.
+ 	loopHead := cogit CmpR: ClassReg R: SendNumArgsReg.
+ 	exit := cogit JumpGreaterOrEqual: 0.
+ 	cogit
+ 		MoveR: SendNumArgsReg R: TempReg;
+ 		SubR: ClassReg R: TempReg;
+ 		MoveXwr: TempReg R: FPReg R: TempReg;
+ 		AddCq: ReceiverIndex R: ClassReg;
+ 		MoveR: TempReg Xwr: ClassReg R: ReceiverResultReg;
+ 		SubCq: ReceiverIndex - 1 R: ClassReg; "add 1 ;-)"
+ 		Jump: loopHead.
+ 	exit jmpTarget: cogit Label.
+ 
+ 	"Initialize the receiver and the temps.  SendNumArgsReg is now free.
+ 	 ClassReg := FPReg + FoxMFReceiver.
+ 	 receiver[ReceiverIndex] := *ClassReg.
+ 	 SendNumArgsReg := SendNumArgsReg+ReceiverIndex.
+ 	 backEnd hasLinkRegister
+ 		ifTrue: [[ClassReg > SPReg] whileTrue: [receiver[SendNumArgsReg] := *ClassReg. ClassReg := ClassReg - 4. SendNumArgsReg := SendNumArgsReg + 1]]
+ 		ifFalse: [[ClassReg >= SPReg] whileTrue: [receiver[SendNumArgsReg] := *ClassReg. ClassReg := ClassReg - 4. SendNumArgsReg := SendNumArgsReg + 1]]"
+ 	cogit
+ 		MoveR: FPReg R: ClassReg;
+ 		AddCq: FoxMFReceiver R: ClassReg;
+ 		MoveMw: 0 r: ClassReg R: TempReg;
+ 		MoveR: TempReg Mw: BaseHeaderSize + (ReceiverIndex * BytesPerOop) r: ReceiverResultReg;
+ 		AddCq: ReceiverIndex + (BaseHeaderSize / BytesPerWord) + 1 R: SendNumArgsReg.
+ 	loopHead :=
+ 	cogit SubCq: BytesPerWord R: ClassReg.
+ 	cogit CmpR: SPReg R: ClassReg. "cogit CmpR: ClassReg R: SPReg."
+ 	exit := cogit backEnd hasLinkRegister
+ 				ifTrue: [cogit JumpLessOrEqual: 0]
+ 				ifFalse: [cogit JumpLess: 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 CallRT: ceSheduleScavengeTrampoline).
+ 	cogit Jump: continuation.
+ 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
  genNewArrayOfSize: size initialized: initialized
  	"Generate a call to code that allocates a new Array of size.
  	 The Array should be initialized with nils iff initialized is true.
  	 The size arg is passed in SendNumArgsReg, the result
  	 must come back in ReceiverResultReg."
+ 	| header skip |
- 	| header headerLow headerHigh byteSize skip |
  	<var: #skip type: #'AbstractInstruction *'>
  	self assert: size < objectMemory numSlotsMask.
  	header := objectMemory
  					headerForSlots: size
  					format: objectMemory arrayFormat
  					classIndex: ClassArrayCompactIndex.
- 	headerLow := self cCoerceSimple: header to: #usqInt.
- 	headerHigh := header >> 32.
- 	byteSize := (size max: 1) + 3 >> 1 * 8. "round up to 8 bytes and add 8 bytes of header"
  	self flag: #endianness.
  	cogit
  		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
+ 		MoveCq: (self cCoerceSimple: header to: #usqInt) R: TempReg;
- 		MoveCq: headerLow R: TempReg;
  		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
+ 		MoveCq: header >> 32 R: TempReg;
- 		MoveCq: headerHigh R: TempReg;
  		MoveR: TempReg Mw: 4 r: ReceiverResultReg.
  	(initialized and: [size > 0]) ifTrue:
  		[cogit MoveCw: objectMemory nilObject R: TempReg.
  		 1 to: size do:
  			[:i| cogit MoveR: TempReg Mw: i * 4 + 4 r: ReceiverResultReg]].
  	cogit
  		MoveR: ReceiverResultReg R: TempReg;
+ 		AddCq: (objectMemory smallObjectBytesForSlots: size) R: TempReg;
- 		AddCq: byteSize R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	skip := cogit JumpLess: 0.
  	cogit CallRT: ceSheduleScavengeTrampoline.
  	skip jmpTarget: cogit Label.
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>log2BytesPerWord (in category 'initialization') -----
+ log2BytesPerWord
+ 	^2!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>log2BytesPerWord (in category 'initialization') -----
+ log2BytesPerWord
+ 	^3!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSpur
+ 	instanceVariableNames: 'ceSheduleScavengeTrampoline ceSmallActiveContextInMethodTrampoline ceSmallActiveContextInBlockTrampoline ceLargeActiveContextInMethodTrampoline ceLargeActiveContextInBlockTrampoline'
- 	instanceVariableNames: 'ceSheduleScavengeTrampoline'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogCompilationConstants VMSqueakClassIndices VMSqueakV3BytecodeConstants'
- 	poolDictionaries: 'CogCompilationConstants VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genActiveContextTrampolineLarge:inBlock: (in category 'initialization') -----
+ genActiveContextTrampolineLarge: isLarge inBlock: isBlock
+ 	"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."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genActiveContextTrampolineLarge:inBlock:called: (in category 'initialization') -----
+ genActiveContextTrampolineLarge: isLarge inBlock: isInBlock called: aString
+ 	"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."
+ 	| startAddress |
+ 	startAddress := cogit methodZoneBase.
+ 	cogit zeroOpcodeIndex.
+ 	self genGetActiveContextLarge: isLarge inBlock: isInBlock.
+ 	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	cogit recordGeneratedRunTime: aString address: startAddress.
+ 	cogit recordRunTimeObjectReferences.
+ 	^startAddress!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genGetActiveContextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
+ genGetActiveContextNumArgs: numArgs large: isLargeContext inBlock: isInBlock
+ 	"Get the active context into ReceiverResultReg, creating it if necessary."
+ 	| routine |
+ 	routine := isLargeContext
+ 				ifFalse: [isInBlock
+ 							ifFalse: [ceSmallActiveContextInMethodTrampoline]
+ 							ifTrue: [ceSmallActiveContextInBlockTrampoline]]
+ 				ifTrue: [isInBlock
+ 							ifFalse: [ceLargeActiveContextInMethodTrampoline]
+ 							ifTrue: [ceLargeActiveContextInBlockTrampoline]].
+ 	cogit
+ 		MoveCq: numArgs R: SendNumArgsReg;
+ 		CallRT: routine.
+ 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>generateObjectRepresentationTrampolines (in category 'initialization') -----
  generateObjectRepresentationTrampolines
  	super generateObjectRepresentationTrampolines.
  	ceSheduleScavengeTrampoline := cogit
  											genSafeTrampolineFor: #ceSheduleScavenge
+ 											called: 'ceSheduleScavengeTrampoline'.
+ 	ceSmallActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: false inBlock: false called: 'ceSmallMethodContext'.
+ 	ceSmallActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: false inBlock: true called: 'ceSmallBlockContext'.
+ 	ceLargeActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: true inBlock: false called: 'ceLargeMethodContext'.
+ 	ceLargeActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: true inBlock: true called: 'ceLargeBlockContext'!
- 											called: 'ceSheduleScavengeTrampoline'!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>getActiveContextAllocatesInMachineCode (in category 'bytecode generator support') -----
+ getActiveContextAllocatesInMachineCode
+ 	"Make sure SendNumArgsReg and ClassReg are available in addition to
+ 	 ReceiverResultReg and TempReg in genGetActiveContextNumArgs:large:inBlock:."
+ 	^true!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSqueakV3
+ 	instanceVariableNames: 'ceCreateNewArrayTrampoline cePositive32BitIntegerTrampoline ceActiveContextTrampoline'
- 	instanceVariableNames: 'ceCreateNewArrayTrampoline cePositive32BitIntegerTrampoline'
  	classVariableNames: 'RootBitDigitLength'
  	poolDictionaries: 'VMSqueakClassIndices VMSqueakV3ObjectRepresentationConstants'
  	category: 'VMMaker-JIT'!
  
  !CogObjectRepresentationForSqueakV3 commentStamp: '<historical>' prior: 0!
  Read my superclass' class comment.  I am a CogObjectRepresentation for the Squeak V3 object representation.!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genActiveContextTrampoline (in category 'initialization') -----
+ genActiveContextTrampoline
+ 	"Short-circuit the interpreter call if a frame is already married."
+ 	| jumpSingle |
+ 	<var: #jumpSingle type: #'AbstractInstruction *'>
+ 	cogit
+ 		zeroOpcodeIndex;
+ 		MoveMw: FoxMethod r: FPReg R: TempReg;
+ 		AndCq: MFMethodFlagHasContextFlag R: TempReg.
+ 	jumpSingle := cogit JumpZero: 0.
+ 	cogit
+ 		MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
+ 		RetN: 0.
+ 	jumpSingle jmpTarget: cogit Label.
+ 	^cogit genTrampolineFor: #ceActiveContext
+ 		called: 'ceActiveContextTrampoline'
+ 		callJumpBar: true
+ 		numArgs: 0
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		saveRegs: false
+ 		resultReg: ReceiverResultReg
+ 		appendOpcodes: true!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genGetActiveContextNumArgs:large:inBlock: (in category 'bytecode generator support') -----
+ genGetActiveContextNumArgs: numArgs large: isLargeContext inBlock: isInBlock
+ 	"Get the active context into ReceiverResultReg, creating it if necessary."
+ 	cogit CallRT: ceActiveContextTrampoline!

Item was changed:
+ ----- Method: CogObjectRepresentationForSqueakV3>>generateObjectRepresentationTrampolines (in category 'initialization') -----
- ----- Method: CogObjectRepresentationForSqueakV3>>generateObjectRepresentationTrampolines (in category 'in-line cacheing') -----
  generateObjectRepresentationTrampolines
  	super generateObjectRepresentationTrampolines.
  	ceCreateNewArrayTrampoline := cogit genTrampolineFor: #ceNewArraySlotSize:
  											called: 'ceCreateNewArrayTrampoline'
  											arg: SendNumArgsReg
  											result: ReceiverResultReg.
  	cePositive32BitIntegerTrampoline := cogit genTrampolineFor: #cePositive32BitIntegerFor:
  											called: 'cePositive32BitIntegerTrampoline'
  											arg: ReceiverResultReg
+ 											result: TempReg.
+ 	ceActiveContextTrampoline := self genActiveContextTrampoline!
- 											result: TempReg!

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

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

Item was added:
+ ----- Method: Cogit>>backEnd (in category 'trampoline support') -----
+ backEnd
+ 	<cmacro: '() backEnd'>
+ 	^backEnd!

Item was removed:
- ----- Method: Cogit>>genActiveContextTrampoline (in category 'initialization') -----
- genActiveContextTrampoline
- 	"Short-circuit the interpreter call if a frame is already married."
- 	| jumpSingle |
- 	<var: #jumpSingle type: #'AbstractInstruction *'>
- 	opcodeIndex := 0.
- 	self MoveMw: FoxMethod r: FPReg R: TempReg.
- 	self AndCq: MFMethodFlagHasContextFlag R: TempReg.
- 	jumpSingle := self JumpZero: 0.
- 	self MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	jumpSingle jmpTarget: self Label.
- 	^self genTrampolineFor: #ceActiveContext
- 		called: 'ceActiveContextTrampoline'
- 		callJumpBar: true
- 		numArgs: 0
- 		arg: nil
- 		arg: nil
- 		arg: nil
- 		arg: nil
- 		saveRegs: false
- 		resultReg: ReceiverResultReg
- 		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>generateRunTimeTrampolines (in category 'initialization') -----
  generateRunTimeTrampolines
  	"Generate the run-time entries at the base of the native code zone and update the base."
  	
  	ceSendMustBeBooleanAddFalseTrampoline := self genMustBeBooleanTrampolineFor: objectMemory falseObject
  														called: 'ceSendMustBeBooleanAddFalseTrampoline'.
  	ceSendMustBeBooleanAddTrueTrampoline := self genMustBeBooleanTrampolineFor: objectMemory trueObject
  														called: 'ceSendMustBeBooleanAddTrueTrampoline'.
  	ceClosureCopyTrampoline := self genTrampolineFor: #ceClosureCopyDescriptor:
  									called: 'ceClosureCopyTrampoline'
  									arg: SendNumArgsReg
  									result: ReceiverResultReg.
- 	ceActiveContextTrampoline := self genActiveContextTrampoline.
  	ceNonLocalReturnTrampoline := self genNonLocalReturnTrampoline.
  	ceBaseFrameReturnTrampoline := self genTrampolineFor: #ceBaseFrameReturn:
  										called: 'ceBaseFrameReturnTrampoline'
  										arg: ReceiverResultReg.
  	ceCheckForInterruptTrampoline := self genCheckForInterruptsTrampoline.
  	ceFetchContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:
  											called: 'ceFetchContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											result: SendNumArgsReg.
  	ceStoreContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:value:
  											called: 'ceStoreContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											arg: ClassReg
  											result: ReceiverResultReg. "to keep ReceiverResultReg live."
  	ceReturnToInterpreterTrampoline := self genTrampolineFor: #ceReturnToInterpreter:
  											called: 'ceReturnToInterpreterTrampoline'
  											arg: ReceiverResultReg.
  	ceCannotResumeTrampoline := self genTrampolineFor: #ceCannotResume
  											called: 'ceCannotResumeTrampoline'!

Item was changed:
  ----- Method: Cogit>>generateTrampolines (in category 'initialization') -----
  generateTrampolines
  	"Generate the run-time entries and exits at the base of the native code zone and update the base.
  	 Read the class-side method trampolines for documentation on the various trampolines"
  	| methodZoneStart |
  	methodZoneStart := methodZoneBase.
+ 	self allocateOpcodes: 72 bytecodes: 0.
- 	self allocateOpcodes: 42 bytecodes: 0.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	hasYoungReferent := false.
  	self generateSendTrampolines.
  	self generateMissAbortTrampolines.
  	objectRepresentation generateObjectRepresentationTrampolines.
  	self generateRunTimeTrampolines.
  	self cppIf: NewspeakVM ifTrue: 	[self generateNewspeakRuntime].
  	self generateEnilopmarts.
  	self generateTracingTrampolines.
  
  	"finish up"
  	self recordGeneratedRunTime: 'methodZoneBase' address: methodZoneBase.
  	processor flushICacheFrom: methodZoneStart to: methodZoneBase.
  	self cCode: ''
  		inSmalltalk:
  			[simulatedTrampolines keysAndValuesDo:
  				[:addr :selector|
  				simulatedTrampolines
  					at: addr
  					put: (MessageSend
  							receiver: ((self respondsTo: selector)
  										ifTrue: [self]
  										ifFalse: [(coInterpreter respondsTo: selector)
  													ifTrue: [coInterpreter]
  													ifFalse: [(objectMemory respondsTo: selector)
  														ifTrue: [objectMemory]
  														ifFalse: [self notify: 'cannot find receiver for ', selector]]])
  							selector: selector
  							arguments: (1 to: selector numArgs) asArray)]]!

Item was added:
+ ----- Method: Cogit>>methodZoneBase (in category 'trampoline support') -----
+ methodZoneBase
+ 	<cmacro: '() methodZoneBase'>
+ 	^methodZoneBase!

Item was added:
+ ----- Method: Cogit>>zeroOpcodeIndex (in category 'accessing') -----
+ zeroOpcodeIndex
+ 	"Access for the object representations when they need to prepend code to trampolines."
+ 	opcodeIndex := 0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushActiveContextBytecode (in category 'bytecode generators') -----
  genPushActiveContextBytecode
  	self assert: needsFrame.
+ 	objectRepresentation
+ 		genGetActiveContextNumArgs: methodOrBlockNumArgs
+ 		large: (coInterpreter methodNeedsLargeContext: methodObj)
+ 		inBlock: inBlock.
- 	self CallRT: ceActiveContextTrampoline.
  	self PushR: ReceiverResultReg.
  	^0!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>freeStart (in category 'accessing') -----
+ freeStart
+ 	"freeStart = 16r1BDFF8 ifTrue: [self halt]."
+ 	^super freeStart!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>smallObjectBytesForSlots: (in category 'allocation') -----
  smallObjectBytesForSlots: numSlots
  	"Answer the total number of bytes in an object without an overflow header, including header bytes."
+ 	<api>
  	^self baseHeaderSize "single header"
  	+ (numSlots <= 1
  		ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  		ifFalse: [numSlots + (numSlots bitAnd: 1) * self bytesPerSlot]) "round up to allocationUnit"!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushActiveContextBytecode (in category 'bytecode generators') -----
  genPushActiveContextBytecode
  	self assert: needsFrame.
  	optStatus isReceiverResultRegLive: false.
+ 	objectRepresentation getActiveContextAllocatesInMachineCode
+ 		ifTrue: [self ssAllocateCallReg: ReceiverResultReg
+ 					and: SendNumArgsReg
+ 					and: ClassReg]
+ 		ifFalse: [self ssAllocateCallReg: ReceiverResultReg].
+ 	objectRepresentation
+ 		genGetActiveContextNumArgs: methodOrBlockNumArgs
+ 		large: (coInterpreter methodNeedsLargeContext: methodObj)
+ 		inBlock: inBlock.
- 	self ssAllocateCallReg: ReceiverResultReg.
- 	self CallRT: ceActiveContextTrampoline.
  	^self ssPushRegister: ReceiverResultReg!



More information about the Vm-dev mailing list