llvm-pretty-0.3.0.0: A pretty printing library inspired by the llvm binding.

Safe HaskellSafe-Inferred

Text.LLVM.AST

Synopsis

Documentation

commas :: [Doc] -> DocSource

colons :: [Doc] -> DocSource

breaks :: (a -> Bool) -> [a] -> [[a]]Source

uncons :: MonadPlus m => [a] -> m (a, [a])Source

int32 :: Int32 -> DocSource

angles :: Doc -> DocSource

structBraces :: Doc -> DocSource

ppMaybe :: (a -> Doc) -> Maybe a -> DocSource

opt :: Bool -> Doc -> DocSource

data NamedMd Source

Constructors

NamedMd 

Fields

nmName :: String
 
nmValues :: [Int]
 

Instances

Show NamedMd 

data UnnamedMd Source

Constructors

UnnamedMd 

Fields

umIndex :: !Int
 
umValues :: [Typed Value]
 

Instances

Show UnnamedMd 

data GlobalAlias Source

Constructors

GlobalAlias 

Instances

ppDataLayout :: DataLayout -> DocSource

Pretty print a data layout specification.

data LayoutSpec Source

Constructors

BigEndian 
LittleEndian 
PointerSize !Int !Int (Maybe Int) 
IntegerSize !Int !Int (Maybe Int) 
VectorSize !Int !Int (Maybe Int) 
FloatSize !Int !Int (Maybe Int) 
AggregateSize !Int !Int (Maybe Int) 
StackObjSize !Int !Int (Maybe Int) 
NativeIntSize [Int] 
StackAlign !Int 
Mangling Mangling 

Instances

Show LayoutSpec 

ppLayoutSpec :: LayoutSpec -> DocSource

Pretty print a single layout specification.

ppLayoutBody :: Int -> Int -> Maybe Int -> DocSource

Pretty-print the common case for data layout specifications.

parseDataLayout :: MonadPlus m => String -> m DataLayoutSource

Parse the data layout string.

parseLayoutSpec :: MonadPlus m => String -> m LayoutSpecSource

Parse a single layout specification from a string.

type InlineAsm = [String]Source

ppInlineAsm :: InlineAsm -> DocSource

Pretty-print the inline assembly block.

newtype Ident Source

Constructors

Ident String 

Instances

Eq Ident 
Ord Ident 
Show Ident 
IsString Ident 
IsValue Ident 
DefineArgs Type (Typed Value -> BB ()) 
DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) 
DefineArgs as k => DefineArgs (:> Type as) (Typed Value -> k) 
DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) 

newtype Symbol Source

Constructors

Symbol String 

Instances

Eq Symbol 
Ord Symbol 
Show Symbol 
IsString Symbol 
IsValue Symbol 

data PrimType Source

Instances

Eq PrimType 
Ord PrimType 
Show PrimType 

data FloatType Source

Constructors

Float 
Double 
Fp128 
X86_fp80 
PPC_fp128 

Instances

Eq FloatType 
Ord FloatType 
Show FloatType 

data Type' ident Source

Constructors

PrimType PrimType 
Alias ident 
Array Int32 (Type' ident) 
FunTy (Type' ident) [Type' ident] Bool 
PtrTo (Type' ident) 
Struct [Type' ident] 
PackedStruct [Type' ident] 
Vector Int32 (Type' ident) 
Opaque 

Instances

Functor Type' 
DefineArgs Type (Typed Value -> BB ()) 
Eq ident => Eq (Type' ident) 
Ord ident => Ord (Type' ident) 
Show ident => Show (Type' ident) 
DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) 
DefineArgs as k => DefineArgs (:> Type as) (Typed Value -> k) 
DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) 

updateAliases :: (a -> Type' b) -> Type' a -> Type' bSource

Traverse a type, updating or removing aliases.

ppType :: Type -> DocSource

isAlias :: Type -> BoolSource

isPrimTypeOf :: (PrimType -> Bool) -> Type -> BoolSource

isVector :: Type -> BoolSource

isVectorOf :: (Type -> Bool) -> Type -> BoolSource

isArray :: Type -> BoolSource

ppArgList :: Bool -> [Doc] -> DocSource

Build a variable-argument argument list.

data NullResult lab Source

Constructors

HasNull (Value' lab) 
ResolveNull Ident 

elimFunTy :: MonadPlus m => Type -> m (Type, [Type], Bool)Source

elimAlias :: MonadPlus m => Type -> m IdentSource

elimPtrTo :: MonadPlus m => Type -> m TypeSource

elimVector :: MonadPlus m => Type -> m (Int32, Type)Source

elimArray :: MonadPlus m => Type -> m (Int32, Type)Source

elimFunPtr :: MonadPlus m => Type -> m (Type, [Type], Bool)Source

elimPrimType :: MonadPlus m => Type -> m PrimTypeSource

elimFloatType :: MonadPlus m => PrimType -> m FloatTypeSource

elimSequentialType :: MonadPlus m => Type -> m TypeSource

Eliminator for array, pointer and vector types.

data TypeDecl Source

Constructors

TypeDecl 

Fields

typeName :: Ident
 
typeValue :: Type
 

Instances

Show TypeDecl 

data Global Source

Instances

Show Global 

data GlobalAttrs Source

Constructors

GlobalAttrs 

Fields

gaLinkage :: Maybe Linkage
 
gaConstant :: Bool
 

Instances

data Declare Source

Constructors

Declare 

Fields

decRetType :: Type
 
decName :: Symbol
 
decArgs :: [Type]
 
decVarArgs :: Bool
 

Instances

Show Declare 

data Define Source

Constructors

Define 

Fields

defAttrs :: FunAttrs
 
defRetType :: Type
 
defName :: Symbol
 
defArgs :: [Typed Ident]
 
defVarArgs :: Bool
 
defSection :: Maybe String
 
defBody :: [BasicBlock]
 

Instances

Show Define 

data FunAttrs Source

Constructors

FunAttrs 

Fields

funLinkage :: Maybe Linkage
 
funGC :: Maybe GC
 

Instances

Show FunAttrs 

data BlockLabel Source

Constructors

Named Ident 
Anon Int 

data BasicBlock' lab Source

Constructors

BasicBlock 

Fields

bbLabel :: lab
 
bbStmts :: [Stmt]
 

Instances

Show lab => Show (BasicBlock' lab) 

newtype GC Source

Constructors

GC 

Fields

getGC :: String
 

Instances

Show GC 

ppGC :: GC -> DocSource

data Typed a Source

Constructors

Typed 

Fields

typedType :: Type
 
typedValue :: a
 

Instances

Functor Typed 
Foldable Typed 
Traversable Typed 
DefineArgs Type (Typed Value -> BB ()) 
Show a => Show (Typed a) 
IsValue a => IsValue (Typed a) 
DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) 
DefineArgs as k => DefineArgs (:> Type as) (Typed Value -> k) 
DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) 

mapMTyped :: Monad m => (a -> m b) -> Typed a -> m (Typed b)Source

ppTyped :: (a -> Doc) -> Typed a -> DocSource

data ArithOp Source

Constructors

Add Bool Bool 
FAdd 
Sub Bool Bool 
FSub 
Mul Bool Bool 
FMul 
UDiv Bool 
SDiv Bool 
FDiv 
URem 
SRem 
FRem 

Instances

Eq ArithOp 
Show ArithOp 

ppSignBits :: Bool -> Bool -> DocSource

ppExact :: Bool -> DocSource

data BitOp Source

Constructors

Shl Bool Bool 
Lshr Bool 
Ashr Bool 
And 
Or 
Xor 

Instances

Show BitOp 

type Align = IntSource

data Instr' lab Source

Constructors

Ret (Typed (Value' lab)) 
RetVoid 
Arith ArithOp (Typed (Value' lab)) (Value' lab) 
Bit BitOp (Typed (Value' lab)) (Value' lab) 
Conv ConvOp (Typed (Value' lab)) Type 
Call Bool Type (Value' lab) [Typed (Value' lab)] 
Alloca Type (Maybe (Typed (Value' lab))) (Maybe Int) 
Load (Typed (Value' lab)) (Maybe Align) 
Store (Typed (Value' lab)) (Typed (Value' lab)) (Maybe Align) 
ICmp ICmpOp (Typed (Value' lab)) (Value' lab) 
FCmp FCmpOp (Typed (Value' lab)) (Value' lab) 
Phi Type [(Value' lab, lab)] 
GEP Bool (Typed (Value' lab)) [Typed (Value' lab)] 
Select (Typed (Value' lab)) (Typed (Value' lab)) (Value' lab) 
ExtractValue (Typed (Value' lab)) [Int32] 
InsertValue (Typed (Value' lab)) (Typed (Value' lab)) [Int32] 
ExtractElt (Typed (Value' lab)) (Value' lab) 
InsertElt (Typed (Value' lab)) (Typed (Value' lab)) (Value' lab) 
ShuffleVector (Typed (Value' lab)) (Value' lab) (Typed (Value' lab)) 
Jump lab 
Br (Typed (Value' lab)) lab lab 
Invoke Type (Value' lab) [Typed (Value' lab)] lab lab 
Comment String 
Unreachable 
Unwind 
VaArg (Typed (Value' lab)) Type 
IndirectBr (Typed (Value' lab)) [lab] 
Switch (Typed (Value' lab)) lab [(Integer, lab)] 
LandingPad Type (Typed (Value' lab)) Bool [Clause' lab] 
Resume (Typed (Value' lab)) 

Instances

Functor Instr' 
HasLabel Instr' 
Show lab => Show (Instr' lab) 

data Clause' lab Source

Constructors

Catch (Typed (Value' lab)) 
Filter (Typed (Value' lab)) 

Instances

Functor Clause' 
HasLabel Clause' 
Show lab => Show (Clause' lab) 

isTerminator :: Instr' lab -> BoolSource

isComment :: Instr' lab -> BoolSource

isPhi :: Instr' lab -> BoolSource

ppClauses :: Bool -> [Clause] -> DocSource

ppSwitchEntry :: Type -> (Integer, BlockLabel) -> DocSource

ppAlign :: Maybe Align -> DocSource

ppAlloca :: Type -> Maybe (Typed Value) -> Maybe Int -> DocSource

ppCall :: Bool -> Type -> Value -> [Typed Value] -> DocSource

ppGEP :: Bool -> Typed Value -> [Typed Value] -> DocSource

data ICmpOp Source

Constructors

Ieq 
Ine 
Iugt 
Iuge 
Iult 
Iule 
Isgt 
Isge 
Islt 
Isle 

Instances

Show ICmpOp 

data FCmpOp Source

Instances

Show FCmpOp 

data Value' lab Source

Constructors

ValInteger Integer 
ValBool Bool 
ValFloat Float 
ValDouble Double 
ValIdent Ident 
ValSymbol Symbol 
ValNull 
ValArray Type [Value' lab] 
ValVector Type [Value' lab] 
ValStruct [Typed (Value' lab)] 
ValPackedStruct [Typed (Value' lab)] 
ValString String 
ValConstExpr (ConstExpr' lab) 
ValUndef 
ValLabel lab 
ValZeroInit 
ValAsm Bool Bool String String 
ValMd (ValMd' lab) 

Instances

Functor Value' 
HasLabel Value' 
IsValue Value 
DefineArgs Type (Typed Value -> BB ()) 
Show lab => Show (Value' lab) 
DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) 
DefineArgs as k => DefineArgs (:> Type as) (Typed Value -> k) 
DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) 

data ValMd' lab Source

Constructors

ValMdString String 
ValMdNode [Typed (Value' lab)] 
ValMdRef Int 
ValMdLoc (DebugLoc' lab) 

Instances

Functor ValMd' 
HasLabel ValMd' 
Show lab => Show (ValMd' lab) 

data DebugLoc' lab Source

Constructors

DebugLoc 

Fields

dlLine :: Int32
 
dlCol :: Int32
 
dlScope :: ValMd' lab
 
dlIA :: Maybe (ValMd' lab)
 

Instances

Functor DebugLoc' 
HasLabel DebugLoc' 
Show lab => Show (DebugLoc' lab) 

isConst :: Value' lab -> BoolSource

ppMetadata :: Doc -> DocSource

ppBool :: Bool -> DocSource

ppStringLiteral :: String -> DocSource

ppAsm :: Bool -> Bool -> String -> String -> DocSource

elimValSymbol :: MonadPlus m => Value' lab -> m SymbolSource

elimValInteger :: MonadPlus m => Value' lab -> m IntegerSource

data Stmt' lab Source

Constructors

Result Ident (Instr' lab) [(String, ValMd' lab)] 
Effect (Instr' lab) [(String, ValMd' lab)] 

Instances

Functor Stmt' 
HasLabel Stmt' 
Show lab => Show (Stmt' lab) 

stmtMetadata :: Stmt' lab -> [(String, ValMd' lab)]Source

extendMetadata :: (String, ValMd' lab) -> Stmt' lab -> Stmt' labSource

ppStmt :: Stmt -> DocSource

ppAttachedMetadata :: [(String, ValMd)] -> DocSource

data ConstExpr' lab Source

Constructors

ConstGEP Bool [Typed (Value' lab)] 
ConstConv ConvOp (Typed (Value' lab)) Type 
ConstSelect (Typed (Value' lab)) (Typed (Value' lab)) (Typed (Value' lab)) 
ConstBlockAddr Symbol lab 

Instances

Functor ConstExpr' 
HasLabel ConstExpr' 
Show lab => Show (ConstExpr' lab) 

data IndexResult Source

Constructors

Invalid

An invalid use of GEP

HasType Type

A resolved type

Resolve Ident (Type -> IndexResult)

Continue, after resolving an alias

resolveGep :: Type -> [Typed (Value' lab)] -> IndexResultSource

Resolve the type of a GEP instruction. Note that the type produced is the type of the result, not necessarily a pointer.

resolveGepBody :: Type -> [Typed (Value' lab)] -> IndexResultSource

Resolve the type of a GEP instruction. This assumes that the input has already been processed as a pointer.

isGepIndex :: Typed (Value' lab) -> BoolSource

isGepStructIndex :: Typed (Value' lab) -> Maybe IntegerSource