[commit: ghc] wip/llvm-3.6: llvmGen: metadata no longer marked with `metadata` keyword (bde6e36)

git at git.haskell.org git at git.haskell.org
Mon Jan 19 23:16:35 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/llvm-3.6
Link       : http://ghc.haskell.org/trac/ghc/changeset/bde6e36379ee8cf7238dcb6bd23d09152844ac34/ghc

>---------------------------------------------------------------

commit bde6e36379ee8cf7238dcb6bd23d09152844ac34
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Sun Jan 4 18:25:24 2015 -0500

    llvmGen: metadata no longer marked with `metadata` keyword
    
    As of LLVM 3.6


>---------------------------------------------------------------

bde6e36379ee8cf7238dcb6bd23d09152844ac34
 compiler/llvmGen/Llvm/MetaData.hs | 14 +++++++-------
 compiler/llvmGen/Llvm/PpLlvm.hs   | 12 ++++++++----
 2 files changed, 15 insertions(+), 11 deletions(-)

diff --git a/compiler/llvmGen/Llvm/MetaData.hs b/compiler/llvmGen/Llvm/MetaData.hs
index 36efcd7..e1e63c9 100644
--- a/compiler/llvmGen/Llvm/MetaData.hs
+++ b/compiler/llvmGen/Llvm/MetaData.hs
@@ -20,12 +20,12 @@ import Outputable
 --   information. They consist of metadata strings, metadata nodes, regular
 --   LLVM values (both literals and references to global variables) and
 --   metadata expressions (i.e., recursive data type). Some examples:
---     !{ metadata !"hello", metadata !0, i32 0 }
---     !{ metadata !1, metadata !{ i32 0 } }
+--     !{ !"hello", !0, i32 0 }
+--     !{ !1, !{ i32 0 } }
 --
 -- * Metadata nodes -- global metadata variables that attach a metadata
 --   expression to a number. For example:
---     !0 = metadata !{ [<metadata expressions>] !}
+--     !0 = !{ [<metadata expressions>] !}
 --
 -- * Named metadata -- global metadata variables that attach a metadata nodes
 --   to a name. Used ONLY to communicated module level information to LLVM
@@ -39,7 +39,7 @@ import Outputable
 -- * Attach to instructions -- metadata can be attached to LLVM instructions
 --   using a specific reference as follows:
 --     %l = load i32* @glob, !nontemporal !10
---     %m = load i32* @glob, !nontemporal !{ i32 0, metadata !{ i32 0 } }
+--     %m = load i32* @glob, !nontemporal !{ i32 0, !{ i32 0 } }
 --   Only metadata nodes or expressions can be attached, named metadata cannot.
 --   Refer to LLVM documentation for which instructions take metadata and its
 --   meaning.
@@ -63,10 +63,10 @@ data MetaExpr = MetaStr LMString
               deriving (Eq)
 
 instance Outputable MetaExpr where
-  ppr (MetaStr    s ) = text "metadata !\"" <> ftext s <> char '"'
-  ppr (MetaNode   n ) = text "metadata !" <> int n
+  ppr (MetaStr    s ) = text "!\"" <> ftext s <> char '"'
+  ppr (MetaNode   n ) = text "!" <> int n
   ppr (MetaVar    v ) = ppr v
-  ppr (MetaStruct es) = text "metadata !{ " <> ppCommaJoin es <> char '}'
+  ppr (MetaStruct es) = text "!{ " <> ppCommaJoin es <> char '}'
 
 -- | Associates some metadata with a specific label for attaching to an
 -- instruction.
diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs
index de76766..0b3deac 100644
--- a/compiler/llvmGen/Llvm/PpLlvm.hs
+++ b/compiler/llvmGen/Llvm/PpLlvm.hs
@@ -117,11 +117,11 @@ ppLlvmMeta (MetaNamed n m)
 
 -- | Print out an LLVM metadata value.
 ppLlvmMetaExpr :: MetaExpr -> SDoc
-ppLlvmMetaExpr (MetaStr    s ) = text "metadata !" <> doubleQuotes (ftext s)
-ppLlvmMetaExpr (MetaNode   n ) = text "metadata !" <> int n
+ppLlvmMetaExpr (MetaStr    s ) = text "!" <> doubleQuotes (ftext s)
+ppLlvmMetaExpr (MetaNode   n ) = text "!" <> int n
 ppLlvmMetaExpr (MetaVar    v ) = ppr v
 ppLlvmMetaExpr (MetaStruct es) =
-    text "metadata !{" <> hsep (punctuate comma (map ppLlvmMetaExpr es)) <> char '}'
+    text "!{" <> hsep (punctuate comma (map ppLlvmMetaExpr es)) <> char '}'
 
 
 -- | Print out a list of function definitions.
@@ -272,7 +272,7 @@ ppCall ct fptr args attrs = case fptr of
     where
         ppCall' (LlvmFunctionDecl _ _ cc ret argTy params _) =
             let tc = if ct == TailCall then text "tail " else empty
-                ppValues = ppCommaJoin args
+                ppValues = hsep $ punctuate comma $ map ppCallMetaExpr args
                 ppArgTy  = (ppCommaJoin $ map fst params) <>
                            (case argTy of
                                VarArgs   -> text ", ..."
@@ -283,6 +283,10 @@ ppCall ct fptr args attrs = case fptr of
                     <> fnty <+> ppName fptr <> lparen <+> ppValues
                     <+> rparen <+> attrDoc
 
+        -- Metadata needs to be marked as having the `metadata` type when used
+        -- in a call argument
+        ppCallMetaExpr (MetaVar v) = ppr v
+        ppCallMetaExpr v           = text "metadata" <+> ppr v
 
 ppMachOp :: LlvmMachOp -> LlvmVar -> LlvmVar -> SDoc
 ppMachOp op left right =



More information about the ghc-commits mailing list