[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: AArch64: Remove unused instructions

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Nov 18 09:03:34 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
f21a891e by Sven Tennie at 2023-11-18T04:03:25-05:00
AArch64: Remove unused instructions

As these aren't ever emitted, we don't even know if they work or will
ever be used. If one of them is needed in future, we may easily re-add
it.

Deleted instructions are:
- CMN
- ANDS
- BIC
- BICS
- EON
- ORN
- ROR
- TST
- STP
- LDP
- DMBSY

- - - - -
64d8d36b by Alan Zimmerman at 2023-11-18T04:03:25-05:00
EPA: Replace Monoid with NoAnn

Remove the final Monoid instances in the exact print infrastructure.

For Windows CI

Metric Decrease:
    T5205

- - - - -


5 changed files:

- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Parser/Annotation.hs
- utils/check-exact/Orphans.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -434,7 +434,7 @@ getMovWideImm n w
 
 -- | Arithmetic(immediate)
 --  Allows for 12bit immediates which can be shifted by 0 or 12 bits.
--- Used with ADD, ADDS, SUB, SUBS, CMP, CMN
+-- Used with ADD, ADDS, SUB, SUBS, CMP
 -- See Note [Aarch64 immediates]
 getArithImm :: Integer -> Width -> Maybe Operand
 getArithImm n w
@@ -459,7 +459,7 @@ getArithImm n w
 
 -- |  Logical (immediate)
 -- Allows encoding of some repeated bitpatterns
--- Used with AND, ANDS, EOR, ORR, TST
+-- Used with AND, EOR, ORR
 -- and their aliases which includes at least MOV (bitmask immediate)
 -- See Note [Aarch64 immediates]
 getBitmaskImm :: Integer -> Width -> Maybe Operand


=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -79,7 +79,6 @@ regUsageOfInstr platform instr = case instr of
 
   -- 1. Arithmetic Instructions ------------------------------------------------
   ADD dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
-  CMN l r                  -> usage (regOp l ++ regOp r, [])
   CMP l r                  -> usage (regOp l ++ regOp r, [])
   MSUB dst src1 src2 src3  -> usage (regOp src1 ++ regOp src2 ++ regOp src3, regOp dst)
   MUL dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
@@ -102,9 +101,6 @@ regUsageOfInstr platform instr = case instr of
   -- 3. Logical and Move Instructions ------------------------------------------
   AND dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   ASR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
-  BIC dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
-  BICS dst src1 src2       -> usage (regOp src1 ++ regOp src2, regOp dst)
-  EON dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   EOR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   LSL dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   LSR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
@@ -113,8 +109,6 @@ regUsageOfInstr platform instr = case instr of
   MOVZ dst src             -> usage (regOp src, regOp dst)
   MVN dst src              -> usage (regOp src, regOp dst)
   ORR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
-  ROR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
-  TST src1 src2            -> usage (regOp src1 ++ regOp src2, [])
   -- 4. Branch Instructions ----------------------------------------------------
   J t                      -> usage (regTarget t, [])
   B t                      -> usage (regTarget t, [])
@@ -131,12 +125,8 @@ regUsageOfInstr platform instr = case instr of
   STLR _ src dst           -> usage (regOp src ++ regOp dst, [])
   LDR _ dst src            -> usage (regOp src, regOp dst)
   LDAR _ dst src           -> usage (regOp src, regOp dst)
-  -- TODO is this right? see STR, which I'm only partial about being right?
-  STP _ src1 src2 dst      -> usage (regOp src1 ++ regOp src2 ++ regOp dst, [])
-  LDP _ dst1 dst2 src      -> usage (regOp src, regOp dst1 ++ regOp dst2)
 
   -- 8. Synchronization Instructions -------------------------------------------
-  DMBSY                    -> usage ([], [])
   DMBISH                   -> usage ([], [])
 
   -- 9. Floating Point Instructions --------------------------------------------
@@ -219,7 +209,6 @@ patchRegsOfInstr instr env = case instr of
     DELTA{}             -> instr
     -- 1. Arithmetic Instructions ----------------------------------------------
     ADD o1 o2 o3   -> ADD (patchOp o1) (patchOp o2) (patchOp o3)
-    CMN o1 o2      -> CMN (patchOp o1) (patchOp o2)
     CMP o1 o2      -> CMP (patchOp o1) (patchOp o2)
     MSUB o1 o2 o3 o4 -> MSUB (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4)
     MUL o1 o2 o3   -> MUL (patchOp o1) (patchOp o2) (patchOp o3)
@@ -242,11 +231,7 @@ patchRegsOfInstr instr env = case instr of
 
     -- 3. Logical and Move Instructions ----------------------------------------
     AND o1 o2 o3   -> AND  (patchOp o1) (patchOp o2) (patchOp o3)
-    ANDS o1 o2 o3  -> ANDS (patchOp o1) (patchOp o2) (patchOp o3)
     ASR o1 o2 o3   -> ASR  (patchOp o1) (patchOp o2) (patchOp o3)
-    BIC o1 o2 o3   -> BIC  (patchOp o1) (patchOp o2) (patchOp o3)
-    BICS o1 o2 o3  -> BICS (patchOp o1) (patchOp o2) (patchOp o3)
-    EON o1 o2 o3   -> EON  (patchOp o1) (patchOp o2) (patchOp o3)
     EOR o1 o2 o3   -> EOR  (patchOp o1) (patchOp o2) (patchOp o3)
     LSL o1 o2 o3   -> LSL  (patchOp o1) (patchOp o2) (patchOp o3)
     LSR o1 o2 o3   -> LSR  (patchOp o1) (patchOp o2) (patchOp o3)
@@ -255,8 +240,6 @@ patchRegsOfInstr instr env = case instr of
     MOVZ o1 o2     -> MOVZ (patchOp o1) (patchOp o2)
     MVN o1 o2      -> MVN  (patchOp o1) (patchOp o2)
     ORR o1 o2 o3   -> ORR  (patchOp o1) (patchOp o2) (patchOp o3)
-    ROR o1 o2 o3   -> ROR  (patchOp o1) (patchOp o2) (patchOp o3)
-    TST o1 o2      -> TST  (patchOp o1) (patchOp o2)
 
     -- 4. Branch Instructions --------------------------------------------------
     J t            -> J (patchTarget t)
@@ -274,11 +257,8 @@ patchRegsOfInstr instr env = case instr of
     STLR f o1 o2   -> STLR f (patchOp o1) (patchOp o2)
     LDR f o1 o2    -> LDR f (patchOp o1) (patchOp o2)
     LDAR f o1 o2   -> LDAR f (patchOp o1) (patchOp o2)
-    STP f o1 o2 o3 -> STP f (patchOp o1) (patchOp o2) (patchOp o3)
-    LDP f o1 o2 o3 -> LDP f (patchOp o1) (patchOp o2) (patchOp o3)
 
     -- 8. Synchronization Instructions -----------------------------------------
-    DMBSY          -> DMBSY
     DMBISH         -> DMBISH
 
     -- 9. Floating Point Instructions ------------------------------------------
@@ -560,7 +540,6 @@ data Instr
     -- | ADDS Operand Operand Operand -- rd = rn + rm
     -- | ADR ...
     -- | ADRP ...
-    | CMN Operand Operand -- rd + op2
     | CMP Operand Operand -- rd - op2
     -- | MADD ...
     -- | MNEG ...
@@ -601,11 +580,7 @@ data Instr
 
     -- 3. Logical and Move Instructions ----------------------------------------
     | AND Operand Operand Operand -- rd = rn & op2
-    | ANDS Operand Operand Operand -- rd = rn & op2
     | ASR Operand Operand Operand -- rd = rn ≫ rm  or  rd = rn ≫ #i, i is 6 bits
-    | BIC Operand Operand Operand -- rd = rn & ~op2
-    | BICS Operand Operand Operand -- rd = rn & ~op2
-    | EON Operand Operand Operand -- rd = rn ⊕ ~op2
     | EOR Operand Operand Operand -- rd = rn ⊕ op2
     | LSL Operand Operand Operand -- rd = rn ≪ rm  or rd = rn ≪ #i, i is 6 bits
     | LSR Operand Operand Operand -- rd = rn ≫ rm  or rd = rn ≫ #i, i is 6 bits
@@ -614,18 +589,13 @@ data Instr
     -- | MOVN Operand Operand
     | MOVZ Operand Operand
     | MVN Operand Operand -- rd = ~rn
-    | ORN Operand Operand Operand -- rd = rn | ~op2
     | ORR Operand Operand Operand -- rd = rn | op2
-    | ROR Operand Operand Operand -- rd = rn ≫ rm  or  rd = rn ≫ #i, i is 6 bits
-    | TST Operand Operand -- rn & op2
     -- Load and stores.
     -- TODO STR/LDR might want to change to STP/LDP with XZR for the second register.
     | STR Format Operand Operand -- str Xn, address-mode // Xn -> *addr
     | STLR Format Operand Operand -- stlr Xn, address-mode // Xn -> *addr
     | LDR Format Operand Operand -- ldr Xn, address-mode // Xn <- *addr
     | LDAR Format Operand Operand -- ldar Xn, address-mode // Xn <- *addr
-    | STP Format Operand Operand Operand -- stp Xn, Xm, address-mode // Xn -> *addr, Xm -> *(addr + 8)
-    | LDP Format Operand Operand Operand -- stp Xn, Xm, address-mode // Xn <- *addr, Xm <- *(addr + 8)
 
     -- Conditional instructions
     | CSET Operand Cond   -- if(cond) op <- 1 else op <- 0
@@ -639,7 +609,6 @@ data Instr
     | BCOND Cond Target   -- branch with condition. b.<cond>
 
     -- 8. Synchronization Instructions -----------------------------------------
-    | DMBSY
     | DMBISH
     -- 9. Floating Point Instructions
     -- Float ConVerT
@@ -675,7 +644,6 @@ instrCon i =
       PUSH_STACK_FRAME{} -> "PUSH_STACK_FRAME"
       POP_STACK_FRAME{} -> "POP_STACK_FRAME"
       ADD{} -> "ADD"
-      CMN{} -> "CMN"
       CMP{} -> "CMP"
       MSUB{} -> "MSUB"
       MUL{} -> "MUL"
@@ -690,11 +658,7 @@ instrCon i =
       SBFX{} -> "SBFX"
       UBFX{} -> "UBFX"
       AND{} -> "AND"
-      ANDS{} -> "ANDS"
       ASR{} -> "ASR"
-      BIC{} -> "BIC"
-      BICS{} -> "BICS"
-      EON{} -> "EON"
       EOR{} -> "EOR"
       LSL{} -> "LSL"
       LSR{} -> "LSR"
@@ -702,16 +666,11 @@ instrCon i =
       MOVK{} -> "MOVK"
       MOVZ{} -> "MOVZ"
       MVN{} -> "MVN"
-      ORN{} -> "ORN"
       ORR{} -> "ORR"
-      ROR{} -> "ROR"
-      TST{} -> "TST"
       STR{} -> "STR"
       STLR{} -> "STLR"
       LDR{} -> "LDR"
       LDAR{} -> "LDAR"
-      STP{} -> "STP"
-      LDP{} -> "LDP"
       CSET{} -> "CSET"
       CBZ{} -> "CBZ"
       CBNZ{} -> "CBNZ"
@@ -719,7 +678,6 @@ instrCon i =
       B{} -> "B"
       BL{} -> "BL"
       BCOND{} -> "BCOND"
-      DMBSY{} -> "DMBSY"
       DMBISH{} -> "DMBISH"
       FCVT{} -> "FCVT"
       SCVTF{} -> "SCVTF"


=====================================
compiler/GHC/CmmToAsm/AArch64/Ppr.hs
=====================================
@@ -370,7 +370,6 @@ pprInstr platform instr = case instr of
   ADD  o1 o2 o3
     | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> op3 (text "\tfadd") o1 o2 o3
     | otherwise -> op3 (text "\tadd") o1 o2 o3
-  CMN  o1 o2    -> op2 (text "\tcmn") o1 o2
   CMP  o1 o2
     | isFloatOp o1 && isFloatOp o2 -> op2 (text "\tfcmp") o1 o2
     | otherwise -> op2 (text "\tcmp") o1 o2
@@ -405,11 +404,7 @@ pprInstr platform instr = case instr of
 
   -- 3. Logical and Move Instructions ------------------------------------------
   AND o1 o2 o3  -> op3 (text "\tand") o1 o2 o3
-  ANDS o1 o2 o3 -> op3 (text "\tands") o1 o2 o3
   ASR o1 o2 o3  -> op3 (text "\tasr") o1 o2 o3
-  BIC o1 o2 o3  -> op3 (text "\tbic") o1 o2 o3
-  BICS o1 o2 o3 -> op3 (text "\tbics") o1 o2 o3
-  EON o1 o2 o3  -> op3 (text "\teon") o1 o2 o3
   EOR o1 o2 o3  -> op3 (text "\teor") o1 o2 o3
   LSL o1 o2 o3  -> op3 (text "\tlsl") o1 o2 o3
   LSR o1 o2 o3  -> op3 (text "\tlsr") o1 o2 o3
@@ -419,10 +414,7 @@ pprInstr platform instr = case instr of
   MOVK o1 o2    -> op2 (text "\tmovk") o1 o2
   MOVZ o1 o2    -> op2 (text "\tmovz") o1 o2
   MVN o1 o2     -> op2 (text "\tmvn") o1 o2
-  ORN o1 o2 o3  -> op3 (text "\torn") o1 o2 o3
   ORR o1 o2 o3  -> op3 (text "\torr") o1 o2 o3
-  ROR o1 o2 o3  -> op3 (text "\tror") o1 o2 o3
-  TST o1 o2     -> op2 (text "\ttst") o1 o2
 
   -- 4. Branch Instructions ----------------------------------------------------
   J t            -> pprInstr platform (B t)
@@ -526,12 +518,9 @@ pprInstr platform instr = case instr of
   LDR _f o1 o2 -> op2 (text "\tldr") o1 o2
   LDAR _f o1 o2 -> op2 (text "\tldar") o1 o2
 
-  STP _f o1 o2 o3 -> op3 (text "\tstp") o1 o2 o3
-  LDP _f o1 o2 o3 -> op3 (text "\tldp") o1 o2 o3
-
   -- 8. Synchronization Instructions -------------------------------------------
-  DMBSY -> line $ text "\tdmb sy"
   DMBISH -> line $ text "\tdmb ish"
+
   -- 9. Floating Point Instructions --------------------------------------------
   FCVT o1 o2 -> op2 (text "\tfcvt") o1 o2
   SCVTF o1 o2 -> op2 (text "\tscvtf") o1 o2


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -1393,7 +1393,7 @@ instance (Semigroup a) => Semigroup (EpAnn a) where
    -- annotations must follow it. So we combine them which yields the
    -- largest span
 
-instance Semigroup Anchor where
+instance Semigroup EpaLocation where
   EpaSpan s1 m1    <> EpaSpan s2 m2     = EpaSpan (combineRealSrcSpans s1 s2) (liftA2 combineBufSpans m1 m2)
   EpaSpan s1 m1    <> _                 = EpaSpan s1 m1
   _                <> EpaSpan s2 m2     = EpaSpan s2 m2


=====================================
utils/check-exact/Orphans.hs
=====================================
@@ -5,65 +5,61 @@ module Orphans where
 
 import GHC hiding (EpaComment)
 
--- ---------------------------------------------------------------------
--- Orphan NoAnn instances. See https://gitlab.haskell.org/ghc/ghc/-/issues/20372
+-- -- ---------------------------------------------------------------------
 
 instance NoAnn [a] where
   noAnn = []
 
-instance NoAnn AnnPragma where
-  noAnn = AnnPragma noAnn noAnn noAnn
-
-instance NoAnn EpAnnImportDecl where
-  noAnn = EpAnnImportDecl noAnn  Nothing  Nothing  Nothing  Nothing  Nothing
+instance (NoAnn a, NoAnn b) => NoAnn (a, b) where
+  noAnn = (noAnn, noAnn)
 
-instance NoAnn AnnParen where
-  noAnn = AnnParen AnnParens noAnn noAnn
+instance NoAnn EpaLocation where
+  noAnn = EpaDelta (SameLine 0) []
 
-instance NoAnn HsRuleAnn where
-  noAnn = HsRuleAnn Nothing Nothing noAnn
+instance NoAnn EpAnnSumPat where
+  noAnn = EpAnnSumPat [] [] []
 
-instance NoAnn AnnSig where
-  noAnn = AnnSig noAnn  noAnn
+instance NoAnn AnnPragma where
+  noAnn = AnnPragma noAnn noAnn []
 
-instance NoAnn GrhsAnn where
-  noAnn = GrhsAnn Nothing  noAnn
+instance NoAnn AddEpAnn where
+  noAnn = AddEpAnn noAnn noAnn
 
-instance NoAnn EpAnnUnboundVar where
-  noAnn = EpAnnUnboundVar noAnn  noAnn
+instance NoAnn AnnKeywordId where
+  noAnn = Annlarrowtail  {- gotta pick one -}
 
-instance (NoAnn a, NoAnn b) => NoAnn (a, b) where
-  noAnn = (noAnn, noAnn)
+instance NoAnn AnnParen where
+  noAnn = AnnParen AnnParens noAnn noAnn
 
-instance NoAnn AnnExplicitSum where
-  noAnn = AnnExplicitSum noAnn  noAnn  noAnn  noAnn
+instance NoAnn AnnsIf where
+  noAnn = AnnsIf noAnn noAnn noAnn Nothing Nothing
 
 instance NoAnn EpAnnHsCase where
   noAnn = EpAnnHsCase noAnn noAnn noAnn
 
-instance NoAnn AnnsIf where
-  noAnn = AnnsIf noAnn noAnn noAnn noAnn noAnn
-
-instance NoAnn (Maybe a) where
-  noAnn = Nothing
+instance NoAnn AnnFieldLabel where
+  noAnn = AnnFieldLabel Nothing
 
 instance NoAnn AnnProjection where
   noAnn = AnnProjection noAnn noAnn
 
-instance NoAnn AnnFieldLabel where
-  noAnn = AnnFieldLabel Nothing
+instance NoAnn AnnExplicitSum where
+  noAnn = AnnExplicitSum noAnn noAnn noAnn noAnn
 
-instance NoAnn EpaLocation where
-  noAnn = EpaDelta (SameLine 0) []
+instance NoAnn EpAnnUnboundVar where
+  noAnn = EpAnnUnboundVar noAnn  noAnn
 
-instance NoAnn AddEpAnn where
-  noAnn = AddEpAnn noAnn noAnn
+instance NoAnn GrhsAnn where
+  noAnn = GrhsAnn Nothing noAnn
 
-instance NoAnn AnnKeywordId where
-  noAnn = Annlarrowtail  {- gotta pick one -}
+instance NoAnn HsRuleAnn where
+  noAnn = HsRuleAnn Nothing Nothing noAnn
 
-instance NoAnn EpAnnSumPat where
-  noAnn = EpAnnSumPat noAnn  noAnn  noAnn
+instance NoAnn AnnSig where
+  noAnn = AnnSig noAnn noAnn
+
+instance NoAnn EpAnnImportDecl where
+  noAnn = EpAnnImportDecl noAnn  Nothing  Nothing  Nothing  Nothing  Nothing
 
 instance NoAnn AnnsModule where
-  noAnn = AnnsModule [] mempty Nothing
+  noAnn = AnnsModule [] [] Nothing



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/920d12db780c49d18e430cd5b57231794c95d363...64d8d36be9786186033e0e0ff94b9654f248b065

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/920d12db780c49d18e430cd5b57231794c95d363...64d8d36be9786186033e0e0ff94b9654f248b065
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20231118/4218b837/attachment-0001.html>


More information about the ghc-commits mailing list