Copyright | Trevor Elliott 2011-2016 |
---|---|
License | BSD3 |
Maintainer | awesomelyawesome@gmail.com |
Stability | experimental |
Portability | unknown |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This is the pretty-printer for llvm assembly versions 3.6 and lower.
Synopsis
- type LLVMVer = Int
- llvmV3_5 :: LLVMVer
- llvmV3_6 :: LLVMVer
- llvmV3_7 :: LLVMVer
- llvmV3_8 :: LLVMVer
- llvmVlatest :: LLVMVer
- newtype Config = Config {}
- withConfig :: Config -> ((?config :: Config) => a) -> a
- ppLLVM :: LLVMVer -> ((?config :: Config) => a) -> a
- ppLLVM35 :: ((?config :: Config) => a) -> a
- ppLLVM36 :: ((?config :: Config) => a) -> a
- ppLLVM37 :: ((?config :: Config) => a) -> a
- ppLLVM38 :: ((?config :: Config) => a) -> a
- llvmVer :: (?config :: Config) => LLVMVer
- when' :: Monoid a => Bool -> a -> a
- type Fmt a = (?config :: Config) => a -> Doc
- class LLVMPretty a where
- ppModule :: Fmt Module
- ppSourceName :: Fmt (Maybe String)
- ppNamedMd :: Fmt NamedMd
- ppUnnamedMd :: Fmt UnnamedMd
- ppGlobalAlias :: Fmt GlobalAlias
- ppTargetTriple :: Fmt TargetTriple
- ppDataLayout :: Fmt DataLayout
- ppLayoutSpec :: Fmt LayoutSpec
- ppLayoutBody :: Int -> Int -> Fmt (Maybe Int)
- ppMangling :: Fmt Mangling
- ppInlineAsm :: Fmt InlineAsm
- ppIdent :: Fmt Ident
- validIdentifier :: String -> Bool
- ppSymbol :: Fmt Symbol
- ppPrimType :: Fmt PrimType
- ppFloatType :: Fmt FloatType
- ppType :: Fmt Type
- ppTypeDecl :: Fmt TypeDecl
- ppGlobal :: Fmt Global
- ppGlobalAttrs :: Bool -> Fmt GlobalAttrs
- ppDeclare :: Fmt Declare
- ppComdatName :: Fmt String
- ppComdat :: Fmt (String, SelectionKind)
- ppSelectionKind :: Fmt SelectionKind
- ppDefine :: Fmt Define
- ppFunAttr :: Fmt FunAttr
- ppLabelDef :: Fmt BlockLabel
- ppLabel :: Fmt BlockLabel
- ppBasicBlock :: Fmt BasicBlock
- ppStmt :: Fmt Stmt
- ppAttachedMetadata :: Fmt [(String, ValMd)]
- ppLinkage :: Fmt Linkage
- ppVisibility :: Fmt Visibility
- ppGC :: Fmt GC
- ppTyped :: Fmt a -> Fmt (Typed a)
- ppSignBits :: Bool -> Fmt Bool
- ppExact :: Fmt Bool
- ppArithOp :: Fmt ArithOp
- ppUnaryArithOp :: Fmt UnaryArithOp
- ppBitOp :: Fmt BitOp
- ppConvOp :: Fmt ConvOp
- ppAtomicOrdering :: Fmt AtomicOrdering
- ppAtomicOp :: Fmt AtomicRWOp
- ppScope :: Fmt (Maybe String)
- ppInstr :: Fmt Instr
- ppLoad :: Type -> Typed (Value' BlockLabel) -> Maybe AtomicOrdering -> Fmt (Maybe Align)
- ppStore :: Typed (Value' BlockLabel) -> Typed (Value' BlockLabel) -> Maybe AtomicOrdering -> Fmt (Maybe Align)
- ppClauses :: Bool -> Fmt [Clause]
- ppClause :: Fmt Clause
- ppTypedLabel :: Fmt BlockLabel
- ppSwitchEntry :: Type -> Fmt (Integer, BlockLabel)
- ppVectorIndex :: Fmt Value
- ppAlign :: Fmt (Maybe Align)
- ppAlloca :: Type -> Maybe (Typed Value) -> Fmt (Maybe Int)
- ppCall :: Bool -> Type -> Value -> Fmt [Typed Value]
- ppCallBr :: Type -> Value -> [Typed Value] -> BlockLabel -> Fmt [BlockLabel]
- ppCallSym :: Type -> Fmt Value
- ppGEP :: Bool -> Type -> Typed Value -> Fmt [Typed Value]
- ppInvoke :: Type -> Value -> [Typed Value] -> BlockLabel -> Fmt BlockLabel
- ppPhiArg :: Fmt (Value, BlockLabel)
- ppICmpOp :: Fmt ICmpOp
- ppFCmpOp :: Fmt FCmpOp
- ppValue' :: Fmt i -> Fmt (Value' i)
- ppValue :: Fmt Value
- ppValMd' :: Fmt i -> Fmt (ValMd' i)
- ppValMd :: Fmt ValMd
- ppDebugLoc' :: Fmt i -> Fmt (DebugLoc' i)
- ppDebugLoc :: Fmt DebugLoc
- ppTypedValMd :: Fmt ValMd
- ppMetadata :: Fmt Doc
- ppMetadataNode' :: Fmt i -> Fmt [Maybe (ValMd' i)]
- ppMetadataNode :: Fmt [Maybe ValMd]
- ppStringLiteral :: Fmt String
- ppAsm :: Bool -> Bool -> String -> Fmt String
- ppConstExpr' :: Fmt i -> Fmt (ConstExpr' i)
- ppConstExpr :: Fmt ConstExpr
- ppDebugInfo' :: Fmt i -> Fmt (DebugInfo' i)
- ppDebugInfo :: Fmt DebugInfo
- ppDIImportedEntity' :: Fmt i -> Fmt (DIImportedEntity' i)
- ppDIImportedEntity :: Fmt DIImportedEntity
- ppDILabel' :: Fmt i -> Fmt (DILabel' i)
- ppDILabel :: Fmt DILabel
- ppDINameSpace' :: Fmt i -> Fmt (DINameSpace' i)
- ppDINameSpace :: Fmt DINameSpace
- ppDITemplateTypeParameter' :: Fmt i -> Fmt (DITemplateTypeParameter' i)
- ppDITemplateTypeParameter :: Fmt DITemplateTypeParameter
- ppDITemplateValueParameter' :: Fmt i -> Fmt (DITemplateValueParameter' i)
- ppDITemplateValueParameter :: Fmt DITemplateValueParameter
- ppDIBasicType :: Fmt DIBasicType
- ppDICompileUnit' :: Fmt i -> Fmt (DICompileUnit' i)
- ppDICompileUnit :: Fmt DICompileUnit
- ppFlags :: Fmt (Maybe String)
- ppDICompositeType' :: Fmt i -> Fmt (DICompositeType' i)
- ppDICompositeType :: Fmt DICompositeType
- ppDIDerivedType' :: Fmt i -> Fmt (DIDerivedType' i)
- ppDIDerivedType :: Fmt DIDerivedType
- ppDIEnumerator :: String -> Integer -> Fmt Bool
- ppDIExpression :: Fmt DIExpression
- ppDIFile :: Fmt DIFile
- ppDIGlobalVariable' :: Fmt i -> Fmt (DIGlobalVariable' i)
- ppDIGlobalVariable :: Fmt DIGlobalVariable
- ppDIGlobalVariableExpression' :: Fmt i -> Fmt (DIGlobalVariableExpression' i)
- ppDIGlobalVariableExpression :: Fmt DIGlobalVariableExpression
- ppDILexicalBlock' :: Fmt i -> Fmt (DILexicalBlock' i)
- ppDILexicalBlock :: Fmt DILexicalBlock
- ppDILexicalBlockFile' :: Fmt i -> Fmt (DILexicalBlockFile' i)
- ppDILexicalBlockFile :: Fmt DILexicalBlockFile
- ppDILocalVariable' :: Fmt i -> Fmt (DILocalVariable' i)
- ppDILocalVariable :: Fmt DILocalVariable
- ppDISubprogram' :: Fmt i -> Fmt (DISubprogram' i)
- ppDISubprogram :: Fmt DISubprogram
- ppDISubrange' :: Fmt i -> Fmt (DISubrange' i)
- ppDISubrange :: Fmt DISubrange
- ppDISubroutineType' :: Fmt i -> Fmt (DISubroutineType' i)
- ppDISubroutineType :: Fmt DISubroutineType
- ppDIArgList' :: Fmt i -> Fmt (DIArgList' i)
- ppDIArgList :: Fmt DIArgList
- ppBool :: Fmt Bool
- ppArgList :: Bool -> Fmt [Doc]
- integral :: Integral i => Fmt i
- hex :: (Integral i, Show i) => Fmt i
- opt :: Bool -> Fmt Doc
- ppInt64ValMd' :: Bool -> Fmt i -> Fmt (ValMd' i)
- commas :: Fmt [Doc]
- mcommas :: Fmt [Maybe Doc]
- angles :: Fmt Doc
- structBraces :: Fmt Doc
- ppMaybe :: Fmt a -> Fmt (Maybe a)
Documentation
The value used to specify the LLVM major version. The LLVM text format (i.e. assembly code) changes with different versions of LLVM, so this value is used to select the version the output should be generated for.
At the current time, changes primarily occur when the LLVM major version changes, and this is expected to be the case going forward, so it is sufficient to reference the LLVM version by the single major version number. There is one exception and one possible future exception to this approach:
- During LLVM v3, there were changes in 3.5, 3.6, 3.7, and 3.8. There are
explicit
ppLLVMnn
function entry points for those versions, but in the event that a numerical value is needed, we note the serendipitous fact that prior to LLVM 4, there are exactly 4 versions we need to differentiate and can therefore assign the values of 0, 1, 2, and 3 to those versions (and we have no intention of supporting any other pre-4.0 versions at this point). - If at some future date, there are text format changes associated with a minor version, then the LLVM version designation here will need to be enhanced and made more sophisticated. At the present time, the likelihood of that is small enough that the current simple implementation is a benefit over a more complex mechanism that might not be needed.
llvmVlatest :: LLVMVer Source #
This value should be updated when support is added for new LLVM versions; this is used for defaulting and otherwise reporting the maximum LLVM version known to be supported.
The differences between various versions of the llvm textual AST.
withConfig :: Config -> ((?config :: Config) => a) -> a Source #
when' :: Monoid a => Bool -> a -> a Source #
This is a helper function for when a list of parameters is gated by a condition (usually the llvmVer value).
type Fmt a = (?config :: Config) => a -> Doc Source #
This type encapsulates the ability to convert an object into Doc
format. Using this abstraction allows for a consolidated representation of the
declaration. Most pretty-printing for LLVM elements will have a
function signature for that element.Fmt
a
class LLVMPretty a where Source #
The LLVMPretty class has instances for most AST elements. It allows the
conversion of an AST element (and its sub-elements) into a Doc assembly format
by simply using the llvmPP
method rather than needing to explicitly invoke
the specific pretty-printing function for that element.
Instances
ppTargetTriple :: Fmt TargetTriple Source #
Pretty print a TargetTriple
ppDataLayout :: Fmt DataLayout Source #
Pretty print a data layout specification.
ppLayoutSpec :: Fmt LayoutSpec Source #
Pretty print a single layout specification.
ppLayoutBody :: Int -> Int -> Fmt (Maybe Int) Source #
Pretty-print the common case for data layout specifications.
ppMangling :: Fmt Mangling Source #
ppInlineAsm :: Fmt InlineAsm Source #
Pretty-print the inline assembly block.
validIdentifier :: String -> Bool Source #
According to the LLVM Language Reference Manual, the regular expression for LLVM identifiers is "[-a-zA-Z$._][-a-zA-Z$._0-9]". Identifiers may also be strings of one or more decimal digits.
ppPrimType :: Fmt PrimType Source #
ppTypeDecl :: Fmt TypeDecl Source #
ppGlobalAttrs :: Bool -> Fmt GlobalAttrs Source #
Pretty-print Global Attributes (usually associated with a global variable declaration). The first argument to ppGlobalAttrs indicates whether there is a value associated with this global declaration: a global declaration with a value should not be identified as "external" and "default" visibility, whereas one without a value may have those attributes.
ppComdatName :: Fmt String Source #
ppLabel :: Fmt BlockLabel Source #
ppStore :: Typed (Value' BlockLabel) -> Typed (Value' BlockLabel) -> Maybe AtomicOrdering -> Fmt (Maybe Align) Source #
ppSwitchEntry :: Type -> Fmt (Integer, BlockLabel) Source #
ppVectorIndex :: Fmt Value Source #
ppCallBr :: Type -> Value -> [Typed Value] -> BlockLabel -> Fmt [BlockLabel] Source #
Note that the textual syntax changed in LLVM 10 (callbr
was introduced in
LLVM 9).
ppCallSym :: Type -> Fmt Value Source #
Print out the ty|fnty fnptrval
portion of a call
, callbr
, or
invoke
instruction, where:
ty
is the return type.fnty
is the overall function type.fnptrval
is a pointer value, where the memory it points to is treated as a value of typefnty
.
The LLVM Language Reference Manual indicates that either ty
or fnty
can be used, but in practice, ty
is typically preferred unless the
function type involves varargs. We adopt the same convention here.
ppInvoke :: Type -> Value -> [Typed Value] -> BlockLabel -> Fmt BlockLabel Source #
ppDebugLoc :: Fmt DebugLoc Source #
ppTypedValMd :: Fmt ValMd Source #
ppMetadata :: Fmt Doc Source #
ppConstExpr' :: Fmt i -> Fmt (ConstExpr' i) Source #
ppDebugInfo' :: Fmt i -> Fmt (DebugInfo' i) Source #
ppDIImportedEntity' :: Fmt i -> Fmt (DIImportedEntity' i) Source #
ppDINameSpace' :: Fmt i -> Fmt (DINameSpace' i) Source #
ppDITemplateTypeParameter' :: Fmt i -> Fmt (DITemplateTypeParameter' i) Source #
ppDITemplateValueParameter' :: Fmt i -> Fmt (DITemplateValueParameter' i) Source #
ppDICompileUnit' :: Fmt i -> Fmt (DICompileUnit' i) Source #
ppDICompositeType' :: Fmt i -> Fmt (DICompositeType' i) Source #
ppDIDerivedType' :: Fmt i -> Fmt (DIDerivedType' i) Source #
ppDIGlobalVariable' :: Fmt i -> Fmt (DIGlobalVariable' i) Source #
ppDILexicalBlock' :: Fmt i -> Fmt (DILexicalBlock' i) Source #
ppDILexicalBlockFile' :: Fmt i -> Fmt (DILexicalBlockFile' i) Source #
ppDILocalVariable' :: Fmt i -> Fmt (DILocalVariable' i) Source #
ppDISubprogram' :: Fmt i -> Fmt (DISubprogram' i) Source #
See writeDISubprogram
in the LLVM source, in the file AsmWriter.cpp
Note that the textual syntax changed in LLVM 7, as the retainedNodes
field
was called variables
in previous LLVM versions.
ppDISubrange' :: Fmt i -> Fmt (DISubrange' i) Source #
ppDISubroutineType' :: Fmt i -> Fmt (DISubroutineType' i) Source #
ppDIArgList' :: Fmt i -> Fmt (DIArgList' i) Source #
ppInt64ValMd' :: Bool -> Fmt i -> Fmt (ValMd' i) Source #
Print a ValMd' value as a plain signed integer (Int64) if possible. If the ValMd' is not representable as an Int64, defer to ValMd' printing (if canFallBack is True) or print nothing (for when a ValMd is not a valid representation).
mcommas :: Fmt [Maybe Doc] Source #
Helpful for all of the optional fields that appear in the metadata values
structBraces :: Fmt Doc Source #