[Git][ghc/ghc][master] Use TupleSections in CmmParse.y, simplify a few exprs

Marge Bot gitlab at gitlab.haskell.org
Sun Jun 16 23:39:33 UTC 2019



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


Commits:
b965de1e by Ömer Sinan Ağacan at 2019-06-16T23:39:29Z
Use TupleSections in CmmParse.y, simplify a few exprs

- - - - -


1 changed file:

- compiler/cmm/CmmParse.y


Changes:

=====================================
compiler/cmm/CmmParse.y
=====================================
@@ -198,6 +198,8 @@ necessary to the stack to accommodate it (e.g. 2).
 ----------------------------------------------------------------------------- -}
 
 {
+{-# LANGUAGE TupleSections #-}
+
 module CmmParse ( parseCmmFile ) where
 
 import GhcPrelude
@@ -808,7 +810,7 @@ foreign_formals :: { [CmmParse (LocalReg, ForeignHint)] }
         | foreign_formal ',' foreign_formals    { $1 : $3 }
 
 foreign_formal :: { CmmParse (LocalReg, ForeignHint) }
-        : local_lreg            { do e <- $1; return (e, (inferCmmHint (CmmReg (CmmLocal e)))) }
+        : local_lreg            { do e <- $1; return (e, inferCmmHint (CmmReg (CmmLocal e))) }
         | STRING local_lreg     {% do h <- parseCmmHint $1;
                                       return $ do
                                          e <- $2; return (e,h) }
@@ -999,36 +1001,36 @@ machOps = listToUFM $
 callishMachOps :: UniqFM ([CmmExpr] -> (CallishMachOp, [CmmExpr]))
 callishMachOps = listToUFM $
         map (\(x, y) -> (mkFastString x, y)) [
-        ( "write_barrier", (,) MO_WriteBarrier ),
+        ( "write_barrier", (MO_WriteBarrier,)),
         ( "memcpy", memcpyLikeTweakArgs MO_Memcpy ),
         ( "memset", memcpyLikeTweakArgs MO_Memset ),
         ( "memmove", memcpyLikeTweakArgs MO_Memmove ),
         ( "memcmp", memcpyLikeTweakArgs MO_Memcmp ),
 
-        ("prefetch0", (,) $ MO_Prefetch_Data 0),
-        ("prefetch1", (,) $ MO_Prefetch_Data 1),
-        ("prefetch2", (,) $ MO_Prefetch_Data 2),
-        ("prefetch3", (,) $ MO_Prefetch_Data 3),
-
-        ( "popcnt8",  (,) $ MO_PopCnt W8  ),
-        ( "popcnt16", (,) $ MO_PopCnt W16 ),
-        ( "popcnt32", (,) $ MO_PopCnt W32 ),
-        ( "popcnt64", (,) $ MO_PopCnt W64 ),
-
-        ( "pdep8",  (,) $ MO_Pdep W8  ),
-        ( "pdep16", (,) $ MO_Pdep W16 ),
-        ( "pdep32", (,) $ MO_Pdep W32 ),
-        ( "pdep64", (,) $ MO_Pdep W64 ),
-
-        ( "pext8",  (,) $ MO_Pext W8  ),
-        ( "pext16", (,) $ MO_Pext W16 ),
-        ( "pext32", (,) $ MO_Pext W32 ),
-        ( "pext64", (,) $ MO_Pext W64 ),
-
-        ( "cmpxchg8",  (,) $ MO_Cmpxchg W8  ),
-        ( "cmpxchg16", (,) $ MO_Cmpxchg W16 ),
-        ( "cmpxchg32", (,) $ MO_Cmpxchg W32 ),
-        ( "cmpxchg64", (,) $ MO_Cmpxchg W64 )
+        ("prefetch0", (MO_Prefetch_Data 0,)),
+        ("prefetch1", (MO_Prefetch_Data 1,)),
+        ("prefetch2", (MO_Prefetch_Data 2,)),
+        ("prefetch3", (MO_Prefetch_Data 3,)),
+
+        ( "popcnt8",  (MO_PopCnt W8,)),
+        ( "popcnt16", (MO_PopCnt W16,)),
+        ( "popcnt32", (MO_PopCnt W32,)),
+        ( "popcnt64", (MO_PopCnt W64,)),
+
+        ( "pdep8",  (MO_Pdep W8,)),
+        ( "pdep16", (MO_Pdep W16,)),
+        ( "pdep32", (MO_Pdep W32,)),
+        ( "pdep64", (MO_Pdep W64,)),
+
+        ( "pext8",  (MO_Pext W8,)),
+        ( "pext16", (MO_Pext W16,)),
+        ( "pext32", (MO_Pext W32,)),
+        ( "pext64", (MO_Pext W64,)),
+
+        ( "cmpxchg8",  (MO_Cmpxchg W8,)),
+        ( "cmpxchg16", (MO_Cmpxchg W16,)),
+        ( "cmpxchg32", (MO_Cmpxchg W32,)),
+        ( "cmpxchg64", (MO_Cmpxchg W64,))
 
         -- ToDo: the rest, maybe
         -- edit: which rest?



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/b965de1ef0e2770f71d49d66f88df7fa7cd2cd58

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/b965de1ef0e2770f71d49d66f88df7fa7cd2cd58
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/20190616/f4fc3e1f/attachment-0001.html>


More information about the ghc-commits mailing list