llvm-pretty-0.12.0.0: A pretty printing library inspired by the llvm binding.
CopyrightTrevor Elliott 2011-2016
LicenseBSD3
Maintainerawesomelyawesome@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.LLVM.PP

Description

This is the pretty-printer for llvm assembly versions 3.6 and lower.

Synopsis

Documentation

type LLVMVer = Int Source #

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:

  1. 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).
  2. 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.

llvmV3_5 :: LLVMVer Source #

Helpers for specifying the LLVM versions prior to v4

llvmV3_6 :: LLVMVer Source #

Helpers for specifying the LLVM versions prior to v4

llvmV3_7 :: LLVMVer Source #

Helpers for specifying the LLVM versions prior to v4

llvmV3_8 :: LLVMVer Source #

Helpers for specifying the LLVM versions prior to v4

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.

newtype Config Source #

The differences between various versions of the llvm textual AST.

Constructors

Config 

Fields

withConfig :: Config -> ((?config :: Config) => a) -> a Source #

ppLLVM :: LLVMVer -> ((?config :: Config) => a) -> a Source #

ppLLVM35 :: ((?config :: Config) => a) -> a Source #

ppLLVM36 :: ((?config :: Config) => a) -> a Source #

ppLLVM37 :: ((?config :: Config) => a) -> a Source #

ppLLVM38 :: ((?config :: Config) => a) -> a Source #

llvmVer :: (?config :: Config) => LLVMVer 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 Fmt a function signature for that element.

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.

Methods

llvmPP :: Fmt a Source #

Instances

Instances details
LLVMPretty Ident Source # 
Instance details

Defined in Text.LLVM.PP

Methods

llvmPP :: Fmt Ident Source #

LLVMPretty Module Source # 
Instance details

Defined in Text.LLVM.PP

LLVMPretty Symbol Source # 
Instance details

Defined in Text.LLVM.PP

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.

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.

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.

ppTyped :: Fmt a -> Fmt (Typed a) 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 type fnty.

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.

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.

ppArgList :: Bool -> Fmt [Doc] Source #

Build a variable-argument argument list.

hex :: (Integral i, Show i) => Fmt 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

ppMaybe :: Fmt a -> Fmt (Maybe a) Source #