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

Ryan Macnak rmacnak at gmail.com
Wed Nov 4 00:04:51 UTC 2015


I don't think ARM or MIPS have an instruction that preserves the high bits
in the destination register. How about using movzxb on ia32/x64?
On Nov 3, 2015 3:10 AM, "Eliot Miranda" <eliot.miranda at gmail.com> wrote:

>
> Hi Ryan,
>
> On Nov 2, 2015, at 8:51 PM, Ryan Macnak <rmacnak at gmail.com> wrote:
>
> Does MoveAbR want zero extension or sign extension?
>
>
> If there is extension it must be zero extension.  I *think* that on x86
> assignment to %al, %bl et al on x86 leaves all other bits in the
> corresponding 32-bit register unchanged, so I stated in the comment for
> MoveMb:r:R: that if the code generator wants the higher bits zero it will
> explicitly zero the register before the byte load. I'll make the comment
> for MoveAb:R: explicit.  To save the instruction I could add a backEnd
> query, eg backEnd byteLoadsZeroExtend.
>
> _,,,^..^,,,_ (phone)
>
>
> On Mon, Nov 2, 2015 at 6:17 PM, <commits at source.squeak.org> wrote:
>
>>
>> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
>> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1504.mcz
>>
>> ==================== Summary ====================
>>
>> Name: VMMaker.oscog-eem.1504
>> Author: eem
>> Time: 2 November 2015, 10:16:22.592 pm
>> UUID: 3c702143-ff40-4e38-a55e-065a3aec15ec
>> Ancestors: VMMaker.oscog-EstebanLorenzano.1503
>>
>> Merge with VMMaker.oscog-EstebanLorenzano.1503:
>> - simplify the addressIsInInstructions: macro.
>> - express some concerns about ffiAddressOf:startingAt:size:
>>
>> x64 Cogit:
>> Add support for MoveAb:R: & MoveR:Ab: on x64 & x86.  Tim, would you mind
>> adding support for ARM?
>> The misuse of MoveMb:r:R:/MoveR:Mb:r: as a stand-in for
>> MoveAb:R:/MoveR:Ab: only works on 32-bit platforms.
>>
>> Fix rip-relative addressing for MoveCwR/PushCw.  Add some tests.
>>
>> Nuke the leaking breaks in genInnerPrimitiveNew[WithArg]:
>>
>> Execution now gets to the first jitted method that wants to create a
>> closure.
>>
>> =============== Diff against VMMaker.oscog-EstebanLorenzano.1503
>> ===============
>>
>> Item was changed:
>>   ----- Method: CogIA32Compiler>>computeMaximumSize (in category
>> 'generate machine code') -----
>>   computeMaximumSize
>>         "Compute the maximum size for each opcode.  This allows jump
>> offsets to
>>          be determined, provided that all backward branches are long
>> branches."
>>         "N.B.  The ^N forms are to get around the bytecode compiler's
>> long branch
>>          limits which are exceeded when each case jumps around the
>> otherwise."
>>         opcode caseOf: {
>>                 "Noops & Pseudo Ops"
>>                 [Label]                                 -> [^0].
>>                 [AlignmentNops]         -> [^(operands at: 0) - 1].
>>                 [Fill16]                                        -> [^2].
>>                 [Fill32]                                        -> [^4].
>>                 [FillFromWord]                  -> [^4].
>>                 [Nop]                                   -> [^1].
>>                 "Specific Control/Data Movement"
>>                 [CDQ]                                   -> [^1].
>>                 [IDIVR]                                 -> [^2].
>>                 [IMULRR]                                -> [^3].
>>                 [CPUID]                                 -> [^2].
>>                 [CMPXCHGAwR]                    -> [^7].
>>                 [CMPXCHGMwrR]           -> [^(self concreteRegister:
>> (operands at: 1)) = ESP
>>
>>       ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
>>
>>       ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
>>                 [LFENCE]                                -> [^3].
>>                 [MFENCE]                                -> [^3].
>>                 [SFENCE]                                -> [^3].
>>                 [LOCK]                                  -> [^1].
>>                 [XCHGAwR]                               -> [^6].
>>                 [XCHGMwrR]                      -> [^(self
>> concreteRegister: (operands at: 1)) = ESP
>>
>>       ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]
>>
>>       ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [3] ifFalse: [6]]].
>>                 [XCHGRR]                                -> [^((self
>> concreteRegister: (operands at: 0)) = EAX
>>
>>  or: [(self concreteRegister: (operands at: 1)) = EAX])
>>
>>       ifTrue: [1]
>>
>>       ifFalse: [2]].
>>                 "Control"
>>                 [CallFull]                                      -> [^5].
>>                 [Call]                                          -> [^5].
>>                 [JumpR]                                         -> [^2].
>>                 [JumpFull]                                      -> [self
>> resolveJumpTarget. ^5].
>>                 [JumpLong]                                      -> [self
>> resolveJumpTarget. ^5].
>>                 [Jump]                                          -> [self
>> resolveJumpTarget. ^5].
>>                 [JumpZero]                                      -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpNonZero]                           -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpNegative]                          -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpNonNegative]                       -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpOverflow]                          -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpNoOverflow]                        -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpCarry]                             -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpNoCarry]                           -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpLess]                                      -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpGreaterOrEqual]            -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpGreater]                           -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpLessOrEqual]                       -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpBelow]                             -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpAboveOrEqual]              -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpAbove]                             -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpBelowOrEqual]              -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpLongZero]                  -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpLongNonZero]               -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpFPEqual]                           -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpFPNotEqual]                        -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpFPLess]                            -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpFPGreaterOrEqual]  -> [self resolveJumpTarget. ^6].
>>                 [JumpFPGreater]                 -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpFPLessOrEqual]             -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpFPOrdered]                 -> [self
>> resolveJumpTarget. ^6].
>>                 [JumpFPUnordered]                       -> [self
>> resolveJumpTarget. ^6].
>>                 [RetN]                                          ->
>> [^(operands at: 0) = 0 ifTrue: [1] ifFalse: [3]].
>>                 [Stop]                                          -> [^1].
>>
>>                 "Arithmetic"
>>                 [AddCqR]                -> [^(self isQuick: (operands at:
>> 0))
>>
>>               ifTrue: [3]
>>
>>               ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
>>
>>                                       ifTrue: [5]
>>
>>                                       ifFalse: [6]]].
>>                 [AndCqR]                -> [^(self isQuick: (operands at:
>> 0))
>>
>>               ifTrue: [3]
>>
>>               ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
>>
>>                                       ifTrue: [5]
>>
>>                                       ifFalse: [6]]].
>>                 [CmpCqR]                -> [^(self isQuick: (operands at:
>> 0))
>>
>>               ifTrue: [3]
>>
>>               ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
>>
>>                                       ifTrue: [5]
>>
>>                                       ifFalse: [6]]].
>>                 [OrCqR]                 -> [^(self isQuick: (operands at:
>> 0))
>>
>>               ifTrue: [3]
>>
>>               ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
>>
>>                                       ifTrue: [5]
>>
>>                                       ifFalse: [6]]].
>>                 [SubCqR]                -> [^(self isQuick: (operands at:
>> 0))
>>
>>               ifTrue: [3]
>>
>>               ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
>>
>>                                       ifTrue: [5]
>>
>>                                       ifFalse: [6]]].
>>                 [TstCqR]                -> [^((self isQuick: (operands
>> at: 0)) and: [(self concreteRegister: (operands at: 1)) < 4])
>>
>>               ifTrue: [3]
>>
>>               ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
>>
>>                                       ifTrue: [5]
>>
>>                                       ifFalse: [6]]].
>>                 [AddCwR]                -> [^(self concreteRegister:
>> (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [AndCwR]                -> [^(self concreteRegister:
>> (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [CmpCwR]                -> [^(self concreteRegister:
>> (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [OrCwR]         -> [^(self concreteRegister: (operands
>> at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [SubCwR]                -> [^(self concreteRegister:
>> (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [XorCwR]                -> [^(self concreteRegister:
>> (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [AddRR]                 -> [^2].
>>                 [AndRR]                 -> [^2].
>>                 [CmpRR]         -> [^2].
>>                 [OrRR]                  -> [^2].
>>                 [XorRR]                 -> [^2].
>>                 [SubRR]                 -> [^2].
>>                 [NegateR]               -> [^2].
>>                 [LoadEffectiveAddressMwrR]
>>                                                 -> [^((self isQuick:
>> (operands at: 0))
>>
>>               ifTrue: [3]
>>
>>               ifFalse: [6])
>>
>>       + ((self concreteRegister: (operands at: 1)) = ESP
>>
>>               ifTrue: [1]
>>
>>               ifFalse: [0])].
>>                 [LogicalShiftLeftCqR]           -> [^(operands at: 0) = 1
>> ifTrue: [2] ifFalse: [3]].
>>                 [LogicalShiftRightCqR]          -> [^(operands at: 0) = 1
>> ifTrue: [2] ifFalse: [3]].
>>                 [ArithmeticShiftRightCqR]       -> [^(operands at: 0) = 1
>> ifTrue: [2] ifFalse: [3]].
>>                 [LogicalShiftLeftRR]                    -> [^self
>> computeShiftRRSize].
>>                 [LogicalShiftRightRR]           -> [^self
>> computeShiftRRSize].
>>                 [ArithmeticShiftRightRR]                -> [^self
>> computeShiftRRSize].
>>                 [AddRdRd]                                       -> [^4].
>>                 [CmpRdRd]                                       -> [^4].
>>                 [SubRdRd]                                       -> [^4].
>>                 [MulRdRd]                                       -> [^4].
>>                 [DivRdRd]                                       -> [^4].
>>                 [SqrtRd]                                        -> [^4].
>>                 "Data Movement"
>>                 [MoveCqR]               -> [^(operands at: 0) = 0 ifTrue:
>> [2] ifFalse: [5]].
>>                 [MoveCwR]               -> [^5].
>>                 [MoveRR]                -> [^2].
>>                 [MoveRdRd]              -> [^4].
>>                 [MoveAwR]               -> [^(self concreteRegister:
>> (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [MoveRAw]               -> [^(self concreteRegister:
>> (operands at: 0)) = EAX ifTrue: [5] ifFalse: [6]].
>> +               [MoveAbR]               -> [^(self concreteRegister:
>> (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
>> +               [MoveRAb]               -> [^(self concreteRegister:
>> (operands at: 0)) = EAX ifTrue: [5] ifFalse: [6]].
>>                 [MoveRMwr]      -> [^((self isQuick: (operands at: 1))
>>
>> ifTrue: [((operands at: 1) = 0
>>
>>               and: [(self concreteRegister: (operands at: 2)) ~= EBP])
>>
>>                       ifTrue: [2]
>>
>>                       ifFalse: [3]]
>>
>> ifFalse: [6])
>>                                                                 + ((self
>> concreteRegister: (operands at: 2)) = ESP
>>
>> ifTrue: [1]
>>
>> ifFalse: [0])].
>>                 [MoveRdM64r]    -> [^((self isQuick: (operands at: 1))
>>
>>               ifTrue: [5]
>>
>>               ifFalse: [8])
>>
>>       + ((self concreteRegister: (operands at: 2)) = ESP
>>
>>               ifTrue: [1]
>>
>>               ifFalse: [0])].
>>                 [MoveMbrR]              -> [^(self concreteRegister:
>> (operands at: 1)) = ESP
>>                                                                 ifTrue:
>> [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
>>                                                                 ifFalse:
>> [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
>>                 [MoveRMbr]              -> [^(self concreteRegister:
>> (operands at: 2)) = ESP
>>                                                                 ifTrue:
>> [7]
>>                                                                 ifFalse:
>> [(self isQuick: (operands at: 1)) ifTrue: [3] ifFalse: [6]]].
>>                 [MoveM16rR]     -> [^(self concreteRegister: (operands
>> at: 1)) = ESP
>>                                                                 ifTrue:
>> [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
>>                                                                 ifFalse:
>> [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
>>                 [MoveM64rRd]    -> [^((self isQuick: (operands at: 0))
>>
>>               ifTrue: [5]
>>
>>               ifFalse: [8])
>>
>>       + ((self concreteRegister: (operands at: 1)) = ESP
>>
>>               ifTrue: [1]
>>
>>               ifFalse: [0])].
>>                 [MoveMwrR]              -> [^((self isQuick: (operands
>> at: 0))
>>
>> ifTrue: [((operands at: 0) = 0
>>
>>               and: [(self concreteRegister: (operands at: 1)) ~= EBP])
>>
>>                       ifTrue: [2]
>>
>>                       ifFalse: [3]]
>>
>> ifFalse: [6])
>>                                                                 + ((self
>> concreteRegister: (operands at: 1)) = ESP
>>
>> ifTrue: [1]
>>
>> ifFalse: [0])].
>>                 [MoveXbrRR]     -> [self assert: (self concreteRegister:
>> (operands at: 0)) ~= ESP.
>>                                                         ^(self
>> concreteRegister: (operands at: 1)) = EBP
>>
>>               ifTrue: [5]
>>
>>               ifFalse: [4]].
>>                 [MoveRXbrR]     ->      [self assert: (self
>> concreteRegister: (operands at: 1)) ~= ESP.
>>                                                         ^((self
>> concreteRegister: (operands at: 2)) = EBP
>>
>>               ifTrue: [4]
>>
>>               ifFalse: [3])
>>
>>       + ((self concreteRegister: (operands at: 0)) >= 4
>>
>>               ifTrue: [2]
>>
>>               ifFalse: [0])].
>>                 [MoveXwrRR]     -> [self assert: (self concreteRegister:
>> (operands at: 0)) ~= ESP.
>>                                                         ^(self
>> concreteRegister: (operands at: 1)) = EBP
>>
>>               ifTrue: [4]
>>
>>               ifFalse: [3]].
>>                 [MoveRXwrR]     -> [self assert: (self concreteRegister:
>> (operands at: 1)) ~= ESP.
>>                                                         ^(self
>> concreteRegister: (operands at: 2)) = EBP
>>
>>               ifTrue: [4]
>>
>>               ifFalse: [3]].
>>                 [PopR]                  -> [^1].
>>                 [PushR]                 -> [^1].
>>                 [PushCq]                -> [^(self isQuick: (operands at:
>> 0)) ifTrue: [2] ifFalse: [5]].
>>                 [PushCw]                -> [^5].
>>                 [PrefetchAw]    -> [^self hasSSEInstructions ifTrue: [7]
>> ifFalse: [0]].
>>                 "Conversion"
>>                 [ConvertRRd]    -> [^4] }.
>>         ^0 "to keep C compiler quiet"!
>>
>> Item was added:
>> + ----- Method: CogIA32Compiler>>concretizeMoveAbR (in category 'generate
>> machine code') -----
>> + concretizeMoveAbR
>> +       "Will get inlined into concretizeAt: switch."
>> +       <inline: true>
>> +       | addressOperand reg |
>> +       addressOperand := operands at: 0.
>> +       (self isAnInstruction: (cogit cCoerceSimple: addressOperand to:
>> #'AbstractInstruction *')) ifTrue:
>> +               [addressOperand := (cogit cCoerceSimple: addressOperand
>> to: #'AbstractInstruction *') address].
>> +       reg := self concreteRegister: (operands at: 1).
>> +       reg = EAX ifTrue:
>> +               [machineCode
>> +                       at: 0 put: 16rA0;
>> +                       at: 1 put: (addressOperand bitAnd: 16rFF);
>> +                       at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
>> +                       at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
>> +                       at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
>> +                       ^machineCodeSize := 5].
>> +       machineCode
>> +               at: 0 put: 16r8A;
>> +               at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
>> +               at: 2 put: (addressOperand bitAnd: 16rFF);
>> +               at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
>> +               at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
>> +               at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
>> +       ^machineCodeSize := 6!
>>
>> Item was added:
>> + ----- Method: CogIA32Compiler>>concretizeMoveRAb (in category 'generate
>> machine code') -----
>> + concretizeMoveRAb
>> +       "Will get inlined into concretizeAt: switch."
>> +       <inline: true>
>> +       | addressOperand reg |
>> +       reg := self concreteRegister: (operands at: 0).
>> +       addressOperand := operands at: 1.
>> +       (self isAnInstruction: (cogit cCoerceSimple: addressOperand to:
>> #'AbstractInstruction *')) ifTrue:
>> +               [addressOperand := (cogit cCoerceSimple: addressOperand
>> to: #'AbstractInstruction *') address].
>> +       reg = EAX ifTrue:
>> +               [machineCode
>> +                       at: 0 put: 16rA2;
>> +                       at: 1 put: (addressOperand bitAnd: 16rFF);
>> +                       at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
>> +                       at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
>> +                       at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
>> +                       ^machineCodeSize := 5].
>> +       machineCode
>> +               at: 0 put: 16r88;
>> +               at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
>> +               at: 2 put: (addressOperand bitAnd: 16rFF);
>> +               at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
>> +               at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
>> +               at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
>> +       ^machineCodeSize := 6!
>>
>> Item was changed:
>>   ----- Method: CogIA32Compiler>>dispatchConcretize (in category
>> 'generate machine code') -----
>>   dispatchConcretize
>>         "Attempt to generate concrete machine code for the instruction at
>> address.
>>          This is the inner dispatch of concretizeAt: actualAddress which
>> exists only
>>          to get around the branch size limits in the SqueakV3 (blue book
>> derived)
>>          bytecode set."
>>         <returnTypeC: #void>
>>         opcode caseOf: {
>>                 "Noops & Pseudo Ops"
>>                 [Label]                         -> [^self
>> concretizeLabel].
>>                 [AlignmentNops] -> [^self concretizeAlignmentNops].
>>                 [Fill16]                                -> [^self
>> concretizeFill16].
>>                 [Fill32]                                -> [^self
>> concretizeFill32].
>>                 [FillFromWord]          -> [^self concretizeFillFromWord].
>>                 [Nop]                           -> [^self concretizeNop].
>>                 "Specific Control/Data Movement"
>>                 [CDQ]                                   -> [^self
>> concretizeCDQ].
>>                 [IDIVR]                                 -> [^self
>> concretizeIDIVR].
>>                 [IMULRR]                                -> [^self
>> concretizeMulRR].
>>                 [CPUID]                                 -> [^self
>> concretizeCPUID].
>>                 [CMPXCHGAwR]                    -> [^self
>> concretizeCMPXCHGAwR].
>>                 [CMPXCHGMwrR]           -> [^self concretizeCMPXCHGMwrR].
>>                 [LFENCE]                                -> [^self
>> concretizeFENCE: 5].
>>                 [MFENCE]                                -> [^self
>> concretizeFENCE: 6].
>>                 [SFENCE]                                -> [^self
>> concretizeFENCE: 7].
>>                 [LOCK]                                  -> [^self
>> concretizeLOCK].
>>                 [XCHGAwR]                               -> [^self
>> concretizeXCHGAwR].
>>                 [XCHGMwrR]                      -> [^self
>> concretizeXCHGMwrR].
>>                 [XCHGRR]                                -> [^self
>> concretizeXCHGRR].
>>                 "Control"
>>                 [Call]                                  -> [^self
>> concretizeCall].
>>                 [CallFull]                              -> [^self
>> concretizeCall].
>>                 [JumpR]                                 -> [^self
>> concretizeJumpR].
>>                 [JumpFull]                              -> [^self
>> concretizeJumpLong].
>>                 [JumpLong]                              -> [^self
>> concretizeJumpLong].
>>                 [JumpLongZero]          -> [^self
>> concretizeConditionalJump: 16r4].
>>                 [JumpLongNonZero]       -> [^self
>> concretizeConditionalJump: 16r5].
>>                 [Jump]                                  -> [^self
>> concretizeJump].
>>                 "Table B-1 IntelŽ 64 and IA-32 Architectures Software
>> Developer's Manual Volume 1: Basic Architecture"
>>                 [JumpZero]                              -> [^self
>> concretizeConditionalJump: 16r4].
>>                 [JumpNonZero]                   -> [^self
>> concretizeConditionalJump: 16r5].
>>                 [JumpNegative]                  -> [^self
>> concretizeConditionalJump: 16r8].
>>                 [JumpNonNegative]               -> [^self
>> concretizeConditionalJump: 16r9].
>>                 [JumpOverflow]                  -> [^self
>> concretizeConditionalJump: 16r0].
>>                 [JumpNoOverflow]                -> [^self
>> concretizeConditionalJump: 16r1].
>>                 [JumpCarry]                     -> [^self
>> concretizeConditionalJump: 16r2].
>>                 [JumpNoCarry]                   -> [^self
>> concretizeConditionalJump: 16r3].
>>                 [JumpLess]                              -> [^self
>> concretizeConditionalJump: 16rC].
>>                 [JumpGreaterOrEqual]    -> [^self
>> concretizeConditionalJump: 16rD].
>>                 [JumpGreater]                   -> [^self
>> concretizeConditionalJump: 16rF].
>>                 [JumpLessOrEqual]               -> [^self
>> concretizeConditionalJump: 16rE].
>>                 [JumpBelow]                     -> [^self
>> concretizeConditionalJump: 16r2].
>>                 [JumpAboveOrEqual]      -> [^self
>> concretizeConditionalJump: 16r3].
>>                 [JumpAbove]                     -> [^self
>> concretizeConditionalJump: 16r7].
>>                 [JumpBelowOrEqual]      -> [^self
>> concretizeConditionalJump: 16r6].
>>                 [JumpFPEqual]                           -> [^self
>> concretizeConditionalJump: 16r4].
>>                 [JumpFPNotEqual]                        -> [^self
>> concretizeConditionalJump: 16r5].
>>                 [JumpFPLess]                            -> [^self
>> concretizeConditionalJump: 16r2].
>>                 [JumpFPGreaterOrEqual]  -> [^self
>> concretizeConditionalJump: 16r3].
>>                 [JumpFPGreater]                 -> [^self
>> concretizeConditionalJump: 16r7].
>>                 [JumpFPLessOrEqual]             -> [^self
>> concretizeConditionalJump: 16r6].
>>                 [JumpFPOrdered]                 -> [^self
>> concretizeConditionalJump: 16rB].
>>                 [JumpFPUnordered]                       -> [^self
>> concretizeConditionalJump: 16rA].
>>                 [RetN]                                          -> [^self
>> concretizeRetN].
>>                 [Stop]                                          -> [^self
>> concretizeStop].
>>                 "Arithmetic"
>>                 [AddCqR]                                        -> [^self
>> concretizeAddCqR].
>>                 [AddCwR]                                        -> [^self
>> concretizeAddCwR].
>>                 [AddRR]                                         -> [^self
>> concretizeAddRR].
>>                 [AddRdRd]                                       -> [^self
>> concretizeSEE2OpRdRd: 16r58].
>>                 [AndCqR]                                        -> [^self
>> concretizeAndCqR].
>>                 [AndCwR]                                        -> [^self
>> concretizeAndCwR].
>>                 [AndRR]                                         -> [^self
>> concretizeAndRR].
>>                 [TstCqR]                                        -> [^self
>> concretizeTstCqR].
>>                 [CmpCqR]                                        -> [^self
>> concretizeCmpCqR].
>>                 [CmpCwR]                                        -> [^self
>> concretizeCmpCwR].
>>                 [CmpRR]                                 -> [^self
>> concretizeCmpRR].
>>                 [CmpRdRd]                                       -> [^self
>> concretizeCmpRdRd].
>>                 [DivRdRd]                                       -> [^self
>> concretizeSEE2OpRdRd: 16r5E].
>>                 [MulRdRd]                                       -> [^self
>> concretizeSEE2OpRdRd: 16r59].
>>                 [OrCqR]                                         -> [^self
>> concretizeOrCqR].
>>                 [OrCwR]                                 -> [^self
>> concretizeOrCwR].
>>                 [OrRR]                                          -> [^self
>> concretizeOrRR].
>>                 [SubCqR]                                        -> [^self
>> concretizeSubCqR].
>>                 [SubCwR]                                        -> [^self
>> concretizeSubCwR].
>>                 [SubRR]                                         -> [^self
>> concretizeSubRR].
>>                 [SubRdRd]                                       -> [^self
>> concretizeSEE2OpRdRd: 16r5C].
>>                 [SqrtRd]
>> -> [^self concretizeSqrtRd].
>>                 [XorCwR]
>> -> [^self concretizeXorCwR].
>>                 [XorRR]
>>  -> [^self concretizeXorRR].
>>                 [NegateR]
>>  -> [^self concretizeNegateR].
>>                 [LoadEffectiveAddressMwrR]      -> [^self
>> concretizeLoadEffectiveAddressMwrR].
>>                 [ArithmeticShiftRightCqR]               -> [^self
>> concretizeArithmeticShiftRightCqR].
>>                 [LogicalShiftRightCqR]                  -> [^self
>> concretizeLogicalShiftRightCqR].
>>                 [LogicalShiftLeftCqR]                   -> [^self
>> concretizeLogicalShiftLeftCqR].
>>                 [ArithmeticShiftRightRR]                        -> [^self
>> concretizeArithmeticShiftRightRR].
>>                 [LogicalShiftLeftRR]                            -> [^self
>> concretizeLogicalShiftLeftRR].
>>                 "Data Movement"
>>                 [MoveCqR]                       -> [^self
>> concretizeMoveCqR].
>>                 [MoveCwR]                       -> [^self
>> concretizeMoveCwR].
>>                 [MoveRR]                        -> [^self
>> concretizeMoveRR].
>>                 [MoveAwR]                       -> [^self
>> concretizeMoveAwR].
>>                 [MoveRAw]                       -> [^self
>> concretizeMoveRAw].
>> +               [MoveAbR]                       -> [^self
>> concretizeMoveAbR].
>> +               [MoveRAb]                       -> [^self
>> concretizeMoveRAb].
>>                 [MoveMbrR]                      -> [^self
>> concretizeMoveMbrR].
>>                 [MoveRMbr]                      -> [^self
>> concretizeMoveRMbr].
>>                 [MoveM16rR]             -> [^self concretizeMoveM16rR].
>>                 [MoveM64rRd]            -> [^self concretizeMoveM64rRd].
>>                 [MoveMwrR]              -> [^self concretizeMoveMwrR].
>>                 [MoveXbrRR]             -> [^self concretizeMoveXbrRR].
>>                 [MoveRXbrR]             -> [^self concretizeMoveRXbrR].
>>                 [MoveXwrRR]             -> [^self concretizeMoveXwrRR].
>>                 [MoveRXwrR]             -> [^self concretizeMoveRXwrR].
>>                 [MoveRMwr]              -> [^self concretizeMoveRMwr].
>>                 [MoveRdM64r]            -> [^self concretizeMoveRdM64r].
>>                 [PopR]                          -> [^self concretizePopR].
>>                 [PushR]                         -> [^self
>> concretizePushR].
>>                 [PushCq]                        -> [^self
>> concretizePushCq].
>>                 [PushCw]                        -> [^self
>> concretizePushCw].
>>                 [PrefetchAw]            -> [^self concretizePrefetchAw].
>>                 "Conversion"
>>                 [ConvertRRd]            -> [^self concretizeConvertRRd] }!
>>
>> Item was added:
>> + ----- Method: CogIA32CompilerTests>>testMoveAbR (in category 'tests')
>> -----
>> + testMoveAbR
>> +       "self new testMoveAbR"
>> +       CogIA32CompilerForTests byteRegistersWithNamesDo:
>> +               [:reg :regname|
>> +               #(16r555555 16rAAAAAA) do:
>> +                       [:addr| | inst len |
>> +                       inst := self gen: MoveAbR operand: addr operand:
>> reg.
>> +                       len := inst concretizeAt: 0.
>> +                       self processor
>> +                               disassembleInstructionAt: 0
>> +                               In: inst machineCode object
>> +                               into: [:str :sz| | plainJane herIntended |
>> +                                       "Convert e.g. '00000000: movl
>> %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
>> +                                       plainJane := self strip: str.
>> +                                       herIntended := 'movb 0x', (addr
>> hex allButFirst: 3), ', ', regname.
>> +                                       self assert: (plainJane match:
>> herIntended).
>> +                                       self assert: len = sz]]]!
>>
>> Item was added:
>> + ----- Method: CogIA32CompilerTests>>testMoveRAb (in category 'tests')
>> -----
>> + testMoveRAb
>> +       "self new testMoveRAb"
>> +       CogIA32CompilerForTests byteRegistersWithNamesDo:
>> +               [:reg :regname|
>> +               #(16r555555 16rAAAAAA) do:
>> +                       [:addr| | inst len |
>> +                       inst := self gen: MoveRAb operand: reg operand:
>> addr.
>> +                       len := inst concretizeAt: 0.
>> +                       self processor
>> +                               disassembleInstructionAt: 0
>> +                               In: inst machineCode object
>> +                               into: [:str :sz| | plainJane herIntended |
>> +                                       plainJane := self strip: str.
>> +                                       herIntended := 'movb ', regname,
>> ', 0x', (addr hex allButFirst: 3).
>> +                                       self assert: (plainJane match:
>> herIntended).
>> +                                       self assert: len = sz]]]!
>>
>> Item was changed:
>>   ----- Method: CogInLineLiteralsX64Compiler>>concretizeMoveCwR (in
>> category 'generate machine code') -----
>>   concretizeMoveCwR
>>         "Will get inlined into concretizeAt: switch."
>>         <inline: true>
>>         | value reg offset |
>>         value := operands at: 0.
>>         reg := self concreteRegister: (operands at: 1).
>>         (self isAnInstruction: (cogit cCoerceSimple: value to:
>> #'AbstractInstruction *')) ifTrue:
>>                 [value := (cogit cCoerceSimple: value to:
>> #'AbstractInstruction *') address].
>>         (cogit addressIsInCurrentCompilation: value) ifTrue:
>>                 [offset := value - (address + 7).
>>                  machineCode
>>                         at: 0 put: (self rexR: reg x: 0 b: 0);
>> +                       at: 1 put: 16r8D; "LoadEffectiveAddress"
>> +                       at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
>> -                       at: 1 put: 16r8B;
>> -                       at: 2 put: (self mod: ModReg RM: 5 RO: reg);
>>                         at: 3 put: (offset bitAnd: 16rFF);
>>                         at: 4 put: (offset >> 8 bitAnd: 16rFF);
>>                         at: 5 put: (offset >> 16 bitAnd: 16rFF);
>>                         at: 6 put: (offset >> 24 bitAnd: 16rFF).
>>                 ^machineCodeSize := 7].
>>         machineCode
>>                 at:  0 put: (self rexR: reg x: 0 b: reg);
>>                 at:  1 put: 16rB8 + (reg bitAnd: 7);
>>                 at:  2 put: (value bitAnd: 16rFF);
>>                 at:  3 put: (value >> 8 bitAnd: 16rFF);
>>                 at:  4 put: (value >> 16 bitAnd: 16rFF);
>>                 at:  5 put: (value >> 24 bitAnd: 16rFF);
>>                 at:  6 put: (value >> 32 bitAnd: 16rFF);
>>                 at:  7 put: (value >> 40 bitAnd: 16rFF);
>>                 at:  8 put: (value >> 48 bitAnd: 16rFF);
>>                 at:  9 put: (value >> 56 bitAnd: 16rFF);
>>                 at: 10 put: 16r90. "Add a nop to disambiguate between
>> MoveCwR/PushCwR and ArithCwR, which ends with a (self mod: ModReg RM: 0 RO:
>> 0)"
>>         self assert: (self mod: ModReg RM: 0 RO: 0) > 16r90.
>>         ^machineCodeSize := 11!
>>
>> Item was changed:
>>   ----- Method: CogInLineLiteralsX64Compiler>>concretizePushCw (in
>> category 'generate machine code') -----
>>   concretizePushCw
>>         "Will get inlined into concretizeAt: switch."
>>         <inline: true>
>>         | value offset |
>>         value := operands at: 0.
>>         (self isAnInstruction: (cogit cCoerceSimple: value to:
>> #'AbstractInstruction *')) ifTrue:
>>                 [value := (cogit cCoerceSimple: value to:
>> #'AbstractInstruction *') address].
>>         (cogit addressIsInCurrentCompilation: value) ifTrue:
>> +               [offset := value - (address + 7).
>> -               [offset := value - (address + 6).
>>                  machineCode
>> +                       at: 0 put: (self rexR: ConcreteRISCTempReg x: 0
>> b: 0);
>> +                       at: 1 put: 16r8D; "LoadEffectiveAddress"
>> +                       at: 2 put: (self mod: ModRegInd RM: 5 RO:
>> ConcreteRISCTempReg);
>> +                       at: 3 put: (offset bitAnd: 16rFF);
>> +                       at: 4 put: (offset >> 8 bitAnd: 16rFF);
>> +                       at: 5 put: (offset >> 16 bitAnd: 16rFF);
>> +                       at: 6 put: (offset >> 24 bitAnd: 16rFF);
>> +                       at: 7 put: 16r41;
>> +                       at: 8 put: 16r48 + ConcreteRISCTempReg.
>> +               ^machineCodeSize := 9].
>> -                       at: 0 put: 16rFF;
>> -                       at: 1 put: 16r35;
>> -                       at: 2 put: (offset bitAnd: 16rFF);
>> -                       at: 3 put: (offset >> 8 bitAnd: 16rFF);
>> -                       at: 4 put: (offset >> 16 bitAnd: 16rFF);
>> -                       at: 5 put: (offset >> 24 bitAnd: 16rFF).
>> -               ^machineCodeSize := 6].
>>         machineCode
>>                 at:  0 put: (self rexR: ConcreteRISCTempReg x: 0 b:
>> ConcreteRISCTempReg);
>>                 at:  1 put: 16rB8 + (ConcreteRISCTempReg bitAnd: 7);
>>                 at:  2 put: (value bitAnd: 16rFF);
>>                 at:  3 put: (value >> 8 bitAnd: 16rFF);
>>                 at:  4 put: (value >> 16 bitAnd: 16rFF);
>>                 at:  5 put: (value >> 24 bitAnd: 16rFF);
>>                 at:  6 put: (value >> 32 bitAnd: 16rFF);
>>                 at:  7 put: (value >> 40 bitAnd: 16rFF);
>>                 at:  8 put: (value >> 48 bitAnd: 16rFF);
>>                 at:  9 put: (value >> 56 bitAnd: 16rFF);
>>                 at: 10 put: 16r41;
>> +               at: 11 put: 16r48 + ConcreteRISCTempReg. "The 48 will
>> disambiguate between MoveCwR, PushCwR and ArithCwR, which ends with a (self
>> mod: ModReg RM: 0 RO: 0)"
>> -               at: 11 put: 16r50 + (ConcreteRISCTempReg - 8). "The 50
>> will disambiguate between MoveCwR, PushCwR and ArithCwR, which ends with a
>> (self mod: ModReg RM: 0 RO: 0)"
>>                 self assert: ConcreteRISCTempReg >= 8.
>>         self assert: (self mod: ModReg RM: 0 RO: 0) > 16r57.
>>         ^machineCodeSize := 12!
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentationFor64BitSpur>>genInnerPrimitiveNew: (in category
>> 'primitive generators') -----
>>   genInnerPrimitiveNew: retNoffset
>>         "Implement primitiveNew for convenient cases:
>>         - the receiver has a hash
>>         - the receiver is fixed size (excluding ephemerons to save
>> instructions & miniscule time)
>>         - single word header/num slots < numSlotsMask
>>         - the result fits in eden (actually below scavengeThreshold)"
>>
>>         | headerReg fillReg instSpecReg byteSizeReg
>>           jumpUnhashed jumpVariableOrEphemeron jumpNoSpace jumpTooBig
>> jumpHasSlots
>>           fillLoop skip |
>>         <var: 'skip' type: #'AbstractInstruction *'>
>>         <var: 'fillLoop' type: #'AbstractInstruction *'>
>>         <var: 'jumpTooBig' type: #'AbstractInstruction *'>
>>         <var: 'jumpHasSlots' type: #'AbstractInstruction *'>
>>         <var: 'jumpNoSpace' type: #'AbstractInstruction *'>
>>         <var: 'jumpUnhashed' type: #'AbstractInstruction *'>
>>         <var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
>>
>>         "header will contain classIndex/class's hash & format &
>> numSlots/fixed size and finally fill value (nilObject)."
>> -       self break.
>>         headerReg := fillReg := SendNumArgsReg.
>>         "inst spec will hold class's instance specification, then byte
>> size and finally end of new object."
>>         instSpecReg := byteSizeReg := ClassReg.
>>
>>         "get freeStart as early as possible so as not to wait later..."
>>         cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
>>         "get class's hash & fail if 0"
>>         self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.
>>         jumpUnhashed := cogit JumpZero: 0.
>>         "get class's format inst var for both inst spec (format field)
>> and num fixed fields"
>>         self genLoadSlot: InstanceSpecificationIndex sourceReg:
>> ReceiverResultReg destReg: TempReg.
>>         self genConvertSmallIntegerToIntegerInReg: TempReg.
>>         cogit MoveR: TempReg R: instSpecReg.
>>         cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R:
>> TempReg.
>>         cogit AndCq: objectMemory formatMask R: TempReg.
>>         cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R:
>> instSpecReg.
>>         "fail if not fixed or if ephemeron (rare beasts so save the
>> cycles)"
>>         cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
>>         jumpVariableOrEphemeron := cogit JumpAbove: 0.
>>         cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
>>         jumpTooBig := cogit JumpAboveOrEqual: 0.
>>         "Add format to classIndex/format in header; the add in numSlots"
>>         cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
>>         cogit AddR: TempReg R: headerReg.
>>         cogit MoveR: instSpecReg R: TempReg.
>>         cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R:
>> TempReg.
>>         cogit AddR: TempReg R: headerReg.
>>         "compute byte size; remember 0-sized objects still need 1 slot."
>>         cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
>>         jumpHasSlots := cogit JumpNonZero: 0.
>>         cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
>>         skip := cogit Jump: 0.
>>         "round up to allocationUnit"
>>         jumpHasSlots jmpTarget:
>>         (cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize
>> R: byteSizeReg).
>>         cogit LogicalShiftLeftCq: objectMemory shiftForWord R:
>> byteSizeReg.
>>         skip jmpTarget:
>>         "check if allocation fits (freeSize + byteSize <
>> scavengeThreshold); scavengeThreshold is constant."
>>         (cogit AddR: Arg1Reg R: byteSizeReg).
>>         cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
>>         jumpNoSpace := cogit JumpAboveOrEqual: 0.
>>         "write back new freeStart; get result. byteSizeReg holds new
>> freeStart, the limit of the object"
>>         cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
>>         cogit MoveR: Arg1Reg R: ReceiverResultReg.
>>         "write header"
>>         cogit MoveR: headerReg Mw: 0 r: Arg1Reg.
>>         "now fill"
>>         cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r:
>> ReceiverResultReg R: Arg1Reg.
>>         cogit MoveCq: objectMemory nilObject R: fillReg.
>>         fillLoop :=
>>         cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
>>         cogit AddCq: 8 R: Arg1Reg.
>>         cogit CmpR: Arg1Reg R: byteSizeReg.
>>         cogit JumpAbove: fillLoop.
>>         cogit RetN: retNoffset.
>>
>>         jumpUnhashed jmpTarget:
>>         (jumpVariableOrEphemeron jmpTarget:
>>         (jumpTooBig jmpTarget:
>>         (jumpNoSpace jmpTarget: cogit Label))).
>>
>>         ^0!
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentationFor64BitSpur>>genInnerPrimitiveNewWithArg: (in
>> category 'primitive generators') -----
>>   genInnerPrimitiveNewWithArg: retNoffset
>>         "Implement primitiveNewWithArg for convenient cases:
>>         - the receiver has a hash
>>         - the receiver is variable and not compiled method
>>         - single word header/num slots < numSlotsMask
>>         - the result fits in eden
>>         See superclass method for dynamic frequencies of formats.
>>         For the moment we implement only arrayFormat, firstByteFormat &
>> firstLongFormat"
>>
>>         | headerReg fillReg instSpecReg byteSizeReg maxSlots
>>           jumpArrayTooBig jumpByteTooBig jumpLongTooBig
>>           jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
>>           jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace
>> jumpHasSlots fillLoop skip |
>>         <var: 'skip' type: #'AbstractInstruction *'>
>>         <var: 'fillLoop' type: #'AbstractInstruction *'>
>>         <var: 'jumpHasSlots' type: #'AbstractInstruction *'>
>>         <var: 'jumpNoSpace' type: #'AbstractInstruction *'>
>>         <var: 'jumpUnhashed' type: #'AbstractInstruction *'>
>>         <var: 'jumpByteFormat' type: #'AbstractInstruction *'>
>>         <var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
>>         <var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
>>         <var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
>>         <var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
>>         <var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
>>         <var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
>>         <var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
>>         <var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
>>
>>         "header will contain cl
>
>
> ...
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20151103/9ab0e886/attachment-0001.htm


More information about the Vm-dev mailing list