Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • compiler/GHC/CmmToAsm/RV64/CodeGen.hs
    ... ... @@ -1481,7 +1481,7 @@ assignReg_FltCode = assignReg_IntCode
    1481 1481
     genJump :: CmmExpr {-the branch target-} -> NatM InstrBlock
    
    1482 1482
     genJump expr = do
    
    1483 1483
       (target, _format, code) <- getSomeReg expr
    
    1484
    -  return (code `appOL` unitOL (annExpr expr (B (TReg target))))
    
    1484
    +  return (code `appOL` unitOL (annExpr expr (J (TReg target))))
    
    1485 1485
     
    
    1486 1486
     -- -----------------------------------------------------------------------------
    
    1487 1487
     --  Unconditional branches
    
    ... ... @@ -2226,5 +2226,6 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks =
    2226 2226
           BCOND {} -> long_bc_jump_size
    
    2227 2227
           B (TBlock _) -> long_b_jump_size
    
    2228 2228
           B (TReg _) -> 1
    
    2229
    +      J op -> instr_size (B op)
    
    2229 2230
           BL _ _ -> 1
    
    2230 2231
           J_TBL {} -> 1

  • compiler/GHC/CmmToAsm/RV64/Instr.hs
    ... ... @@ -97,6 +97,7 @@ regUsageOfInstr platform instr = case instr of
    97 97
       ORI dst src1 _ -> usage (regOp src1, regOp dst)
    
    98 98
       XORI dst src1 _ -> usage (regOp src1, regOp dst)
    
    99 99
       J_TBL _ _ t -> usage ([t], [])
    
    100
    +  J t -> usage (regTarget t, [])
    
    100 101
       B t -> usage (regTarget t, [])
    
    101 102
       BCOND _ l r t -> usage (regTarget t ++ regOp l ++ regOp r, [])
    
    102 103
       BL t ps -> usage (t : ps, callerSavedRegisters)
    
    ... ... @@ -195,6 +196,7 @@ patchRegsOfInstr instr env = case instr of
    195 196
       ORI o1 o2 o3 -> ORI (patchOp o1) (patchOp o2) (patchOp o3)
    
    196 197
       XORI o1 o2 o3 -> XORI (patchOp o1) (patchOp o2) (patchOp o3)
    
    197 198
       J_TBL ids mbLbl t -> J_TBL ids mbLbl (env t)
    
    199
    +  J t -> J (patchTarget t)
    
    198 200
       B t -> B (patchTarget t)
    
    199 201
       BL t ps -> BL (patchReg t) ps
    
    200 202
       BCOND c o1 o2 t -> BCOND c (patchOp o1) (patchOp o2) (patchTarget t)
    
    ... ... @@ -235,6 +237,7 @@ isJumpishInstr :: Instr -> Bool
    235 237
     isJumpishInstr instr = case instr of
    
    236 238
       ANN _ i -> isJumpishInstr i
    
    237 239
       J_TBL {} -> True
    
    240
    +  J {} -> True
    
    238 241
       B {} -> True
    
    239 242
       BL {} -> True
    
    240 243
       BCOND {} -> True
    
    ... ... @@ -243,6 +246,7 @@ isJumpishInstr instr = case instr of
    243 246
     canFallthroughTo :: Instr -> BlockId -> Bool
    
    244 247
     canFallthroughTo insn bid =
    
    245 248
       case insn of
    
    249
    +    J (TBlock target) -> bid == target
    
    246 250
         B (TBlock target) -> bid == target
    
    247 251
         BCOND _ _ _ (TBlock target) -> bid == target
    
    248 252
         J_TBL targets _ _ -> all isTargetBid targets
    
    ... ... @@ -256,6 +260,7 @@ canFallthroughTo insn bid =
    256 260
     jumpDestsOfInstr :: Instr -> [BlockId]
    
    257 261
     jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i
    
    258 262
     jumpDestsOfInstr (J_TBL ids _mbLbl _r) = catMaybes ids
    
    263
    +jumpDestsOfInstr (J t) = [id | TBlock id <- [t]]
    
    259 264
     jumpDestsOfInstr (B t) = [id | TBlock id <- [t]]
    
    260 265
     jumpDestsOfInstr (BCOND _ _ _ t) = [id | TBlock id <- [t]]
    
    261 266
     jumpDestsOfInstr _ = []
    
    ... ... @@ -269,6 +274,7 @@ patchJumpInstr instr patchF =
    269 274
       case instr of
    
    270 275
         ANN d i -> ANN d (patchJumpInstr i patchF)
    
    271 276
         J_TBL ids mbLbl r -> J_TBL (map (fmap patchF) ids) mbLbl r
    
    277
    +    J (TBlock bid) -> J (TBlock (patchF bid))
    
    272 278
         B (TBlock bid) -> B (TBlock (patchF bid))
    
    273 279
         BCOND c o1 o2 (TBlock bid) -> BCOND c o1 o2 (TBlock (patchF bid))
    
    274 280
         _ -> panic $ "patchJumpInstr: " ++ instrCon instr
    
    ... ... @@ -475,7 +481,7 @@ allocMoreStack platform slots proc@(CmmProc info lbl live (ListGraph code)) = do
    475 481
               block' = foldr insert_dealloc [] insns
    
    476 482
     
    
    477 483
           insert_dealloc insn r = case insn of
    
    478
    -        J_TBL {} -> dealloc ++ (insn : r)
    
    484
    +        J {} -> dealloc ++ (insn : r)
    
    479 485
             ANN _ e -> insert_dealloc e r
    
    480 486
             _other
    
    481 487
               | jumpDestsOfInstr insn /= [] ->
    
    ... ... @@ -591,6 +597,8 @@ data Instr
    591 597
         --
    
    592 598
         -- @if(o2 cond o3) op <- 1 else op <- 0@
    
    593 599
         CSET Operand Operand Operand Cond
    
    600
    +    -- | Like B, but only used for non-local jumps. Used to distinguish genJumps from others.
    
    601
    +  | J Target
    
    594 602
       | -- | A jump instruction with data for switch/jump tables
    
    595 603
         J_TBL [Maybe BlockId] (Maybe CLabel) Reg
    
    596 604
       | -- | Unconditional jump (no linking)
    
    ... ... @@ -663,6 +671,7 @@ instrCon i =
    663 671
         LDRU {} -> "LDRU"
    
    664 672
         CSET {} -> "CSET"
    
    665 673
         J_TBL {} -> "J_TBL"
    
    674
    +    J {} -> "J"
    
    666 675
         B {} -> "B"
    
    667 676
         BL {} -> "BL"
    
    668 677
         BCOND {} -> "BCOND"
    

  • compiler/GHC/CmmToAsm/RV64/Ppr.hs
    ... ... @@ -543,6 +543,7 @@ pprInstr platform instr = case instr of
    543 543
         | otherwise -> op3 (text "\taddi") o1 o2 (OpImm (ImmInt 0))
    
    544 544
       ORI o1 o2 o3 -> op3 (text "\tori") o1 o2 o3
    
    545 545
       XORI o1 o2 o3 -> op3 (text "\txori") o1 o2 o3
    
    546
    +  J o1 -> pprInstr platform (B o1)
    
    546 547
       J_TBL _ _ r -> pprInstr platform (B (TReg r))
    
    547 548
       B l | isLabel l -> line $ text "\tjal" <+> pprOp platform x0 <> comma <+> getLabel platform l
    
    548 549
       B (TReg r) -> line $ text "\tjalr" <+> pprOp platform x0 <> comma <+> pprReg W64 r <> comma <+> text "0"