Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/CmmToAsm/RV64/Instr.hs
    ... ... @@ -138,21 +138,6 @@ regUsageOfInstr platform instr = case instr of
    138 138
         usage (regOp op1 ++ regOp op2 ++ regOp op3, regOp op1)
    
    139 139
       _ -> panic $ "regUsageOfInstr: " ++ instrCon instr
    
    140 140
       where
    
    141
    -    -- filtering the usage is necessary, otherwise the register
    
    142
    -    -- allocator will try to allocate pre-defined fixed stg
    
    143
    -    -- registers as well, as they show up.
    
    144
    -    usage :: ([(Reg, Format)], [(Reg, Format)]) -> RegUsage
    
    145
    -    usage (srcRegs, dstRegs) =
    
    146
    -      RU
    
    147
    -        (map mkFmt $ filter (interesting platform) srcRegs)
    
    148
    -        (map mkFmt $ filter (interesting platform) dstRegs)
    
    149
    -
    
    150
    -    mkFmt (r, fmt) = RegWithFormat r fmt
    
    151
    -
    
    152
    -    regAddr :: AddrMode -> [(Reg, Format)]
    
    153
    -    regAddr (AddrRegImm r1 _imm) = [(r1, II64)]
    
    154
    -    regAddr (AddrReg r1) = [(r1, II64)]
    
    155
    -
    
    156 141
         regOp :: Operand -> [(Reg, Format)]
    
    157 142
         regOp (OpReg fmt r1) = [(r1, fmt)]
    
    158 143
         regOp (OpAddr a) = regAddr a
    
    ... ... @@ -162,10 +147,25 @@ regUsageOfInstr platform instr = case instr of
    162 147
         regTarget (TBlock _bid) = []
    
    163 148
         regTarget (TReg r1) = [(r1, II64)]
    
    164 149
     
    
    165
    -    -- Is this register interesting for the register allocator?
    
    166
    -    interesting :: Platform -> (Reg, Format) -> Bool
    
    167
    -    interesting _ ((RegVirtual _), _) = True
    
    168
    -    interesting platform ((RegReal (RealRegSingle i)), _) = freeReg platform i
    
    150
    +    regAddr :: AddrMode -> [(Reg, Format)]
    
    151
    +    regAddr (AddrRegImm r1 _imm) = [(r1, II64)]
    
    152
    +    regAddr (AddrReg r1) = [(r1, II64)]
    
    153
    +
    
    154
    +    -- filtering the usage is necessary, otherwise the register
    
    155
    +    -- allocator will try to allocate pre-defined fixed stg
    
    156
    +    -- registers as well, as they show up.
    
    157
    +    usage :: ([(Reg, Format)], [(Reg, Format)]) -> RegUsage
    
    158
    +    usage (srcRegs, dstRegs) =
    
    159
    +      RU
    
    160
    +        (map mkFmt $ filter (interesting platform) srcRegs)
    
    161
    +        (map mkFmt $ filter (interesting platform) dstRegs)
    
    162
    +      where
    
    163
    +        mkFmt (r, fmt) = RegWithFormat r fmt
    
    164
    +
    
    165
    +        -- Is this register interesting for the register allocator?
    
    166
    +        interesting :: Platform -> (Reg, Format) -> Bool
    
    167
    +        interesting _ ((RegVirtual _), _) = True
    
    168
    +        interesting platform ((RegReal (RealRegSingle i)), _) = freeReg platform i
    
    169 169
     
    
    170 170
     -- | Caller-saved registers (according to calling convention)
    
    171 171
     --
    
    ... ... @@ -240,7 +240,7 @@ patchRegsOfInstr instr env = case instr of
    240 240
       VSUB o1 o2 o3 -> VSUB (patchOp o1) (patchOp o2) (patchOp o3)
    
    241 241
       VMUL o1 o2 o3 -> VMUL (patchOp o1) (patchOp o2) (patchOp o3)
    
    242 242
       VQUOT mbS o1 o2 o3 -> VQUOT mbS (patchOp o1) (patchOp o2) (patchOp o3)
    
    243
    -  VREM s o1 o2 o3 -> VREM s (patchOp o1) (patchOp o2) (patchOp o3) 
    
    243
    +  VREM s o1 o2 o3 -> VREM s (patchOp o1) (patchOp o2) (patchOp o3)
    
    244 244
       VSMIN o1 o2 o3 -> VSMIN (patchOp o1) (patchOp o2) (patchOp o3)
    
    245 245
       VSMAX o1 o2 o3 -> VSMAX (patchOp o1) (patchOp o2) (patchOp o3)
    
    246 246
       VUMIN o1 o2 o3 -> VUMIN (patchOp o1) (patchOp o2) (patchOp o3)
    
    ... ... @@ -452,7 +452,7 @@ mkRegRegMoveInstr :: Format -> Reg -> Reg -> Instr
    452 452
     mkRegRegMoveInstr fmt src dst = ANN desc instr
    
    453 453
       where
    
    454 454
         desc = text "Reg->Reg Move: " <> ppr src <> text " -> " <> ppr dst
    
    455
    -    instr = MOV (operandFromReg fmt dst) (operandFromReg fmt src)
    
    455
    +    instr = MOV (OpReg fmt dst) (OpReg fmt src)
    
    456 456
     
    
    457 457
     -- | Take the source and destination from this (potential) reg -> reg move instruction
    
    458 458
     --
    
    ... ... @@ -678,8 +678,7 @@ data Instr
    678 678
         -- - fmsub : d = - r1 * r2 + r3
    
    679 679
         -- - fnmadd: d = - r1 * r2 - r3
    
    680 680
         FMA FMASign Operand Operand Operand Operand
    
    681
    -  | -- TODO: Care about the variants (<instr>.x.y) -> sum type
    
    682
    -    VMV Operand Operand
    
    681
    +  | VMV Operand Operand
    
    683 682
       | VID Operand
    
    684 683
       | VMSEQ Operand Operand Operand
    
    685 684
       | VMERGE Operand Operand Operand Operand
    
    ... ... @@ -816,21 +815,17 @@ data Operand
    816 815
         OpAddr AddrMode
    
    817 816
       deriving (Eq, Show)
    
    818 817
     
    
    819
    --- TODO: This just wraps a constructor... Inline?
    
    820
    -operandFromReg :: Format -> Reg -> Operand
    
    821
    -operandFromReg = OpReg
    
    822
    -
    
    823 818
     operandFromRegNo :: Format -> RegNo -> Operand
    
    824
    -operandFromRegNo fmt = operandFromReg fmt . regSingle
    
    819
    +operandFromRegNo fmt = OpReg fmt . regSingle
    
    825 820
     
    
    826 821
     zero, ra, sp, gp, tp, fp, tmp :: Operand
    
    827
    -zero = operandFromReg II64 zeroReg
    
    828
    -ra = operandFromReg II64 raReg
    
    829
    -sp = operandFromReg II64 spMachReg
    
    822
    +zero = OpReg II64 zeroReg
    
    823
    +ra = OpReg II64 raReg
    
    824
    +sp = OpReg II64 spMachReg
    
    830 825
     gp = operandFromRegNo II64 3
    
    831 826
     tp = operandFromRegNo II64 4
    
    832 827
     fp = operandFromRegNo II64 8
    
    833
    -tmp = operandFromReg II64 tmpReg
    
    828
    +tmp = OpReg II64 tmpReg
    
    834 829
     
    
    835 830
     x0, x1, x2, x3, x4, x5, x6, x7 :: Operand
    
    836 831
     x8, x9, x10, x11, x12, x13, x14, x15 :: Operand
    
    ... ... @@ -844,13 +839,9 @@ x4 = operandFromRegNo II64 4
    844 839
     x5 = operandFromRegNo II64 x5RegNo
    
    845 840
     x6 = operandFromRegNo II64 6
    
    846 841
     x7 = operandFromRegNo II64 x7RegNo
    
    847
    -
    
    848 842
     x8 = operandFromRegNo II64 8
    
    849
    -
    
    850 843
     x9 = operandFromRegNo II64 9
    
    851
    -
    
    852 844
     x10 = operandFromRegNo II64 x10RegNo
    
    853
    -
    
    854 845
     x11 = operandFromRegNo II64 11
    
    855 846
     x12 = operandFromRegNo II64 12
    
    856 847
     x13 = operandFromRegNo II64 13
    
    ... ... @@ -885,53 +876,29 @@ d4 = operandFromRegNo FF64 36
    885 876
     d5 = operandFromRegNo FF64 37
    
    886 877
     d6 = operandFromRegNo FF64 38
    
    887 878
     d7 = operandFromRegNo FF64 d7RegNo
    
    888
    -
    
    889 879
     d8 = operandFromRegNo FF64 40
    
    890
    -
    
    891 880
     d9 = operandFromRegNo FF64 41
    
    892
    -
    
    893 881
     d10 = operandFromRegNo FF64 d10RegNo
    
    894
    -
    
    895 882
     d11 = operandFromRegNo FF64 43
    
    896
    -
    
    897 883
     d12 = operandFromRegNo FF64 44
    
    898
    -
    
    899 884
     d13 = operandFromRegNo FF64 45
    
    900
    -
    
    901 885
     d14 = operandFromRegNo FF64 46
    
    902
    -
    
    903 886
     d15 = operandFromRegNo FF64 47
    
    904
    -
    
    905 887
     d16 = operandFromRegNo FF64 48
    
    906
    -
    
    907 888
     d17 = operandFromRegNo FF64 d17RegNo
    
    908
    -
    
    909 889
     d18 = operandFromRegNo FF64 50
    
    910
    -
    
    911 890
     d19 = operandFromRegNo FF64 51
    
    912
    -
    
    913 891
     d20 = operandFromRegNo FF64 52
    
    914
    -
    
    915 892
     d21 = operandFromRegNo FF64 53
    
    916
    -
    
    917 893
     d22 = operandFromRegNo FF64 54
    
    918
    -
    
    919 894
     d23 = operandFromRegNo FF64 55
    
    920
    -
    
    921 895
     d24 = operandFromRegNo FF64 56
    
    922
    -
    
    923 896
     d25 = operandFromRegNo FF64 57
    
    924
    -
    
    925 897
     d26 = operandFromRegNo FF64 58
    
    926
    -
    
    927 898
     d27 = operandFromRegNo FF64 59
    
    928
    -
    
    929 899
     d28 = operandFromRegNo FF64 60
    
    930
    -
    
    931 900
     d29 = operandFromRegNo FF64 61
    
    932
    -
    
    933 901
     d30 = operandFromRegNo FF64 62
    
    934
    -
    
    935 902
     d31 = operandFromRegNo FF64 d31RegNo
    
    936 903
     
    
    937 904
     fitsIn12bitImm :: (Num a, Ord a, Bits a) => a -> Bool
    

  • compiler/GHC/CmmToAsm/RV64/Ppr.hs
    ... ... @@ -2,6 +2,7 @@
    2 2
     
    
    3 3
     module GHC.CmmToAsm.RV64.Ppr (pprNatCmmDecl, pprInstr) where
    
    4 4
     
    
    5
    +import Data.Maybe
    
    5 6
     import GHC.Cmm hiding (topInfoTable)
    
    6 7
     import GHC.Cmm.BlockId
    
    7 8
     import GHC.Cmm.CLabel
    
    ... ... @@ -155,7 +156,11 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) =
    155 156
               )
    
    156 157
           )
    
    157 158
       where
    
    158
    -    instrs' = injectVectorConfig (toOL optInstrs)
    
    159
    +    instrs' :: OrdList Instr
    
    160
    +    instrs'
    
    161
    +      | isJust (ncgVectorMinBits config) = injectVectorConfig (toOL optInstrs)
    
    162
    +      | otherwise = toOL optInstrs
    
    163
    +
    
    159 164
         -- TODO: Check if we can  filter more instructions here.
    
    160 165
         -- TODO: Shouldn't this be a more general check on a higher level? And, is this still needed?
    
    161 166
         -- Filter out identity moves. E.g. mov x18, x18 will be dropped.
    
    ... ... @@ -168,8 +173,6 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) =
    168 173
         injectVectorConfig instrs = fst $ foldlOL injectVectorConfig' (nilOL, Nothing) instrs
    
    169 174
     
    
    170 175
         -- TODO: Fuse this with optInstrs
    
    171
    -    -- TODO: Check config and only run this when vectors are configured
    
    172
    -    -- TODO: Check if vectorMinBits is sufficient for the vector config
    
    173 176
         injectVectorConfig' :: (OrdList Instr, Maybe Format) -> Instr -> (OrdList Instr, Maybe Format)
    
    174 177
         injectVectorConfig' (accInstr, configuredVecFmt) currInstr =
    
    175 178
           let configuredVecFmt' Nothing = Nothing
    
    ... ... @@ -217,14 +220,16 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) =
    217 220
                       )
    
    218 221
     
    
    219 222
         configVec :: Format -> Instr
    
    220
    -    configVec (VecFormat length fmt) =
    
    221
    -      VSETIVLI
    
    222
    -        (OpReg II64 zeroReg)
    
    223
    -        (fromIntegral length)
    
    224
    -        ((formatToWidth . scalarFormatFormat) fmt)
    
    225
    -        M1
    
    226
    -        TA
    
    227
    -        MA
    
    223
    +    configVec vFmt@(VecFormat length fmt)
    
    224
    +      | Just vlen <- (ncgVectorMinBits config),
    
    225
    +        (formatInBytes vFmt) * 8 <= fromIntegral vlen =
    
    226
    +          VSETIVLI
    
    227
    +            (OpReg II64 zeroReg)
    
    228
    +            (fromIntegral length)
    
    229
    +            ((formatToWidth . scalarFormatFormat) fmt)
    
    230
    +            M1
    
    231
    +            TA
    
    232
    +            MA
    
    228 233
         configVec fmt = pprPanic "Unsupported vector configuration" ((text . show) fmt)
    
    229 234
     
    
    230 235
         asmLbl = blockLbl blockid
    
    ... ... @@ -620,7 +625,6 @@ pprInstr platform instr = case instr of
    620 625
         | isFloatRegOp o1 && isIntRegOp o2 && isDoubleOp o1 -> op2 (text "\tfmv.d.x") o1 o2
    
    621 626
         | isIntRegOp o1 && isFloatRegOp o2 && isSingleOp o2 -> op2 (text "\tfmv.x.w") o1 o2
    
    622 627
         | isIntRegOp o1 && isFloatRegOp o2 && isDoubleOp o2 -> op2 (text "\tfmv.x.d") o1 o2
    
    623
    -    -- TODO: Why does this NOP (reg1 == reg2) happen?
    
    624 628
         | isVectorRegOp o1 && isVectorRegOp o2 -> op2 (text "\tvmv.v.v") o1 o2
    
    625 629
         | (OpImm (ImmInteger i)) <- o2,
    
    626 630
           fitsIn12bitImm i ->
    
    ... ... @@ -833,7 +837,6 @@ pprInstr platform instr = case instr of
    833 837
       VMERGE o1 o2 o3 o4 -> pprPanic "RV64.pprInstr - VMERGE wrong operands." (pprOps platform [o1, o2, o3, o4])
    
    834 838
       VSLIDEDOWN o1 o2 o3 | allVectorRegOps [o1, o2] && isIntOp o3 -> op3 (text "\tvslidedown.vx") o1 o2 o3
    
    835 839
       VSLIDEDOWN o1 o2 o3 -> pprPanic "RV64.pprInstr - VSLIDEDOWN wrong operands." (pprOps platform [o1, o2, o3])
    
    836
    -  -- TODO: adjust VSETIVLI to contain only format?
    
    837 840
       VSETIVLI (OpReg fmt dst) len width grouping ta ma ->
    
    838 841
         line
    
    839 842
           $ text "\tvsetivli"