Skip to content

Commit

Permalink
Merge branch 'master' of ssh://darcs.haskell.org/srv/darcs/ghc
Browse files Browse the repository at this point in the history
  • Loading branch information
Richard Eisenberg committed Jun 28, 2013
2 parents 6a25e92 + fe44d05 commit 01234ec
Show file tree
Hide file tree
Showing 14 changed files with 1,566 additions and 1,322 deletions.
1 change: 1 addition & 0 deletions compiler/ghc.cabal.in
Expand Up @@ -139,6 +139,7 @@ Library
Literal
Llvm
Llvm.AbsSyn
Llvm.MetaData
Llvm.PpLlvm
Llvm.Types
LlvmCodeGen
Expand Down
11 changes: 7 additions & 4 deletions compiler/llvmGen/Llvm.hs
Expand Up @@ -32,27 +32,30 @@ module Llvm (

-- * Variables and Type System
LlvmVar(..), LlvmStatic(..), LlvmLit(..), LlvmType(..),
LlvmAlias, LMGlobal, LMString, LMSection, LMAlign,
LlvmAlias, LMGlobal(..), LMString, LMSection, LMAlign,
LMConst(..),

-- ** Some basic types
i64, i32, i16, i8, i1, i8Ptr, llvmWord, llvmWordPtr,

-- ** Metadata types
LlvmMetaVal(..), LlvmMetaUnamed(..), LlvmMeta(..), MetaData,
MetaExpr(..), MetaAnnot(..), MetaDecl(..),

-- ** Operations on the type system.
isGlobal, getLitType, getLit, getName, getPlainName, getVarType,
getLink, getStatType, getGlobalVar, getGlobalType, pVarLift, pVarLower,
isGlobal, getLitType, getVarType,
getLink, getStatType, pVarLift, pVarLower,
pLift, pLower, isInt, isFloat, isPointer, isVector, llvmWidthInBits,

-- * Pretty Printing
ppLit, ppName, ppPlainName,
ppLlvmModule, ppLlvmComments, ppLlvmComment, ppLlvmGlobals,
ppLlvmGlobal, ppLlvmFunctionDecls, ppLlvmFunctionDecl, ppLlvmFunctions,
ppLlvmFunction, ppLlvmAlias, ppLlvmAliases, ppLlvmMetas, ppLlvmMeta,

) where

import Llvm.AbsSyn
import Llvm.MetaData
import Llvm.PpLlvm
import Llvm.Types

24 changes: 17 additions & 7 deletions compiler/llvmGen/Llvm/AbsSyn.hs
Expand Up @@ -4,6 +4,7 @@

module Llvm.AbsSyn where

import Llvm.MetaData
import Llvm.Types

import Unique
Expand Down Expand Up @@ -32,7 +33,7 @@ data LlvmModule = LlvmModule {
modAliases :: [LlvmAlias],

-- | LLVM meta data.
modMeta :: [LlvmMeta],
modMeta :: [MetaDecl],

-- | Global variables to include in the module.
modGlobals :: [LMGlobal],
Expand Down Expand Up @@ -165,11 +166,9 @@ data LlvmStatement
{- |
A LLVM statement with metadata attached to it.
-}
| MetaStmt [MetaData] LlvmStatement
| MetaStmt [MetaAnnot] LlvmStatement

deriving (Show, Eq)

type MetaData = (LMString, LlvmMetaUnamed)
deriving (Eq)


-- | Llvm Expressions
Expand Down Expand Up @@ -252,6 +251,17 @@ data LlvmExpression
-}
| Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr]

{- |
Call a function as above but potentially taking metadata as arguments.
* tailJumps: CallType to signal if the function should be tail called
* fnptrval: An LLVM value containing a pointer to a function to be
invoked. Can be indirect. Should be LMFunction type.
* args: Arguments that may include metadata.
* attrs: A list of function attributes for the call. Only NoReturn,
NoUnwind, ReadOnly and ReadNone are valid here.
-}
| CallM LlvmCallType LlvmVar [MetaExpr] [LlvmFuncAttr]

{- |
Merge variables from different basic blocks which are predecessors of this
basic block in a new variable of type tp.
Expand All @@ -278,7 +288,7 @@ data LlvmExpression
{- |
A LLVM expression with metadata attached to it.
-}
| MetaExpr [MetaData] LlvmExpression
| MExpr [MetaAnnot] LlvmExpression

deriving (Show, Eq)
deriving (Eq)

84 changes: 84 additions & 0 deletions compiler/llvmGen/Llvm/MetaData.hs
@@ -0,0 +1,84 @@
--------------------------------------------------------------------------------
-- | The LLVM Metadata System.
--
-- The LLVM metadata feature is poorly documented but roughly follows the
-- following design:
-- * Metadata can be constructed in a few different ways (See below).
-- * After which it can either be attached to LLVM statements to pass along
-- extra information to the optimizer and code generator OR specificially named
-- metadata has an affect on the whole module (i.e., linking behaviour).
--
--
-- # Constructing metadata
-- Metadata comes largely in three forms:
--
-- * Metadata expressions -- these are the raw metadata values that encode
-- 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 } }
--
-- * Metadata nodes -- global metadata variables that attach a metadata
-- expression to a number. For example:
-- !0 = metadata !{ [<metadata expressions>] !}
--
-- * Named metadata -- global metadata variables that attach a metadata nodes
-- to a name. Used ONLY to communicated module level information to LLVM
-- through a meaningful name. For example:
-- !llvm.module.linkage = !{ !0, !1 }
--
--
-- # Using Metadata
-- Using metadata depends on the form it is in:
--
-- * 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 } }
-- Only metadata nodes or expressions can be attached, named metadata cannot.
-- Refer to LLVM documentation for which instructions take metadata and its
-- meaning.
--
-- * As arguments -- llvm functions can take metadata as arguments, for
-- example:
-- call void @llvm.dbg.value(metadata !{ i32 0 }, i64 0, metadata !1)
-- As with instructions, only metadata nodes or expressions can be attached.
--
-- * As a named metadata -- Here the metadata is simply declared in global
-- scope using a specific name to communicate module level information to LLVM.
-- For example:
-- !llvm.module.linkage = !{ !0, !1 }
--
module Llvm.MetaData where

import Llvm.Types

import Outputable

-- | LLVM metadata expressions
data MetaExpr = MetaStr LMString
| MetaNode Int
| MetaVar LlvmVar
| MetaStruct [MetaExpr]
deriving (Eq)

instance Outputable MetaExpr where
ppr (MetaStr s ) = text "metadata !\"" <> ftext s <> char '"'
ppr (MetaNode n ) = text "metadata !" <> int n
ppr (MetaVar v ) = ppr v
ppr (MetaStruct es) = text "metadata !{ " <> ppCommaJoin es <> char '}'

-- | Associates some metadata with a specific label for attaching to an
-- instruction.
data MetaAnnot = MetaAnnot LMString MetaExpr
deriving (Eq)

-- | Metadata declarations. Metadata can only be declared in global scope.
data MetaDecl
-- | Named metadata. Only used for communicating module information to
-- LLVM. ('!name = !{ [!<n>] }' form).
= MetaNamed LMString [Int]
-- | Metadata node declaration.
-- ('!0 = metadata !{ <metadata expression> }' form).
| MetaUnamed Int MetaExpr

0 comments on commit 01234ec

Please sign in to comment.