[Vm-dev] VM Maker: VMMaker.oscog-cb.1748.mcz

Eliot Miranda eliot.miranda at gmail.com
Wed Mar 30 21:31:52 UTC 2016


Hi Clément,

On Wed, Mar 30, 2016 at 7:32 AM, Clément Bera <bera.clement at gmail.com>
wrote:

>
> It saves 2 bytes for inst var 0 and 5 bytes for inst var between 1 and 255
> in x86. There is one less branch to take on the common path too. Not sure
> if this matters a lot. The difference should be better on x64 as in x86
> MoveCq:R: calls MoveCw:R: if the quick constant is not 0, and we have many
> little constants more than 0.
>
> Isn't there a better way to move quick constant to register on x86 than
> the full word constant ? Maybe we should change MoveCq:R: on x86 to do
> a xor reg,reg, movq r8 as suggested in the comment.
>

It only saves a single byte because the xor to clear the register is 2
bytes and the byte move is 2 bytes so because it saves only a single byte I
haven't bothered.  It makes more difference on x64 where the xor is 3 bytes
and the full move 10, so xor followed by a 5 byte 32-bit move is 7 bytes,
saving 3, for a 30% saving.  I also wonder whether the two byte sequence is
slower on any x86 incarnations.

2016-03-30 15:52 GMT+02:00 <commits at source.squeak.org>:
>
>>
>> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
>> http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1748.mcz
>>
>> ==================== Summary ====================
>>
>> Name: VMMaker.oscog-cb.1748
>> Author: cb
>> Time: 30 March 2016, 3:52:01.732 pm
>> UUID: db420bcd-e4aa-4cad-9543-047274e49915
>> Ancestors: VMMaker.oscog-nice.1747
>>
>> Reworked machine code generation of immutability so for common stores it
>> uses a single trampoline for both store checks and immutability checks.
>>
>> I have simulation bug due to large integers, so I am not entirely sure
>> everything is working, but generated code looks good.
>>
>> =============== Diff against VMMaker.oscog-nice.1747 ===============
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentation>>genStoreSourceReg:slotIndex:destReg:scratchReg:inFrame:
>> (in category 'compile abstract instructions') -----
>>   genStoreSourceReg: sourceReg slotIndex: index destReg: destReg
>> scratchReg: scratchReg inFrame: inFrame
>> +       <inline: true>
>> +       self
>> +               cppIf: IMMUTABILITY
>> +               ifTrue:
>> +                       [ ^ self
>> +                               genStoreWithImmutabilityCheckSourceReg:
>> sourceReg
>> +                               slotIndex: index
>> +                               destReg: destReg
>> +                               scratchReg: scratchReg
>> +                               needsStoreCheck: true
>> +                               needRestoreRcvr: false "RcvrResultReg
>> doesn't need to be live across the instructions" ]
>> +               ifFalse:
>> +                       [ ^ self
>> +                               genStoreSourceReg: sourceReg
>> +                               slotIndex: index
>> +                               destReg: destReg
>> +                               scratchReg: scratchReg
>> +                               inFrame: inFrame
>> +                               needsStoreCheck: true ]!
>> -       ^ self
>> -               genStoreSourceReg: sourceReg
>> -               slotIndex: index
>> -               destReg: destReg
>> -               scratchReg: scratchReg
>> -               inFrame: inFrame
>> -               needsStoreCheck: true!
>>
>> Item was changed:
>>   CogObjectRepresentation subclass: #CogObjectRepresentationForSpur
>> +       instanceVariableNames: 'ceScheduleScavengeTrampoline
>> ceSmallActiveContextInMethodTrampoline
>> ceSmallActiveContextInBlockTrampoline
>> ceLargeActiveContextInMethodTrampoline
>> ceLargeActiveContextInBlockTrampoline ceStoreCheckContextReceiverTrampoline
>> ceStoreTrampoline'
>> -       instanceVariableNames: 'ceScheduleScavengeTrampoline
>> ceSmallActiveContextInMethodTrampoline
>> ceSmallActiveContextInBlockTrampoline
>> ceLargeActiveContextInMethodTrampoline
>> ceLargeActiveContextInBlockTrampoline ceStoreCheckContextReceiverTrampoline
>> ceCannotAssignToWithIndexTrampoline'
>>         classVariableNames: ''
>>         poolDictionaries: 'VMBytecodeConstants VMSqueakClassIndices'
>>         category: 'VMMaker-JIT'!
>>
>> Item was removed:
>> - ----- Method:
>> CogObjectRepresentationForSpur>>genImmutableCheck:slotIndex:sourceReg:scratchReg:needRestoreRcvr:
>> (in category 'compile abstract instructions') -----
>> - genImmutableCheck: regHoldingObjectMutated slotIndex: index sourceReg:
>> regHoldingValueToStore scratchReg: scratchReg needRestoreRcvr:
>> needRestoreRcvr
>> -       | mutableJump fail |
>> -       <var: #mutableJump type: #'AbstractInstruction *'>
>> -       <var: #fail type: #'AbstractInstruction *'>
>> -       <inline: true>
>> -       <option: #IMMUTABILITY>
>> -       "Trampoline convention:
>> -       - objectMutated passed in ReceiverResultReg
>> -       - index (unboxed) passed in TempReg
>> -       - valueToStore passed in ClassReg.
>> -       Simulated stack is flushed, but if needRestoreRcvr is true
>> -       the receiver has to be live after this operation."
>> -       self assert: regHoldingObjectMutated == ReceiverResultReg.
>> -       self assert: scratchReg == TempReg.
>> -       self assert: regHoldingValueToStore == ClassReg.
>> -       mutableJump := self genJumpMutable: ReceiverResultReg scratchReg:
>> TempReg.
>> -
>> -       "We reach this code if the object mutated is immutable."
>> -       cogit MoveCq: index R: TempReg.
>> -       "trampoline call and mcpc to bcpc annotation."
>> -       cogit CallRT: ceCannotAssignToWithIndexTrampoline.
>> -       cogit annotateBytecode: cogit Label.
>> -       "restore ReceiverResultReg state if needed, the rest of the state
>> is spilled"
>> -       needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
>> -       fail := cogit Jump: 0.
>> -
>> -       "We reach this code is the object mutated is mutable"
>> -       mutableJump jmpTarget: cogit Label.
>> -
>> -       ^ fail!
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentationForSpur>>genJumpBaseHeaderImmutable: (in category
>> 'compile abstract instructions') -----
>>   genJumpBaseHeaderImmutable: baseHeaderReg
>>         "baseHeader holds at least the least significant 32 bits of the
>> object"
>>         <returnTypeC: #'AbstractInstruction *'>
>>         <option: #IMMUTABILITY>
>> +       <inline: true>
>>         cogit TstCq: objectMemory immutableBitMask R: baseHeaderReg.
>>         ^ cogit JumpNonZero: 0!
>>
>> Item was changed:
>>   ----- Method: CogObjectRepresentationForSpur>>genJumpBaseHeaderMutable:
>> (in category 'compile abstract instructions') -----
>>   genJumpBaseHeaderMutable: baseHeaderReg
>>         "baseHeader holds at least the least significant 32 bits of the
>> object"
>>         <returnTypeC: #'AbstractInstruction *'>
>>         <option: #IMMUTABILITY>
>> +       <inline: true>
>>         cogit TstCq: objectMemory immutableBitMask R: baseHeaderReg.
>>         ^ cogit JumpZero: 0!
>>
>> Item was added:
>> + ----- Method:
>> CogObjectRepresentationForSpur>>genJumpImmutable:scratchReg: (in category
>> 'compile abstract instructions') -----
>> + genJumpImmutable: sourceReg scratchReg: scratchReg
>> +       <returnTypeC: #'AbstractInstruction *'>
>> +       <option: #IMMUTABILITY>
>> +       cogit MoveMw: 0 r: sourceReg R: scratchReg.
>> +       ^ self genJumpBaseHeaderImmutable: scratchReg!
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentationForSpur>>genStoreSourceReg:slotIndex:destReg:scratchReg:inFrame:needsStoreCheck:
>> (in category 'compile abstract instructions') -----
>>   genStoreSourceReg: sourceReg slotIndex: index destReg: destReg
>> scratchReg: scratchReg inFrame: inFrame needsStoreCheck: needsStoreCheck
>> +
>> +       cogit genTraceStores.
>>         "do the store"
>>         cogit MoveR: sourceReg
>>                    Mw: index * objectMemory wordSize + objectMemory
>> baseHeaderSize
>>                    r: destReg.
>>         "now the check. needStoreCheck is false if the JIT has figured
>> out that the value stored does not need the check (immediate, nil, true,
>> false)"
>>         needsStoreCheck ifTrue:
>>                 [ ^ self
>>                         genStoreCheckReceiverReg: destReg
>>                         valueReg: sourceReg
>>                         scratchReg: scratchReg
>>                         inFrame: inFrame ].
>>         ^ 0!
>>
>> Item was added:
>> + ----- Method: CogObjectRepresentationForSpur>>genStoreTrampolineCalled:
>> (in category 'initialization') -----
>> + genStoreTrampolineCalled: trampolineName
>> +       "This can be entered in one of two states, depending on TempReg.
>> +       TempReg = 0 => store check
>> +       TempReg > 0 => immutability failure
>> +       TempReg holds index + 1 in this case as the value 0 is reserved
>> for store checks.
>> +       In addition the 0 value is convenient to save one instruction for
>> store checks."
>> +       | jumpSC |
>> +       <var: #trampolineName type: #'char *'>
>> +       <var: #jumpSC type: #'AbstractInstruction *'>
>> +       <inline: false>
>> +       cogit zeroOpcodeIndex.
>> +       cogit CmpCq: 0 R: TempReg.
>> +       jumpSC := cogit JumpZero: 0.
>> +
>> +       "CannotAssignTo:, we restore the index."
>> +       cogit SubCq: 1 R: TempReg.
>> +       cogit
>> +               compileTrampolineFor:
>> #ceCannotAssignTo:withIndex:valueToAssign:
>> +               numArgs: 3
>> +               arg: ReceiverResultReg
>> +               arg: TempReg
>> +               arg: ClassReg
>> +               arg: nil
>> +               regsToSave: cogit emptyRegisterMask
>> +               pushLinkReg: true
>> +               resultReg: NoReg.
>> +
>> +       "Store check"
>> +       jumpSC jmpTarget: cogit Label.
>> +       ^ cogit genTrampolineFor: #remember:
>> +               called: trampolineName
>> +               numArgs: 1
>> +               arg: ReceiverResultReg
>> +               arg: nil
>> +               arg: nil
>> +               arg: nil
>> +               regsToSave: cogit emptyRegisterMask
>> +               pushLinkReg: true
>> +               resultReg: NoReg
>> +               appendOpcodes: true!
>>
>> Item was added:
>> + ----- Method:
>> CogObjectRepresentationForSpur>>genStoreWithImmutabilityAndStoreCheckSourceReg:slotIndex:destReg:scratchReg:needRestoreRcvr:
>> (in category 'compile abstract instructions') -----
>> + genStoreWithImmutabilityAndStoreCheckSourceReg: sourceReg slotIndex:
>> index destReg: destReg scratchReg: scratchReg needRestoreRcvr:
>> needRestoreRcvr
>> +       "Store check code is duplicated to use a single trampoline"
>> +       <var: #immutableJump type: #'AbstractInstruction *'>
>> +       <var: #trampJump type: #'AbstractInstruction *'>
>> +       <var: #jmpImmediate type: #'AbstractInstruction *'>
>> +       <var: #jmpDestYoung type: #'AbstractInstruction *'>
>> +       <var: #jmpSourceOld type: #'AbstractInstruction *'>
>> +       <var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
>> +       | immutableJump trampJump jmpImmediate jmpDestYoung jmpSourceOld
>> rememberedBitByteOffset jmpAlreadyRemembered mask |
>> +
>> +       immutableJump := self genJumpImmutable: destReg scratchReg:
>> scratchReg.
>> +
>> +       cogit genTraceStores.
>> +
>> +       "do the store"
>> +       cogit MoveR: sourceReg
>> +                  Mw: index * objectMemory wordSize + objectMemory
>> baseHeaderSize
>> +                  r: destReg.
>> +
>> +       "store check"
>> +       jmpImmediate := self genJumpImmediate: sourceReg.
>> +       "Get the old/new boundary in scratchReg"
>> +       cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
>> +       "Is target young?  If so we're done"
>> +       cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg -
>> scratchReg"
>> +       jmpDestYoung := cogit JumpBelow: 0.
>> +       "Is value stored old?  If so we're done."
>> +       cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := valueReg -
>> scratchReg"
>> +       jmpSourceOld := cogit JumpAboveOrEqual: 0.
>> +       "value is young and target is old.
>> +        Need to remember this only if the remembered bit is not already
>> set.
>> +        Test the remembered bit.  Only need to fetch the byte containing
>> it,
>> +        which reduces the size of the mask constant."
>> +       rememberedBitByteOffset := jmpSourceOld isBigEndian
>> +
>>  ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory
>> rememberedBitShift // 8)]
>> +
>>  ifFalse:[objectMemory rememberedBitShift // 8].
>> +       mask := 1 << (objectMemory rememberedBitShift \\ 8).
>> +       cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
>> +       cogit AndCq: mask R: scratchReg.
>> +       jmpAlreadyRemembered := cogit JumpNonZero: 0.
>> +       "We know scratchReg now holds 0, this is convenient because the
>> trampoline
>> +       convention expects 0 for store check in scratchReg. What a
>> coincidence ;-)"
>> +       "Remembered bit is not set.  Call store check to insert dest into
>> remembered table."
>> +       trampJump := cogit Jump: 0.
>> +       "Here we reach the trampoline for Immutability failure"
>> +       immutableJump jmpTarget: (cogit MoveCq: index + 1 R: scratchReg).
>> "index + 1 as 0 is reserved for store checks"
>> +       trampJump jmpTarget: (cogit CallRT: ceStoreTrampoline).
>> +       cogit annotateBytecode: cogit Label.
>> +       needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
>> +
>> +       jmpImmediate jmpTarget:
>> +       (jmpDestYoung jmpTarget:
>> +       (jmpSourceOld jmpTarget:
>> +       (jmpAlreadyRemembered jmpTarget:
>> +               cogit Label))).
>> +
>> +       ^ 0!
>>
>> Item was added:
>> + ----- Method:
>> CogObjectRepresentationForSpur>>genStoreWithImmutabilityButNoStoreCheckSourceReg:slotIndex:destReg:scratchReg:needRestoreRcvr:
>> (in category 'compile abstract instructions') -----
>> + genStoreWithImmutabilityButNoStoreCheckSourceReg: sourceReg slotIndex:
>> index destReg: destReg scratchReg: scratchReg needRestoreRcvr:
>> needRestoreRcvr
>> +
>> +       <var: #immutableJump type: #'AbstractInstruction *'>
>> +       <var: #immutabilityFailure type: #'AbstractInstruction *'>
>> +       | immutabilityFailure mutableJump |
>> +
>> +       "imm check has its own trampoline"
>> +       mutableJump := self genJumpMutable: destReg scratchReg:
>> scratchReg.
>> +       cogit MoveCq: index + 1 R: TempReg. "index + 1 as 0 is reserved
>> for store checks"
>> +       cogit CallRT: ceStoreTrampoline.
>> +       cogit annotateBytecode: cogit Label.
>> +       needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
>> +       immutabilityFailure := cogit Jump: 0.
>> +       mutableJump jmpTarget: cogit Label.
>> +
>> +       cogit genTraceStores.
>> +
>> +       "do the store"
>> +       cogit MoveR: sourceReg
>> +                  Mw: index * objectMemory wordSize + objectMemory
>> baseHeaderSize
>> +                  r: destReg.
>> +
>> +       immutabilityFailure jmpTarget: cogit Label.
>> +
>> +       ^ 0!
>>
>> Item was added:
>> + ----- Method:
>> CogObjectRepresentationForSpur>>genStoreWithImmutabilityCheckSourceReg:slotIndex:destReg:scratchReg:needsStoreCheck:needRestoreRcvr:
>> (in category 'compile abstract instructions') -----
>> + genStoreWithImmutabilityCheckSourceReg: sourceReg slotIndex: index
>> destReg: destReg scratchReg: scratchReg needsStoreCheck: needsStoreCheck
>> needRestoreRcvr: needRestoreRcvr
>> +       "We know there is a frame as immutability check requires a frame"
>> +       "needRestoreRcvr has to be true to keep RcvrResultReg live with
>> the receiver in it across the trampoline"
>> +
>> +       "Trampoline convention..."
>> +       self assert: destReg == ReceiverResultReg.
>> +       self assert: scratchReg == TempReg.
>> +       self assert: sourceReg == ClassReg.
>> +
>> +       needsStoreCheck
>> +               ifTrue:
>> +                       [ self
>> +
>>  genStoreWithImmutabilityAndStoreCheckSourceReg: sourceReg
>> +                               slotIndex: index
>> +                               destReg: destReg
>> +                               scratchReg: scratchReg
>> +                               needRestoreRcvr: needRestoreRcvr ]
>> +               ifFalse:
>> +                       [ self
>> +
>>  genStoreWithImmutabilityButNoStoreCheckSourceReg: sourceReg
>> +                               slotIndex: index
>> +                               destReg: destReg
>> +                               scratchReg: scratchReg
>> +                               needRestoreRcvr: needRestoreRcvr ].
>> +       ^ 0!
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentationForSpur>>generateObjectRepresentationTrampolines (in
>> category 'initialization') -----
>>   generateObjectRepresentationTrampolines
>>         "Do the store check.  Answer the argument for the benefit of the
>> code generator;
>>          ReceiverResultReg may be caller-saved and hence smashed by this
>> call.  Answering
>>          it allows the code generator to reload ReceiverResultReg cheaply.
>>          In Spur the only thing we leave to the run-time is adding the
>> receiver to the
>>          remembered set and setting its isRemembered bit."
>>         self
>>                 cppIf: IMMUTABILITY
>> +               ifTrue: [ceStoreTrampoline := self
>> genStoreTrampolineCalled: 'ceStoreTrampoline'].
>> -               ifTrue: "c.f.
>> genImmutableCheck:slotIndex:sourceReg:scratchReg:popBoolean:needRestoreRcvr:"
>> -                       [ceCannotAssignToWithIndexTrampoline := cogit
>> -
>>                                                genTrampolineFor:
>> #ceCannotAssignTo:withIndex:valueToAssign:
>> -
>>                                                called:
>> 'ceCannotAssignToWithIndexTrampoline'
>> -
>>                                                arg: ReceiverResultReg
>> -
>>                                                arg: TempReg
>> -
>>                                                arg: ClassReg].
>>         ceStoreCheckTrampoline := cogit
>>
>> genTrampolineFor: #remember:
>>
>> called: 'ceStoreCheckTrampoline'
>>
>> arg: ReceiverResultReg
>>
>> regsToSave: (cogit callerSavedRegMask bitClear: (cogit registerMaskFor:
>> ReceiverResultReg))
>>
>> result: cogit returnRegForStoreCheck.
>>         ceStoreCheckContextReceiverTrampoline := self
>> genStoreCheckContextReceiverTrampoline.
>>         ceScheduleScavengeTrampoline := cogit
>>
>>               genTrampolineFor: #ceScheduleScavenge
>>
>>               called: 'ceScheduleScavengeTrampoline'
>>
>>               regsToSave: cogit callerSavedRegMask.
>>         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'!
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentationForSqueakV3>>genStoreSourceReg:slotIndex:destReg:scratchReg:inFrame:needsStoreCheck:
>> (in category 'compile abstract instructions') -----
>>   genStoreSourceReg: sourceReg slotIndex: index destReg: destReg
>> scratchReg: scratchReg inFrame: inFrame needsStoreCheck: needsStoreCheck
>>         | jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRoot mask
>> rootBitByteOffset |
>>         <var: #jmpImmediate type: #'AbstractInstruction *'>
>>         <var: #jmpDestYoung type: #'AbstractInstruction *'>
>>         <var: #jmpSourceOld type: #'AbstractInstruction *'>
>>         <var: #jmpAlreadyRoot type: #'AbstractInstruction *'>
>> +
>> +       cogit genTraceStores.
>>         "do the store"
>>         cogit MoveR: sourceReg Mw: index * objectMemory wordSize +
>> objectMemory baseHeaderSize r: destReg.
>>         "if no need for the store check then returns"
>>         needsStoreCheck ifFalse: [ ^ 0 ].
>>         "now the check.  Is value stored an integer?  If so we're done"
>>         jmpImmediate := self genJumpImmediate: sourceReg.
>>         "Get the old/new boundary in scratchReg"
>>         cogit MoveAw: objectMemory youngStartAddress R: scratchReg.
>>         "Is target young?  If so we're done"
>>         cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg -
>> scratchReg"
>>         jmpDestYoung := cogit JumpAboveOrEqual: 0.
>>         "Is value stored old?  If so we're done."
>>         cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := sourceReg -
>> scratchReg"
>>         jmpSourceOld := cogit JumpBelow: 0.
>>         "value is young and target is old.
>>          Need to make this a root if the root bit is not already set.
>>          Test the root bit.  Only need to fetch the byte containing it,
>>          which reduces the size of the mask constant."
>>         rootBitByteOffset := jmpSourceOld isBigEndian
>>                                                         ifTrue:
>> [objectMemory wordSize - RootBitDigitLength]
>>
>> ifFalse:[RootBitDigitLength - 1].
>>         mask := RootBitDigitLength > 1
>>                                 ifTrue: [RootBit >> (RootBitDigitLength -
>> 1 * 8)]
>>                                 ifFalse: [RootBit].
>>         cogit MoveMb: rootBitByteOffset r: destReg R: scratchReg.
>>         cogit AndCq: mask R: scratchReg.
>>         jmpAlreadyRoot := cogit JumpNonZero: 0.
>>         "Root bit is not set.  Call store check to insert dest into root
>> table."
>>         self assert: destReg == ReceiverResultReg.
>>         cogit
>>                 evaluateTrampolineCallBlock: [cogit CallRT:
>> ceStoreCheckTrampoline]
>>                 protectLinkRegIfNot: inFrame.
>>         jmpImmediate jmpTarget:
>>         (jmpDestYoung jmpTarget:
>>         (jmpSourceOld jmpTarget:
>>         (jmpAlreadyRoot jmpTarget:
>>                 cogit Label))).
>>         ^0!
>>
>> Item was changed:
>>   ----- Method: SimpleStackBasedCogit>>genStorePop:LiteralVariable: (in
>> category 'bytecode generator support') -----
>>   genStorePop: popBoolean LiteralVariable: litVarIndex
>>         <inline: false>
>> +       | association |
>> -       | association immutabilityFailure |
>> -       <var: #immutabilityFailure type: #'AbstractInstruction *'>
>>         "The only reason we assert needsFrame here is that in a frameless
>> method
>>          ReceiverResultReg must and does contain only self, but the
>> ceStoreCheck
>>          trampoline expects the target of the store to be in
>> ReceiverResultReg.  So
>>          in a frameless method we would have a conflict between the
>> receiver and
>>          the literal store, unless we we smart enough to realise that
>> ReceiverResultReg
>>          was unused after the literal variable store, unlikely given that
>> methods
>>          return self by default."
>>         self assert: needsFrame.
>>         association := self getLiteral: litVarIndex.
>>         self genMoveConstant: association R: ReceiverResultReg.
>>         objectRepresentation
>>                 genEnsureObjInRegNotForwarded: ReceiverResultReg
>>                 scratchReg: TempReg.
>>         popBoolean
>>                 ifTrue: [self PopR: ClassReg]
>>                 ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
>> +       self
>> +               genStoreSourceReg: ClassReg
>> +               slotIndex: ValueIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> -       traceStores > 0 ifTrue:
>> -               [self CallRT: ceTraceStoreTrampoline].
>> -       self cppIf: IMMUTABILITY ifTrue:
>> -               [immutabilityFailure := objectRepresentation
>> -
>>  genImmutableCheck: ReceiverResultReg
>> -
>>  slotIndex: ValueIndex
>> -
>>  sourceReg: ClassReg
>> -
>>  scratchReg: TempReg
>> -
>>  needRestoreRcvr: true].
>> -       objectRepresentation
>> -               genStoreSourceReg: ClassReg
>> -               slotIndex: ValueIndex
>> -               destReg: ReceiverResultReg
>> -               scratchReg: TempReg
>>                 inFrame: needsFrame.
>> -
>> -       self cppIf: IMMUTABILITY ifTrue:
>> -               [immutabilityFailure jmpTarget: self Label].
>> -
>>         ^0!
>>
>> Item was changed:
>>   ----- Method:
>> SimpleStackBasedCogit>>genStorePop:MaybeContextReceiverVariable: (in
>> category 'bytecode generator support') -----
>>   genStorePop: popBoolean MaybeContextReceiverVariable: slotIndex
>>         <inline: false>
>> +       | jmpSingle jmpDone |
>> -       | jmpSingle jmpDone immutabilityFailure |
>> -       <var: #immutabilityFailure type: #'AbstractInstruction *'>
>>         <var: #jmpSingle type: #'AbstractInstruction *'>
>>         <var: #jmpDone type: #'AbstractInstruction *'>
>>         "The reason we need a frame here is that assigning to an inst var
>> of a context may
>>          involve wholesale reorganization of stack pages, and the only
>> way to preserve the
>>          execution state of an activation in that case is if it has a
>> frame."
>>         self assert: needsFrame.
>>         self putSelfInReceiverResultReg.
>>         objectRepresentation
>>                 genLoadSlot: SenderIndex
>>                 sourceReg: ReceiverResultReg
>>                 destReg: TempReg.
>>         self MoveMw: 0 r: SPReg R: ClassReg.
>>         jmpSingle := objectRepresentation
>> genJumpNotSmallIntegerInScratchReg: TempReg.
>>         self MoveCq: slotIndex R: SendNumArgsReg.
>>         self CallRT: ceStoreContextInstVarTrampoline.
>>         jmpDone := self Jump: 0.
>>         jmpSingle jmpTarget: self Label.
>> -       traceStores > 0 ifTrue:
>> -               [self CallRT: ceTraceStoreTrampoline].
>> -       self cppIf: IMMUTABILITY ifTrue:
>> -               [immutabilityFailure := objectRepresentation
>> -
>>  genImmutableCheck: ReceiverResultReg
>> -
>>  slotIndex: slotIndex
>> -
>>  sourceReg: ClassReg
>> -
>>  scratchReg: TempReg
>> -
>>  needRestoreRcvr: true].
>> -       objectRepresentation
>> -               genStoreSourceReg: ClassReg
>> -               slotIndex: slotIndex
>> -               destReg: ReceiverResultReg
>> -               scratchReg: TempReg
>> -               inFrame: true.
>> -       jmpDone jmpTarget: self Label.
>>         popBoolean ifTrue:
>>                 [self AddCq: objectMemory wordSize R: SPReg].
>> +       self
>> +               genStoreSourceReg: ClassReg
>> +               slotIndex: slotIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> +               inFrame: needsFrame.
>> +       jmpDone jmpTarget: self Label.
>> -       self cppIf: IMMUTABILITY ifTrue:
>> -               [immutabilityFailure jmpTarget: self Label].
>>         ^0!
>>
>> Item was changed:
>>   ----- Method: SimpleStackBasedCogit>>genStorePop:ReceiverVariable: (in
>> category 'bytecode generator support') -----
>>   genStorePop: popBoolean ReceiverVariable: slotIndex
>>         <inline: false>
>> -       | immutabilityFailure |
>> -       <var: #immutabilityFailure type: #'AbstractInstruction *'>
>>         needsFrame ifTrue:
>>                 [self putSelfInReceiverResultReg].
>>         popBoolean
>>                 ifTrue: [self PopR: ClassReg]
>>                 ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
>> +       self
>> +               genStoreSourceReg: ClassReg
>> +               slotIndex: slotIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> -       traceStores > 0 ifTrue:
>> -               [self CallRT: ceTraceStoreTrampoline].
>> -       self cppIf: IMMUTABILITY ifTrue:
>> -               [immutabilityFailure := objectRepresentation
>> -
>>  genImmutableCheck: ReceiverResultReg
>> -
>>  slotIndex: slotIndex
>> -
>>  sourceReg: ClassReg
>> -
>>  scratchReg: TempReg
>> -
>>  needRestoreRcvr: true].
>> -       objectRepresentation
>> -               genStoreSourceReg: ClassReg
>> -               slotIndex: slotIndex
>> -               destReg: ReceiverResultReg
>> -               scratchReg: TempReg
>>                 inFrame: needsFrame.
>> -
>> -       self cppIf: IMMUTABILITY ifTrue:
>> -               [immutabilityFailure jmpTarget: self Label].
>> -
>>         ^0!
>>
>> Item was changed:
>>   ----- Method: SimpleStackBasedCogit>>genStorePop:RemoteTemp:At: (in
>> category 'bytecode generator support') -----
>>   genStorePop: popBoolean RemoteTemp: slotIndex At: remoteTempIndex
>>         <inline: false>
>>         "The only reason we assert needsFrame here is that in a frameless
>> method
>>          ReceiverResultReg must and does contain only self, but the
>> ceStoreCheck
>>          trampoline expects the target of the store to be in
>> ReceiverResultReg.  So
>>          in a frameless method we would have a conflict between the
>> receiver and
>>          the temote temp store, unless we we smart enough to realise that
>>          ReceiverResultReg was unused after the literal variable store,
>> unlikely given
>>          that methods return self by default."
>>         self assert: needsFrame.
>>         popBoolean
>>                 ifTrue: [self PopR: ClassReg]
>>                 ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
>>         self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r:
>> FPReg R: ReceiverResultReg.
>> -       traceStores > 0 ifTrue:
>> -               [self CallRT: ceTraceStoreTrampoline].
>>         ^objectRepresentation
>>                 genStoreSourceReg: ClassReg
>>                 slotIndex: slotIndex
>>                 destReg: ReceiverResultReg
>>                 scratchReg: TempReg
>>                 inFrame: needsFrame!
>>
>> Item was added:
>> + ----- Method: SimpleStackBasedCogit>>genTraceStores (in category
>> 'bytecode generator support') -----
>> + genTraceStores
>> +       <inline: true>
>> +       traceStores > 0 ifTrue: [ self CallRT: ceTraceStoreTrampoline ].!
>>
>> Item was added:
>> + ----- Method:
>> StackToRegisterMappingCogit>>genImmutabilityCheckStorePop:LiteralVariable:
>> (in category 'bytecode generator support') -----
>> + genImmutabilityCheckStorePop: popBoolean LiteralVariable: litVarIndex
>> +       <inline: true>
>> +       | association needStoreCheck |
>> +       "The only reason we assert needsFrame here is that in a frameless
>> method
>> +        ReceiverResultReg must and does contain only self, but the
>> ceStoreCheck
>> +        trampoline expects the target of the store to be in
>> ReceiverResultReg.  So
>> +        in a frameless method we would have a conflict between the
>> receiver and
>> +        the literal store, unless we we smart enough to realise that
>> ReceiverResultReg
>> +        was unused after the literal variable store, unlikely given that
>> methods
>> +        return self by default."
>> +       self assert: needsFrame.
>> +       "N.B.  No need to check the stack for references because we
>> generate code for
>> +        literal variable loads that stores the result in a register,
>> deferring only the register push."
>> +       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> +       association := self getLiteral: litVarIndex.
>> +       optStatus isReceiverResultRegLive: false.
>> +       self ssAllocateRequiredReg: ReceiverResultReg. "for store
>> trampoline call in genStoreSourceReg: has to be ReceiverResultReg"
>> +       self genMoveConstant: association R: ReceiverResultReg.
>> +       objectRepresentation genEnsureObjInRegNotForwarded:
>> ReceiverResultReg scratchReg: TempReg.
>> +       self ssAllocateRequiredReg: ClassReg.
>> +       self ssStoreAndReplacePop: popBoolean toReg: ClassReg.
>> +       self ssFlushTo: simStackPtr.
>> +       objectRepresentation
>> +               genStoreWithImmutabilityCheckSourceReg: ClassReg
>> +               slotIndex: ValueIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> +               needsStoreCheck: needStoreCheck
>> +               needRestoreRcvr: false.
>> +       ^ 0!
>>
>> Item was added:
>> + ----- Method:
>> StackToRegisterMappingCogit>>genImmutabilityCheckStorePop:MaybeContextReceiverVariable:
>> (in category 'bytecode generator support') -----
>> + genImmutabilityCheckStorePop: popBoolean MaybeContextReceiverVariable:
>> slotIndex
>> +       <inline: true>
>> +       | jmpSingle jmpDone needStoreCheck |
>> +       <var: #jmpSingle type: #'AbstractInstruction *'>
>> +       <var: #jmpDone type: #'AbstractInstruction *'>
>> +       "The reason we need a frame here is that assigning to an inst var
>> of a context may
>> +        involve wholesale reorganization of stack pages, and the only
>> way to preserve the
>> +        execution state of an activation in that case is if it has a
>> frame."
>> +       self assert: needsFrame.
>> +       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> +       "Note that ReceiverResultReg remains live after both
>> +        ceStoreContextInstVarTrampoline and ceStoreCheckTrampoline."
>> +       self ensureReceiverResultRegContainsSelf.
>> +       self ssPop: 1.
>> +       self ssAllocateCallReg: ClassReg and: SendNumArgsReg. "for
>> ceStoreContextInstVarTrampoline"
>> +       self ssPush: 1.
>> +       objectRepresentation
>> +               genLoadSlot: SenderIndex
>> +               sourceReg: ReceiverResultReg
>> +               destReg: TempReg.
>> +       self ssStoreAndReplacePop: popBoolean toReg: ClassReg.
>> +       "stack is flushed except maybe ssTop if popBoolean is false.
>> +         ssTop is a SSregister in this case due to #ssStoreAndReplacePop:
>> +         to avoid a second indirect read / annotation in case of
>> SSConstant
>> +         or SSBaseRegister"
>> +       self ssFlushTo: simStackPtr.
>> +       jmpSingle := objectRepresentation
>> genJumpNotSmallIntegerInScratchReg: TempReg.
>> +       self MoveCq: slotIndex R: SendNumArgsReg.
>> +       self CallRT: ceStoreContextInstVarTrampoline.
>> +       jmpDone := self Jump: 0.
>> +       jmpSingle jmpTarget: self Label.
>> +       objectRepresentation
>> +               genStoreWithImmutabilityCheckSourceReg: ClassReg
>> +               slotIndex: slotIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> +               needsStoreCheck: needStoreCheck
>> +               needRestoreRcvr: true.
>> +       jmpDone jmpTarget: self Label.
>> +       ^0!
>>
>> Item was added:
>> + ----- Method:
>> StackToRegisterMappingCogit>>genImmutabilityCheckStorePop:ReceiverVariable:
>> (in category 'bytecode generator support') -----
>> + genImmutabilityCheckStorePop: popBoolean ReceiverVariable: slotIndex
>> +       <inline: true>
>> +       | needStoreCheck |
>> +       self assert: needsFrame.
>> +       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> +       "Note that ReceiverResultReg remains live after the trampoline."
>> +       self ensureReceiverResultRegContainsSelf.
>> +       self ssAllocateRequiredReg: ClassReg.
>> +       self ssStoreAndReplacePop: popBoolean toReg: ClassReg.
>> +       self ssFlushTo: simStackPtr.
>> +       objectRepresentation
>> +               genStoreWithImmutabilityCheckSourceReg: ClassReg
>> +               slotIndex: slotIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> +               needsStoreCheck: needStoreCheck
>> +               needRestoreRcvr: true.
>> +
>> +       ^ 0!
>>
>> Item was changed:
>>   ----- Method: StackToRegisterMappingCogit>>genStorePop:LiteralVariable:
>> (in category 'bytecode generator support') -----
>>   genStorePop: popBoolean LiteralVariable: litVarIndex
>>         <inline: false>
>> -       | topReg association needStoreCheck immutabilityFailure |
>> -       "The only reason we assert needsFrame here is that in a frameless
>> method
>> -        ReceiverResultReg must and does contain only self, but the
>> ceStoreCheck
>> -        trampoline expects the target of the store to be in
>> ReceiverResultReg.  So
>> -        in a frameless method we would have a conflict between the
>> receiver and
>> -        the literal store, unless we we smart enough to realise that
>> ReceiverResultReg
>> -        was unused after the literal variable store, unlikely given that
>> methods
>> -        return self by default."
>> -       self assert: needsFrame.
>> -       self cppIf: IMMUTABILITY ifTrue: [ self ssFlushTo: simStackPtr -
>> 1 ].
>> -       "N.B.  No need to check the stack for references because we
>> generate code for
>> -        literal variable loads that stores the result in a register,
>> deferring only the register push."
>> -       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> -       association := self getLiteral: litVarIndex.
>> -       optStatus isReceiverResultRegLive: false.
>> -       self ssAllocateRequiredReg: ReceiverResultReg. "for ceStoreCheck
>> call in genStoreSourceReg: has to be ReceiverResultReg"
>> -       self genMoveConstant: association R: ReceiverResultReg.
>> -       objectRepresentation genEnsureObjInRegNotForwarded:
>> ReceiverResultReg scratchReg: TempReg.
>>         self
>>                 cppIf: IMMUTABILITY
>> +               ifTrue: [ ^ self genImmutabilityCheckStorePop: popBoolean
>> LiteralVariable: litVarIndex ]
>> +               ifFalse: [ ^ self genVanillaStorePop: popBoolean
>> LiteralVariable: litVarIndex ]
>> +               !
>> -               ifTrue:
>> -                       [ self ssAllocateRequiredReg: ClassReg.
>> -                         topReg := ClassReg.
>> -                         self ssStoreAndReplacePop: popBoolean toReg:
>> ClassReg.
>> -                         "stack is flushed except maybe ssTop if
>> popBoolean is false.
>> -                         ssTop is a SSregister in this case due to
>> #ssStoreAndReplacePop:
>> -                         to avoid a second indirect read / annotation in
>> case of SSConstant
>> -                         or SSBaseRegister"
>> -                         self ssFlushTo: simStackPtr.
>> -                         immutabilityFailure := objectRepresentation
>> -
>>        genImmutableCheck: ReceiverResultReg
>> -
>>        slotIndex: ValueIndex
>> -
>>        sourceReg: ClassReg
>> -
>>        scratchReg: TempReg
>> -
>>        needRestoreRcvr: false ]
>> -               ifFalse:
>> -                       [ topReg := self allocateRegForStackEntryAt: 0
>> notConflictingWith: (self registerMaskFor: ReceiverResultReg).
>> -                         self ssStorePop: popBoolean toReg: topReg ].
>> -       traceStores > 0 ifTrue:
>> -               [self MoveR: topReg R: TempReg.
>> -                self CallRT: ceTraceStoreTrampoline].
>> -       objectRepresentation
>> -               genStoreSourceReg: topReg
>> -               slotIndex: ValueIndex
>> -               destReg: ReceiverResultReg
>> -               scratchReg: TempReg
>> -               inFrame: needsFrame
>> -               needsStoreCheck: needStoreCheck.
>> -       self cppIf: IMMUTABILITY ifTrue: [ immutabilityFailure jmpTarget:
>> self Label ].
>> -       ^ 0!
>>
>> Item was changed:
>>   ----- Method:
>> StackToRegisterMappingCogit>>genStorePop:MaybeContextReceiverVariable: (in
>> category 'bytecode generator support') -----
>>   genStorePop: popBoolean MaybeContextReceiverVariable: slotIndex
>>         <inline: false>
>> -       | jmpSingle jmpDone needStoreCheck immutabilityFailure |
>> -       <var: #jmpSingle type: #'AbstractInstruction *'>
>> -       <var: #jmpDone type: #'AbstractInstruction *'>
>> -       "The reason we need a frame here is that assigning to an inst var
>> of a context may
>> -        involve wholesale reorganization of stack pages, and the only
>> way to preserve the
>> -        execution state of an activation in that case is if it has a
>> frame."
>> -       self assert: needsFrame.
>> -       self cppIf: IMMUTABILITY ifTrue: [ self ssFlushTo: simStackPtr -
>> 1 ].
>> -       self ssFlushUpThroughReceiverVariable: slotIndex.
>> -       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> -       "Note that ReceiverResultReg remains live after both
>> -        ceStoreContextInstVarTrampoline and ceStoreCheckTrampoline."
>> -       self ensureReceiverResultRegContainsSelf.
>> -       self ssPop: 1.
>> -       self ssAllocateCallReg: ClassReg and: SendNumArgsReg. "for
>> ceStoreContextInstVarTrampoline"
>> -       self ssPush: 1.
>> -       objectRepresentation
>> -               genLoadSlot: SenderIndex
>> -               sourceReg: ReceiverResultReg
>> -               destReg: TempReg.
>>         self
>>                 cppIf: IMMUTABILITY
>> +               ifTrue: [ ^ self genImmutabilityCheckStorePop: popBoolean
>> MaybeContextReceiverVariable: slotIndex ]
>> +               ifFalse: [ ^ self genVanillaStorePop: popBoolean
>> MaybeContextReceiverVariable: slotIndex ]!
>> -               ifTrue:
>> -                       [ self ssStoreAndReplacePop: popBoolean toReg:
>> ClassReg.
>> -                         "stack is flushed except maybe ssTop if
>> popBoolean is false.
>> -                         ssTop is a SSregister in this case due to
>> #ssStoreAndReplacePop:
>> -                         to avoid a second indirect read / annotation in
>> case of SSConstant
>> -                         or SSBaseRegister"
>> -                         self ssFlushTo: simStackPtr. ]
>> -               ifFalse: [ self ssStorePop: popBoolean toReg: ClassReg ].
>> -       jmpSingle := objectRepresentation
>> genJumpNotSmallIntegerInScratchReg: TempReg.
>> -       self MoveCq: slotIndex R: SendNumArgsReg.
>> -       self CallRT: ceStoreContextInstVarTrampoline.
>> -       jmpDone := self Jump: 0.
>> -       jmpSingle jmpTarget: self Label.
>> -       traceStores > 0 ifTrue:
>> -               [self MoveR: ClassReg R: TempReg.
>> -                self CallRT: ceTraceStoreTrampoline].
>> -       self
>> -               cppIf: IMMUTABILITY
>> -               ifTrue:
>> -                       [ immutabilityFailure := objectRepresentation
>> -
>>        genImmutableCheck: ReceiverResultReg
>> -
>>        slotIndex: ValueIndex
>> -
>>        sourceReg: ClassReg
>> -
>>        scratchReg: TempReg
>> -
>>        needRestoreRcvr: true ].
>> -       objectRepresentation
>> -               genStoreSourceReg: ClassReg
>> -               slotIndex: slotIndex
>> -               destReg: ReceiverResultReg
>> -               scratchReg: TempReg
>> -               inFrame: true
>> -               needsStoreCheck: needStoreCheck.
>> -       jmpDone jmpTarget: self Label.
>> -       self cppIf: IMMUTABILITY ifTrue: [ immutabilityFailure jmpTarget:
>> self Label ].
>> -       ^0!
>>
>> Item was changed:
>>   ----- Method:
>> StackToRegisterMappingCogit>>genStorePop:ReceiverVariable: (in category
>> 'bytecode generator support') -----
>>   genStorePop: popBoolean ReceiverVariable: slotIndex
>>         <inline: false>
>> -       | topReg needStoreCheck immutabilityFailure |
>> -       self cppIf: IMMUTABILITY ifTrue: [ self assert: needsFrame. self
>> ssFlushTo: simStackPtr - 1 ].
>> -       self ssFlushUpThroughReceiverVariable: slotIndex.
>> -       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> -       "Note that ReceiverResultReg remains live after
>> ceStoreCheckTrampoline."
>> -       self ensureReceiverResultRegContainsSelf.
>>         self
>>                 cppIf: IMMUTABILITY
>> +               ifTrue: [ ^ self genImmutabilityCheckStorePop: popBoolean
>> ReceiverVariable: slotIndex ]
>> +               ifFalse: [ ^ self genVanillaStorePop: popBoolean
>> ReceiverVariable: slotIndex ]
>> +               !
>> -               ifTrue:
>> -                       [ self ssAllocateRequiredReg: ClassReg.
>> -                         topReg := ClassReg.
>> -                         self ssStoreAndReplacePop: popBoolean toReg:
>> ClassReg.
>> -                         "stack is flushed except maybe ssTop if
>> popBoolean is false.
>> -                         ssTop is a SSregister in this case due to
>> #ssStoreAndReplacePop:
>> -                         to avoid a second indirect read / annotation in
>> case of SSConstant
>> -                         or SSBaseRegister"
>> -                         self ssFlushTo: simStackPtr.
>> -                         immutabilityFailure := objectRepresentation
>> -
>>        genImmutableCheck: ReceiverResultReg
>> -
>>        slotIndex: slotIndex
>> -
>>        sourceReg: ClassReg
>> -
>>        scratchReg: TempReg
>> -
>>        needRestoreRcvr: true ]
>> -               ifFalse:
>> -                       [ topReg := self allocateRegForStackEntryAt: 0
>> notConflictingWith: (self registerMaskFor: ReceiverResultReg).
>> -                         self ssStorePop: popBoolean toReg: topReg ].
>> -       traceStores > 0 ifTrue:
>> -               [ self MoveR: topReg R: TempReg.
>> -               self evaluateTrampolineCallBlock: [ self CallRT:
>> ceTraceStoreTrampoline ] protectLinkRegIfNot: needsFrame ].
>> -       objectRepresentation
>> -               genStoreSourceReg: topReg
>> -               slotIndex: slotIndex
>> -               destReg: ReceiverResultReg
>> -               scratchReg: TempReg
>> -               inFrame: needsFrame
>> -               needsStoreCheck: needStoreCheck.
>> -       self cppIf: IMMUTABILITY ifTrue: [ immutabilityFailure jmpTarget:
>> self Label ].
>> -       ^ 0!
>>
>> Item was changed:
>>   ----- Method: StackToRegisterMappingCogit>>genStorePop:RemoteTemp:At:
>> (in category 'bytecode generator support') -----
>>   genStorePop: popBoolean RemoteTemp: slotIndex At: remoteTempIndex
>>         <inline: false>
>>         | topReg needStoreCheck |
>>         "The only reason we assert needsFrame here is that in a frameless
>> method
>>          ReceiverResultReg must and does contain only self, but the
>> ceStoreCheck
>>          trampoline expects the target of the store to be in
>> ReceiverResultReg.  So
>>          in a frameless method we would have a conflict between the
>> receiver and
>>          the temote temp store, unless we we smart enough to realise that
>>          ReceiverResultReg was unused after the literal variable store,
>> unlikely given
>>          that methods return self by default."
>>         self assert: needsFrame.
>>         "N.B.  No need to check the stack for references because we
>> generate code for
>>          remote temp loads that stores the result in a register,
>> deferring only the register push."
>>         needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>>         topReg := self allocateRegForStackEntryAt: 0 notConflictingWith:
>> (self registerMaskFor: ReceiverResultReg).
>>         self ssAllocateRequiredReg: ReceiverResultReg.
>>         optStatus isReceiverResultRegLive: false.
>>         self ssStoreAndReplacePop: popBoolean toReg: topReg.
>>         self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r:
>> FPReg R: ReceiverResultReg.
>> -        traceStores > 0 ifTrue:
>> -                       [ self MoveR: topReg R: TempReg.
>> -                       self CallRT: ceTraceStoreTrampoline. ].
>>         ^objectRepresentation
>>                 genStoreSourceReg: topReg
>>                 slotIndex: slotIndex
>>                 destReg: ReceiverResultReg
>>                 scratchReg: TempReg
>>                 inFrame: needsFrame
>>                 needsStoreCheck: needStoreCheck!
>>
>> Item was added:
>> + ----- Method: StackToRegisterMappingCogit>>genTraceStores (in category
>> 'bytecode generator support') -----
>> + genTraceStores
>> +       <inline: true>
>> +       traceStores > 0 ifTrue:
>> +               [ self MoveR: ClassReg R: TempReg.
>> +               self CallRT: ceTraceStoreTrampoline ].!
>>
>> Item was added:
>> + ----- Method:
>> StackToRegisterMappingCogit>>genVanillaStorePop:LiteralVariable: (in
>> category 'bytecode generator support') -----
>> + genVanillaStorePop: popBoolean LiteralVariable: litVarIndex
>> +       <inline: true>
>> +       | topReg association needStoreCheck |
>> +       "The only reason we assert needsFrame here is that in a frameless
>> method
>> +        ReceiverResultReg must and does contain only self, but the
>> ceStoreCheck
>> +        trampoline expects the target of the store to be in
>> ReceiverResultReg.  So
>> +        in a frameless method we would have a conflict between the
>> receiver and
>> +        the literal store, unless we we smart enough to realise that
>> ReceiverResultReg
>> +        was unused after the literal variable store, unlikely given that
>> methods
>> +        return self by default."
>> +       self assert: needsFrame.
>> +       "N.B.  No need to check the stack for references because we
>> generate code for
>> +        literal variable loads that stores the result in a register,
>> deferring only the register push."
>> +       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> +       association := self getLiteral: litVarIndex.
>> +       optStatus isReceiverResultRegLive: false.
>> +       self ssAllocateRequiredReg: ReceiverResultReg. "for ceStoreCheck
>> call in genStoreSourceReg: has to be ReceiverResultReg"
>> +       self genMoveConstant: association R: ReceiverResultReg.
>> +       objectRepresentation genEnsureObjInRegNotForwarded:
>> ReceiverResultReg scratchReg: TempReg.
>> +       topReg := self allocateRegForStackEntryAt: 0 notConflictingWith:
>> (self registerMaskFor: ReceiverResultReg).
>> +       self ssStorePop: popBoolean toReg: topReg.
>> +       objectRepresentation
>> +               genStoreSourceReg: topReg
>> +               slotIndex: ValueIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> +               inFrame: needsFrame
>> +               needsStoreCheck: needStoreCheck.
>> +       ^ 0!
>>
>> Item was added:
>> + ----- Method:
>> StackToRegisterMappingCogit>>genVanillaStorePop:MaybeContextReceiverVariable:
>> (in category 'bytecode generator support') -----
>> + genVanillaStorePop: popBoolean MaybeContextReceiverVariable: slotIndex
>> +       <inline: true>
>> +       | jmpSingle jmpDone needStoreCheck |
>> +       <var: #jmpSingle type: #'AbstractInstruction *'>
>> +       <var: #jmpDone type: #'AbstractInstruction *'>
>> +       "The reason we need a frame here is that assigning to an inst var
>> of a context may
>> +        involve wholesale reorganization of stack pages, and the only
>> way to preserve the
>> +        execution state of an activation in that case is if it has a
>> frame."
>> +       self assert: needsFrame.
>> +       self ssFlushUpThroughReceiverVariable: slotIndex.
>> +       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> +       "Note that ReceiverResultReg remains live after both
>> +        ceStoreContextInstVarTrampoline and ceStoreCheckTrampoline."
>> +       self ensureReceiverResultRegContainsSelf.
>> +       self ssPop: 1.
>> +       self ssAllocateCallReg: ClassReg and: SendNumArgsReg. "for
>> ceStoreContextInstVarTrampoline"
>> +       self ssPush: 1.
>> +       objectRepresentation
>> +               genLoadSlot: SenderIndex
>> +               sourceReg: ReceiverResultReg
>> +               destReg: TempReg.
>> +       self ssStorePop: popBoolean toReg: ClassReg.
>> +       jmpSingle := objectRepresentation
>> genJumpNotSmallIntegerInScratchReg: TempReg.
>> +       self MoveCq: slotIndex R: SendNumArgsReg.
>> +       self CallRT: ceStoreContextInstVarTrampoline.
>> +       jmpDone := self Jump: 0.
>> +       jmpSingle jmpTarget: self Label.
>> +       objectRepresentation
>> +               genStoreSourceReg: ClassReg
>> +               slotIndex: slotIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> +               inFrame: true
>> +               needsStoreCheck: needStoreCheck.
>> +       jmpDone jmpTarget: self Label.
>> +
>> +       ^0!
>>
>> Item was added:
>> + ----- Method:
>> StackToRegisterMappingCogit>>genVanillaStorePop:ReceiverVariable: (in
>> category 'bytecode generator support') -----
>> + genVanillaStorePop: popBoolean ReceiverVariable: slotIndex
>> +       <inline: true>
>> +       | topReg needStoreCheck |
>> +       self ssFlushUpThroughReceiverVariable: slotIndex.
>> +       needStoreCheck := (objectRepresentation isUnannotatableConstant:
>> self ssTop) not.
>> +       "Note that ReceiverResultReg remains live after
>> ceStoreCheckTrampoline."
>> +       self ensureReceiverResultRegContainsSelf.
>> +       topReg := self allocateRegForStackEntryAt: 0 notConflictingWith:
>> (self registerMaskFor: ReceiverResultReg).
>> +       self ssStorePop: popBoolean toReg: topReg.
>> +       objectRepresentation
>> +               genStoreSourceReg: topReg
>> +               slotIndex: slotIndex
>> +               destReg: ReceiverResultReg
>> +               scratchReg: TempReg
>> +               inFrame: needsFrame
>> +               needsStoreCheck: needStoreCheck.
>> +       ^ 0!
>>
>>
>
>


-- 
_,,,^..^,,,_
best, Eliot
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20160330/5d5b200d/attachment-0001.htm


More information about the Vm-dev mailing list