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

Safe HaskellSafe
LanguageHaskell2010

Text.LLVM.AST

Synopsis

Documentation

data Module Source #

Constructors

Module 

Fields

Instances

Show Module Source # 
Generic Module Source # 

Associated Types

type Rep Module :: * -> * #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Monoid Module Source # 
type Rep Module Source # 

data NamedMd Source #

Constructors

NamedMd 

Fields

Instances

Show NamedMd Source # 
Generic NamedMd Source # 

Associated Types

type Rep NamedMd :: * -> * #

Methods

from :: NamedMd -> Rep NamedMd x #

to :: Rep NamedMd x -> NamedMd #

type Rep NamedMd Source # 
type Rep NamedMd = D1 (MetaData "NamedMd" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "NamedMd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "nmName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "nmValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int]))))

data UnnamedMd Source #

Constructors

UnnamedMd 

Fields

Instances

Show UnnamedMd Source # 
Generic UnnamedMd Source # 

Associated Types

type Rep UnnamedMd :: * -> * #

type Rep UnnamedMd Source # 
type Rep UnnamedMd = D1 (MetaData "UnnamedMd" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "UnnamedMd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "umIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "umValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ValMd)) (S1 (MetaSel (Just Symbol "umDistinct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))

data LayoutSpec Source #

Constructors

BigEndian 
LittleEndian 
PointerSize !Int !Int !Int (Maybe Int)

address space, size, abi, pref

IntegerSize !Int !Int (Maybe Int)

size, abi, pref

VectorSize !Int !Int (Maybe Int)

size, abi, pref

FloatSize !Int !Int (Maybe Int)

size, abi, pref

StackObjSize !Int !Int (Maybe Int)

size, abi, pref

AggregateSize !Int !Int (Maybe Int)

size, abi, pref

NativeIntSize [Int] 
StackAlign !Int

size

Mangling Mangling 

Instances

Show LayoutSpec Source # 
Generic LayoutSpec Source # 

Associated Types

type Rep LayoutSpec :: * -> * #

type Rep LayoutSpec Source # 
type Rep LayoutSpec = D1 (MetaData "LayoutSpec" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "BigEndian" PrefixI False) U1) (C1 (MetaCons "LittleEndian" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PointerSize" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))) ((:+:) (C1 (MetaCons "IntegerSize" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))) (C1 (MetaCons "VectorSize" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))))))) ((:+:) ((:+:) (C1 (MetaCons "FloatSize" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))) ((:+:) (C1 (MetaCons "StackObjSize" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))) (C1 (MetaCons "AggregateSize" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))))) ((:+:) (C1 (MetaCons "NativeIntSize" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int]))) ((:+:) (C1 (MetaCons "StackAlign" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) (C1 (MetaCons "Mangling" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mangling)))))))

data Mangling Source #

Instances

Eq Mangling Source # 
Show Mangling Source # 
Generic Mangling Source # 

Associated Types

type Rep Mangling :: * -> * #

Methods

from :: Mangling -> Rep Mangling x #

to :: Rep Mangling x -> Mangling #

type Rep Mangling Source # 
type Rep Mangling = D1 (MetaData "Mangling" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) (C1 (MetaCons "ElfMangling" PrefixI False) U1) (C1 (MetaCons "MipsMangling" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MachOMangling" PrefixI False) U1) (C1 (MetaCons "WindowsCoffMangling" PrefixI False) U1)))

parseDataLayout :: MonadPlus m => String -> m DataLayout Source #

Parse the data layout string.

newtype Ident Source #

Constructors

Ident String 

Instances

Eq Ident Source # 

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident Source # 

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

IsString Ident Source # 

Methods

fromString :: String -> Ident #

Generic Ident Source # 

Associated Types

type Rep Ident :: * -> * #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

IsValue Ident Source # 

Methods

toValue :: Ident -> Value Source #

DefineArgs Type (Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs as k => DefineArgs ((:>) Type as) (Typed Value -> k) Source # 

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

type Rep Ident Source # 
type Rep Ident = D1 (MetaData "Ident" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" True) (C1 (MetaCons "Ident" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

newtype Symbol Source #

Constructors

Symbol String 

Instances

Eq Symbol Source # 

Methods

(==) :: Symbol -> Symbol -> Bool #

(/=) :: Symbol -> Symbol -> Bool #

Ord Symbol Source # 
Show Symbol Source # 
IsString Symbol Source # 

Methods

fromString :: String -> Symbol #

Generic Symbol Source # 

Associated Types

type Rep Symbol :: * -> * #

Methods

from :: Symbol -> Rep Symbol x #

to :: Rep Symbol x -> Symbol #

Monoid Symbol Source # 
IsValue Symbol Source # 

Methods

toValue :: Symbol -> Value Source #

type Rep Symbol Source # 
type Rep Symbol = D1 (MetaData "Symbol" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" True) (C1 (MetaCons "Symbol" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data FloatType Source #

Instances

Eq FloatType Source # 
Ord FloatType Source # 
Show FloatType Source # 
Generic FloatType Source # 

Associated Types

type Rep FloatType :: * -> * #

type Rep FloatType Source # 
type Rep FloatType = D1 (MetaData "FloatType" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) (C1 (MetaCons "Half" PrefixI False) U1) ((:+:) (C1 (MetaCons "Float" PrefixI False) U1) (C1 (MetaCons "Double" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Fp128" PrefixI False) U1) ((:+:) (C1 (MetaCons "X86_fp80" PrefixI False) U1) (C1 (MetaCons "PPC_fp128" PrefixI False) U1))))

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' Source # 

Methods

fmap :: (a -> b) -> Type' a -> Type' b #

(<$) :: a -> Type' b -> Type' a #

DefineArgs Type (Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

Eq ident => Eq (Type' ident) Source # 

Methods

(==) :: Type' ident -> Type' ident -> Bool #

(/=) :: Type' ident -> Type' ident -> Bool #

Ord ident => Ord (Type' ident) Source # 

Methods

compare :: Type' ident -> Type' ident -> Ordering #

(<) :: Type' ident -> Type' ident -> Bool #

(<=) :: Type' ident -> Type' ident -> Bool #

(>) :: Type' ident -> Type' ident -> Bool #

(>=) :: Type' ident -> Type' ident -> Bool #

max :: Type' ident -> Type' ident -> Type' ident #

min :: Type' ident -> Type' ident -> Type' ident #

Show ident => Show (Type' ident) Source # 

Methods

showsPrec :: Int -> Type' ident -> ShowS #

show :: Type' ident -> String #

showList :: [Type' ident] -> ShowS #

Generic (Type' ident) Source # 

Associated Types

type Rep (Type' ident) :: * -> * #

Methods

from :: Type' ident -> Rep (Type' ident) x #

to :: Rep (Type' ident) x -> Type' ident #

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs as k => DefineArgs ((:>) Type as) (Typed Value -> k) Source # 

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

type Rep (Type' ident) Source # 
type Rep (Type' ident) = D1 (MetaData "Type'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PrimType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrimType))) (C1 (MetaCons "Alias" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ident)))) ((:+:) (C1 (MetaCons "Array" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type' ident))))) (C1 (MetaCons "FunTy" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type' ident))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type' ident])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))))) ((:+:) ((:+:) (C1 (MetaCons "PtrTo" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type' ident)))) (C1 (MetaCons "Struct" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type' ident])))) ((:+:) (C1 (MetaCons "PackedStruct" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type' ident]))) ((:+:) (C1 (MetaCons "Vector" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type' ident))))) (C1 (MetaCons "Opaque" PrefixI False) U1)))))

updateAliases :: (a -> Type' b) -> Type' a -> Type' b Source #

Traverse a type, updating or removing aliases.

data NullResult lab Source #

Constructors

HasNull (Value' lab) 
ResolveNull Ident 

elimSequentialType :: MonadPlus m => Type -> m Type Source #

Eliminator for array, pointer and vector types.

data TypeDecl Source #

Constructors

TypeDecl 

Fields

Instances

Show TypeDecl Source # 
Generic TypeDecl Source # 

Associated Types

type Rep TypeDecl :: * -> * #

Methods

from :: TypeDecl -> Rep TypeDecl x #

to :: Rep TypeDecl x -> TypeDecl #

type Rep TypeDecl Source # 
type Rep TypeDecl = D1 (MetaData "TypeDecl" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "TypeDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "typeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident)) (S1 (MetaSel (Just Symbol "typeValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))

data GlobalAttrs Source #

Constructors

GlobalAttrs 

Instances

Show GlobalAttrs Source # 
Generic GlobalAttrs Source # 

Associated Types

type Rep GlobalAttrs :: * -> * #

type Rep GlobalAttrs Source # 
type Rep GlobalAttrs = D1 (MetaData "GlobalAttrs" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "GlobalAttrs" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "gaLinkage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Linkage))) (S1 (MetaSel (Just Symbol "gaConstant") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

decFunType :: Declare -> Type Source #

The function type of this declaration

data Define Source #

Instances

Show Define Source # 
Generic Define Source # 

Associated Types

type Rep Define :: * -> * #

Methods

from :: Define -> Rep Define x #

to :: Rep Define x -> Define #

type Rep Define Source # 

data FunAttr Source #

Instances

Show FunAttr Source # 
Generic FunAttr Source # 

Associated Types

type Rep FunAttr :: * -> * #

Methods

from :: FunAttr -> Rep FunAttr x #

to :: Rep FunAttr x -> FunAttr #

type Rep FunAttr Source # 
type Rep FunAttr = D1 (MetaData "FunAttr" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "AlignStack" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:+:) (C1 (MetaCons "Alwaysinline" PrefixI False) U1) (C1 (MetaCons "Builtin" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Cold" PrefixI False) U1) (C1 (MetaCons "Inlinehint" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Jumptable" PrefixI False) U1) (C1 (MetaCons "Minsize" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Naked" PrefixI False) U1) ((:+:) (C1 (MetaCons "Nobuiltin" PrefixI False) U1) (C1 (MetaCons "Noduplicate" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Noimplicitfloat" PrefixI False) U1) (C1 (MetaCons "Noinline" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Nonlazybind" PrefixI False) U1) (C1 (MetaCons "Noredzone" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Noreturn" PrefixI False) U1) ((:+:) (C1 (MetaCons "Nounwind" PrefixI False) U1) (C1 (MetaCons "Optnone" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Optsize" PrefixI False) U1) (C1 (MetaCons "Readnone" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Readonly" PrefixI False) U1) (C1 (MetaCons "ReturnsTwice" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "SanitizeAddress" PrefixI False) U1) ((:+:) (C1 (MetaCons "SanitizeMemory" PrefixI False) U1) (C1 (MetaCons "SanitizeThread" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "SSP" PrefixI False) U1) (C1 (MetaCons "SSPreq" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SSPstrong" PrefixI False) U1) (C1 (MetaCons "UWTable" PrefixI False) U1))))))

data BlockLabel Source #

Constructors

Named Ident 
Anon Int 

Instances

Eq BlockLabel Source # 
Ord BlockLabel Source # 
Show BlockLabel Source # 
IsString BlockLabel Source # 
Generic BlockLabel Source # 

Associated Types

type Rep BlockLabel :: * -> * #

IsValue Value Source # 

Methods

toValue :: Value -> Value Source #

DefineArgs Type (Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs as k => DefineArgs ((:>) Type as) (Typed Value -> k) Source # 

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

type Rep BlockLabel Source # 

data BasicBlock' lab Source #

Constructors

BasicBlock 

Fields

Instances

Show lab => Show (BasicBlock' lab) Source # 

Methods

showsPrec :: Int -> BasicBlock' lab -> ShowS #

show :: BasicBlock' lab -> String #

showList :: [BasicBlock' lab] -> ShowS #

Generic (BasicBlock' lab) Source # 

Associated Types

type Rep (BasicBlock' lab) :: * -> * #

Methods

from :: BasicBlock' lab -> Rep (BasicBlock' lab) x #

to :: Rep (BasicBlock' lab) x -> BasicBlock' lab #

type Rep (BasicBlock' lab) Source # 
type Rep (BasicBlock' lab) = D1 (MetaData "BasicBlock'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "BasicBlock" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "bbLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe lab))) (S1 (MetaSel (Just Symbol "bbStmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Stmt' lab]))))

brTargets :: BasicBlock' lab -> [lab] Source #

data Linkage Source #

Symbol Linkage

Instances

Eq Linkage Source # 

Methods

(==) :: Linkage -> Linkage -> Bool #

(/=) :: Linkage -> Linkage -> Bool #

Show Linkage Source # 
Generic Linkage Source # 

Associated Types

type Rep Linkage :: * -> * #

Methods

from :: Linkage -> Rep Linkage x #

to :: Rep Linkage x -> Linkage #

type Rep Linkage Source # 
type Rep Linkage = D1 (MetaData "Linkage" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Private" PrefixI False) U1) (C1 (MetaCons "LinkerPrivate" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LinkerPrivateWeak" PrefixI False) U1) (C1 (MetaCons "LinkerPrivateWeakDefAuto" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Internal" PrefixI False) U1) (C1 (MetaCons "AvailableExternally" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Linkonce" PrefixI False) U1) (C1 (MetaCons "Weak" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Common" PrefixI False) U1) (C1 (MetaCons "Appending" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ExternWeak" PrefixI False) U1) (C1 (MetaCons "LinkonceODR" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "WeakODR" PrefixI False) U1) (C1 (MetaCons "External" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DLLImport" PrefixI False) U1) (C1 (MetaCons "DLLExport" PrefixI False) U1)))))

newtype GC Source #

Constructors

GC 

Fields

Instances

Show GC Source # 

Methods

showsPrec :: Int -> GC -> ShowS #

show :: GC -> String #

showList :: [GC] -> ShowS #

Generic GC Source # 

Associated Types

type Rep GC :: * -> * #

Methods

from :: GC -> Rep GC x #

to :: Rep GC x -> GC #

type Rep GC Source # 
type Rep GC = D1 (MetaData "GC" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" True) (C1 (MetaCons "GC" PrefixI True) (S1 (MetaSel (Just Symbol "getGC") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data Typed a Source #

Constructors

Typed 

Fields

Instances

Functor Typed Source # 

Methods

fmap :: (a -> b) -> Typed a -> Typed b #

(<$) :: a -> Typed b -> Typed a #

Foldable Typed Source # 

Methods

fold :: Monoid m => Typed m -> m #

foldMap :: Monoid m => (a -> m) -> Typed a -> m #

foldr :: (a -> b -> b) -> b -> Typed a -> b #

foldr' :: (a -> b -> b) -> b -> Typed a -> b #

foldl :: (b -> a -> b) -> b -> Typed a -> b #

foldl' :: (b -> a -> b) -> b -> Typed a -> b #

foldr1 :: (a -> a -> a) -> Typed a -> a #

foldl1 :: (a -> a -> a) -> Typed a -> a #

toList :: Typed a -> [a] #

null :: Typed a -> Bool #

length :: Typed a -> Int #

elem :: Eq a => a -> Typed a -> Bool #

maximum :: Ord a => Typed a -> a #

minimum :: Ord a => Typed a -> a #

sum :: Num a => Typed a -> a #

product :: Num a => Typed a -> a #

Traversable Typed Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Typed a -> f (Typed b) #

sequenceA :: Applicative f => Typed (f a) -> f (Typed a) #

mapM :: Monad m => (a -> m b) -> Typed a -> m (Typed b) #

sequence :: Monad m => Typed (m a) -> m (Typed a) #

DefineArgs Type (Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

Show a => Show (Typed a) Source # 

Methods

showsPrec :: Int -> Typed a -> ShowS #

show :: Typed a -> String #

showList :: [Typed a] -> ShowS #

Generic (Typed a) Source # 

Associated Types

type Rep (Typed a) :: * -> * #

Methods

from :: Typed a -> Rep (Typed a) x #

to :: Rep (Typed a) x -> Typed a #

IsValue a => IsValue (Typed a) Source # 

Methods

toValue :: Typed a -> Value Source #

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs as k => DefineArgs ((:>) Type as) (Typed Value -> k) Source # 

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

type Rep (Typed a) Source # 
type Rep (Typed a) = D1 (MetaData "Typed" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "Typed" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "typedType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Just Symbol "typedValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

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

data ArithOp Source #

Constructors

Add Bool Bool
  • Integral addition.
  • First boolean flag: check for unsigned overflow.
  • Second boolean flag: check for signed overflow.
  • If the checks fail, then the result is poisoned.
FAdd

Floating point addition.

Sub Bool Bool
  • Integral subtraction.
  • First boolean flag: check for unsigned overflow.
  • Second boolean flag: check for signed overflow.
  • If the checks fail, then the result is poisoned.
FSub

Floating point subtraction.

Mul Bool Bool
  • Integral multiplication.
  • First boolean flag: check for unsigned overflow.
  • Second boolean flag: check for signed overflow.
  • If the checks fail, then the result is poisoned.
FMul

Floating point multiplication.

UDiv Bool
  • Integral unsigned division.
  • Boolean flag: check for exact result.
  • If the check fails, then the result is poisoned.
SDiv Bool
  • Integral signed division.
  • Boolean flag: check for exact result.
  • If the check fails, then the result is poisoned.
FDiv

Floating point division.

URem

Integral unsigned reminder resulting from unsigned division. Division by 0 is undefined.

SRem
  • Integral signded reminder resulting from signed division.
  • The sign of the reminder matches the divident (first parameter).
  • Division by 0 is undefined.
FRem
  • Floating point reminder resulting from floating point division.
  • The reminder has the same sign as the divident (first parameter).

Instances

Eq ArithOp Source # 

Methods

(==) :: ArithOp -> ArithOp -> Bool #

(/=) :: ArithOp -> ArithOp -> Bool #

Show ArithOp Source # 
Generic ArithOp Source # 

Associated Types

type Rep ArithOp :: * -> * #

Methods

from :: ArithOp -> Rep ArithOp x #

to :: Rep ArithOp x -> ArithOp #

type Rep ArithOp Source # 

data BitOp Source #

Binary bitwise operators.

Constructors

Shl Bool Bool
  • Shift left.
  • First bool flag: check for unsigned overflow (i.e., shifted out a 1).
  • Second bool flag: check for signed overflow (i.e., shifted out something that does not match the sign bit)

    If a check fails, then the result is poisoned.

    The value of the second parameter must be strictly less than the number of bits in the first parameter, otherwise the result is undefined.

Lshr Bool
  • Logical shift right.
  • The boolean is for exact check: poison the result, if we shift out a 1 bit (i.e., had to round).

The value of the second parameter must be strictly less than the number of bits in the first parameter, otherwise the result is undefined.

Ashr Bool
  • Arithmetic shift right.
  • The boolean is for exact check: poison the result, if we shift out a 1 bit (i.e., had to round).

The value of the second parameter must be strictly less than the number of bits in the first parameter, otherwise the result is undefined.

And 
Or 
Xor 

data ConvOp Source #

Conversions from one type to another.

Instances

Show ConvOp Source # 
Generic ConvOp Source # 

Associated Types

type Rep ConvOp :: * -> * #

Methods

from :: ConvOp -> Rep ConvOp x #

to :: Rep ConvOp x -> ConvOp #

type Rep ConvOp Source # 
type Rep ConvOp = D1 (MetaData "ConvOp" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Trunc" PrefixI False) U1) ((:+:) (C1 (MetaCons "ZExt" PrefixI False) U1) (C1 (MetaCons "SExt" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FpTrunc" PrefixI False) U1) ((:+:) (C1 (MetaCons "FpExt" PrefixI False) U1) (C1 (MetaCons "FpToUi" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "FpToSi" PrefixI False) U1) ((:+:) (C1 (MetaCons "UiToFp" PrefixI False) U1) (C1 (MetaCons "SiToFp" PrefixI False) U1))) ((:+:) (C1 (MetaCons "PtrToInt" PrefixI False) U1) ((:+:) (C1 (MetaCons "IntToPtr" PrefixI False) U1) (C1 (MetaCons "BitCast" PrefixI False) U1)))))

type Align = Int Source #

data Instr' lab Source #

Constructors

Ret (Typed (Value' lab))
  • Return from function with the given value.
  • Ends basic block.
RetVoid
  • Return from function.
  • Ends basic block.
Arith ArithOp (Typed (Value' lab)) (Value' lab)
  • Binary arithmetic operation, both operands have the same type.
  • Middle of basic block.
  • The result is the same as parameters.
Bit BitOp (Typed (Value' lab)) (Value' lab)
  • Binary bit-vector operation, both operands have the same type.
  • Middle of basic block.
  • The result is the same as parameters.
Conv ConvOp (Typed (Value' lab)) Type
  • Convert a value from one type to another.
  • Middle of basic block.
  • The result matches the 3rd parameter.
Call Bool Type (Value' lab) [Typed (Value' lab)]
  • Call a function. The boolean is tail-call hint (XXX: needs to be updated)
  • Middle of basic block.
  • The result is as indicated by the provided type.
Alloca Type (Maybe (Typed (Value' lab))) (Maybe Int)
  • Allocated space on the stack: type of elements; how many elements (1 if Nothing); required alignment.
  • Middle of basic block.
  • Returns a pointer to hold the given number of elements.
Load (Typed (Value' lab)) (Maybe Align)
  • Read a value from the given address: address to read from; assumptions about alignment of the given pointer.
  • Middle of basic block.
  • Returns a value of type matching the pointer.
Store (Typed (Value' lab)) (Typed (Value' lab)) (Maybe Align)
  • Write a value to memory: value to store; pointer to location where to store; assumptions about the alignment of the given pointer.
  • Middle of basic block.
  • Effect.
ICmp ICmpOp (Typed (Value' lab)) (Value' lab)
  • Compare two integral values.
  • Middle of basic block.
  • Returns a boolean value.
FCmp FCmpOp (Typed (Value' lab)) (Value' lab)
  • Compare two floating point values.
  • Middle of basic block.
  • Returns a boolean value.
Phi Type [(Value' lab, lab)]
  • Join point for an SSA value: we get one value per predecessor basic block.
  • Middle of basic block.
  • Returns a value of the specified type.
GEP Bool (Typed (Value' lab)) [Typed (Value' lab)]
  • "Get element pointer", compute the address of a field in a structure: inbounds check (value poisoned if this fails); pointer to parent strucutre; path to a sub-component of a strucutre.
  • Middle of basic block.
  • Returns the address of the requiested member.

The types in path are the types of the index, not the fields.

The indexes are in units of a fields (i.e., the first element in a struct is field 0, the next one is 1, etc., regardless of the size of the fields in bytes).

Select (Typed (Value' lab)) (Typed (Value' lab)) (Value' lab)
  • Local if-then-else; the first argument is boolean, if true pick the 2nd argument, otherwise evaluate to the 3rd.
  • Middle of basic block.
  • Returns either the 2nd or the 3rd argument.
ExtractValue (Typed (Value' lab)) [Int32]
  • Get the value of a member of an aggregate value: the first argument is an aggregate value (not a pointer!), the second is a path of indexes, similar to the one in GEP.
  • Middle of basic block.
  • Returns the given member of the aggregate value.
InsertValue (Typed (Value' lab)) (Typed (Value' lab)) [Int32]
  • Set the value for a member of an aggregate value: the first argument is the value to insert, the second is the aggreagate value to be modified.
  • Middle of basic block.
  • Returns an updated aggregate value.
ExtractElt (Typed (Value' lab)) (Value' lab)
  • Get an element from a vector: the first argument is a vector, the second an index.
  • Middle of basic block.
  • Returns the element at the given position.
InsertElt (Typed (Value' lab)) (Typed (Value' lab)) (Value' lab)
  • Modify an element of a vector: the first argument is the vector, the second the value to be inserted, the third is the index where to insert the value.
  • Middle of basic block.
  • Returns an updated vector.
ShuffleVector (Typed (Value' lab)) (Value' lab) (Typed (Value' lab)) 
Jump lab
  • Jump to the given basic block.
  • Ends basic block.
Br (Typed (Value' lab)) lab lab
  • Conditional jump: if the value is true jump to the first basic block, otherwise jump to the second.
  • Ends basic block.
Invoke Type (Value' lab) [Typed (Value' lab)] lab lab 
Comment String

Comment

Unreachable

No defined sematics, we should not get to here.

Unwind 
VaArg (Typed (Value' lab)) Type 
IndirectBr (Typed (Value' lab)) [lab] 
Switch (Typed (Value' lab)) lab [(Integer, lab)]
  • Multi-way branch: the first value determines the direction of the branch, the label is a default direction, if the value does not appear in the jump table, the last argument is the jump table.
  • Ends basic block.
LandingPad Type (Typed (Value' lab)) Bool [Clause' lab] 
Resume (Typed (Value' lab)) 

Instances

Functor Instr' Source # 

Methods

fmap :: (a -> b) -> Instr' a -> Instr' b #

(<$) :: a -> Instr' b -> Instr' a #

HasLabel Instr' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Instr' a -> m (Instr' b) Source #

Show lab => Show (Instr' lab) Source # 

Methods

showsPrec :: Int -> Instr' lab -> ShowS #

show :: Instr' lab -> String #

showList :: [Instr' lab] -> ShowS #

Generic (Instr' lab) Source # 

Associated Types

type Rep (Instr' lab) :: * -> * #

Methods

from :: Instr' lab -> Rep (Instr' lab) x #

to :: Rep (Instr' lab) x -> Instr' lab #

type Rep (Instr' lab) Source # 
type Rep (Instr' lab) = D1 (MetaData "Instr'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ret" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))) ((:+:) (C1 (MetaCons "RetVoid" PrefixI False) U1) (C1 (MetaCons "Arith" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ArithOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))))) ((:+:) ((:+:) (C1 (MetaCons "Bit" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BitOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))) (C1 (MetaCons "Conv" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConvOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) ((:+:) (C1 (MetaCons "Call" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Typed (Value' lab)]))))) (C1 (MetaCons "Alloca" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Typed (Value' lab))))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Load" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Align))))) (C1 (MetaCons "Store" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Align))))))) ((:+:) (C1 (MetaCons "ICmp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ICmpOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))) (C1 (MetaCons "FCmp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FCmpOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))))) ((:+:) ((:+:) (C1 (MetaCons "Phi" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Value' lab, lab)])))) (C1 (MetaCons "GEP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Typed (Value' lab)])))))) ((:+:) (C1 (MetaCons "Select" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))) (C1 (MetaCons "ExtractValue" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int32])))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "InsertValue" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int32]))))) ((:+:) (C1 (MetaCons "ExtractElt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab))))) (C1 (MetaCons "InsertElt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))))) ((:+:) ((:+:) (C1 (MetaCons "ShuffleVector" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))))) (C1 (MetaCons "Jump" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab)))) ((:+:) (C1 (MetaCons "Br" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab))))) (C1 (MetaCons "Invoke" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Typed (Value' lab)])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Comment" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) (C1 (MetaCons "Unreachable" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Unwind" PrefixI False) U1) (C1 (MetaCons "VaArg" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) ((:+:) ((:+:) (C1 (MetaCons "IndirectBr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [lab])))) (C1 (MetaCons "Switch" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Integer, lab)])))))) ((:+:) (C1 (MetaCons "LandingPad" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Clause' lab]))))) (C1 (MetaCons "Resume" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))))))))

data Clause' lab Source #

Constructors

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

Instances

Functor Clause' Source # 

Methods

fmap :: (a -> b) -> Clause' a -> Clause' b #

(<$) :: a -> Clause' b -> Clause' a #

Generic1 Clause' Source # 

Associated Types

type Rep1 (Clause' :: * -> *) :: * -> * #

Methods

from1 :: Clause' a -> Rep1 Clause' a #

to1 :: Rep1 Clause' a -> Clause' a #

HasLabel Clause' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Clause' a -> m (Clause' b) Source #

Show lab => Show (Clause' lab) Source # 

Methods

showsPrec :: Int -> Clause' lab -> ShowS #

show :: Clause' lab -> String #

showList :: [Clause' lab] -> ShowS #

Generic (Clause' lab) Source # 

Associated Types

type Rep (Clause' lab) :: * -> * #

Methods

from :: Clause' lab -> Rep (Clause' lab) x #

to :: Rep (Clause' lab) x -> Clause' lab #

type Rep1 Clause' Source # 
type Rep (Clause' lab) Source # 
type Rep (Clause' lab) = D1 (MetaData "Clause'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) (C1 (MetaCons "Catch" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))) (C1 (MetaCons "Filter" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))))

data ICmpOp Source #

Integer comparison operators.

Constructors

Ieq 
Ine 
Iugt 
Iuge 
Iult 
Iule 
Isgt 
Isge 
Islt 
Isle 

Instances

Show ICmpOp Source # 
Generic ICmpOp Source # 

Associated Types

type Rep ICmpOp :: * -> * #

Methods

from :: ICmpOp -> Rep ICmpOp x #

to :: Rep ICmpOp x -> ICmpOp #

type Rep ICmpOp Source # 
type Rep ICmpOp = D1 (MetaData "ICmpOp" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ieq" PrefixI False) U1) (C1 (MetaCons "Ine" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Iugt" PrefixI False) U1) ((:+:) (C1 (MetaCons "Iuge" PrefixI False) U1) (C1 (MetaCons "Iult" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Iule" PrefixI False) U1) (C1 (MetaCons "Isgt" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Isge" PrefixI False) U1) ((:+:) (C1 (MetaCons "Islt" PrefixI False) U1) (C1 (MetaCons "Isle" PrefixI False) U1)))))

data FCmpOp Source #

Floating-point comparison operators.

Instances

Show FCmpOp Source # 
Generic FCmpOp Source # 

Associated Types

type Rep FCmpOp :: * -> * #

Methods

from :: FCmpOp -> Rep FCmpOp x #

to :: Rep FCmpOp x -> FCmpOp #

type Rep FCmpOp Source # 
type Rep FCmpOp = D1 (MetaData "FCmpOp" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Ffalse" PrefixI False) U1) (C1 (MetaCons "Foeq" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Fogt" PrefixI False) U1) (C1 (MetaCons "Foge" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Folt" PrefixI False) U1) (C1 (MetaCons "Fole" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Fone" PrefixI False) U1) (C1 (MetaCons "Ford" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Fueq" PrefixI False) U1) (C1 (MetaCons "Fugt" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Fuge" PrefixI False) U1) (C1 (MetaCons "Fult" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Fule" PrefixI False) U1) (C1 (MetaCons "Fune" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Funo" PrefixI False) U1) (C1 (MetaCons "Ftrue" PrefixI False) U1)))))

data Value' lab Source #

Instances

Functor Value' Source # 

Methods

fmap :: (a -> b) -> Value' a -> Value' b #

(<$) :: a -> Value' b -> Value' a #

Generic1 Value' Source # 

Associated Types

type Rep1 (Value' :: * -> *) :: * -> * #

Methods

from1 :: Value' a -> Rep1 Value' a #

to1 :: Rep1 Value' a -> Value' a #

HasLabel Value' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Value' a -> m (Value' b) Source #

IsValue Value Source # 

Methods

toValue :: Value -> Value Source #

DefineArgs Type (Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

Show lab => Show (Value' lab) Source # 

Methods

showsPrec :: Int -> Value' lab -> ShowS #

show :: Value' lab -> String #

showList :: [Value' lab] -> ShowS #

Generic (Value' lab) Source # 

Associated Types

type Rep (Value' lab) :: * -> * #

Methods

from :: Value' lab -> Rep (Value' lab) x #

to :: Rep (Value' lab) x -> Value' lab #

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs as k => DefineArgs ((:>) Type as) (Typed Value -> k) Source # 

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) Source # 

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

type Rep1 Value' Source # 
type Rep1 Value' = D1 (MetaData "Value'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ValInteger" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) (C1 (MetaCons "ValBool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:+:) (C1 (MetaCons "ValFloat" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) (C1 (MetaCons "ValDouble" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))))) ((:+:) ((:+:) (C1 (MetaCons "ValIdent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident))) (C1 (MetaCons "ValSymbol" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Symbol)))) ((:+:) (C1 (MetaCons "ValNull" PrefixI False) U1) ((:+:) (C1 (MetaCons "ValArray" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) [] (Rec1 Value'))))) (C1 (MetaCons "ValVector" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) [] (Rec1 Value'))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ValStruct" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) [] ((:.:) Typed (Rec1 Value'))))) (C1 (MetaCons "ValPackedStruct" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) [] ((:.:) Typed (Rec1 Value')))))) ((:+:) (C1 (MetaCons "ValString" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) (C1 (MetaCons "ValConstExpr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ConstExpr'))))) ((:+:) ((:+:) (C1 (MetaCons "ValUndef" PrefixI False) U1) (C1 (MetaCons "ValLabel" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))) ((:+:) (C1 (MetaCons "ValZeroInit" PrefixI False) U1) ((:+:) (C1 (MetaCons "ValAsm" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) (C1 (MetaCons "ValMd" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ValMd'))))))))
type Rep (Value' lab) Source # 
type Rep (Value' lab) = D1 (MetaData "Value'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ValInteger" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) (C1 (MetaCons "ValBool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:+:) (C1 (MetaCons "ValFloat" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) (C1 (MetaCons "ValDouble" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))))) ((:+:) ((:+:) (C1 (MetaCons "ValIdent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident))) (C1 (MetaCons "ValSymbol" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Symbol)))) ((:+:) (C1 (MetaCons "ValNull" PrefixI False) U1) ((:+:) (C1 (MetaCons "ValArray" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Value' lab])))) (C1 (MetaCons "ValVector" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Value' lab])))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ValStruct" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Typed (Value' lab)]))) (C1 (MetaCons "ValPackedStruct" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Typed (Value' lab)])))) ((:+:) (C1 (MetaCons "ValString" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) (C1 (MetaCons "ValConstExpr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ConstExpr' lab)))))) ((:+:) ((:+:) (C1 (MetaCons "ValUndef" PrefixI False) U1) (C1 (MetaCons "ValLabel" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab)))) ((:+:) (C1 (MetaCons "ValZeroInit" PrefixI False) U1) ((:+:) (C1 (MetaCons "ValAsm" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) (C1 (MetaCons "ValMd" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ValMd' lab)))))))))

data ValMd' lab Source #

Instances

Functor ValMd' Source # 

Methods

fmap :: (a -> b) -> ValMd' a -> ValMd' b #

(<$) :: a -> ValMd' b -> ValMd' a #

Generic1 ValMd' Source # 

Associated Types

type Rep1 (ValMd' :: * -> *) :: * -> * #

Methods

from1 :: ValMd' a -> Rep1 ValMd' a #

to1 :: Rep1 ValMd' a -> ValMd' a #

HasLabel ValMd' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> ValMd' a -> m (ValMd' b) Source #

Show lab => Show (ValMd' lab) Source # 

Methods

showsPrec :: Int -> ValMd' lab -> ShowS #

show :: ValMd' lab -> String #

showList :: [ValMd' lab] -> ShowS #

Generic (ValMd' lab) Source # 

Associated Types

type Rep (ValMd' lab) :: * -> * #

Methods

from :: ValMd' lab -> Rep (ValMd' lab) x #

to :: Rep (ValMd' lab) x -> ValMd' lab #

type Rep1 ValMd' Source # 
type Rep (ValMd' lab) Source # 

data DebugLoc' lab Source #

Constructors

DebugLoc 

Fields

Instances

Functor DebugLoc' Source # 

Methods

fmap :: (a -> b) -> DebugLoc' a -> DebugLoc' b #

(<$) :: a -> DebugLoc' b -> DebugLoc' a #

Generic1 DebugLoc' Source # 

Associated Types

type Rep1 (DebugLoc' :: * -> *) :: * -> * #

HasLabel DebugLoc' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DebugLoc' a -> m (DebugLoc' b) Source #

Show lab => Show (DebugLoc' lab) Source # 

Methods

showsPrec :: Int -> DebugLoc' lab -> ShowS #

show :: DebugLoc' lab -> String #

showList :: [DebugLoc' lab] -> ShowS #

Generic (DebugLoc' lab) Source # 

Associated Types

type Rep (DebugLoc' lab) :: * -> * #

Methods

from :: DebugLoc' lab -> Rep (DebugLoc' lab) x #

to :: Rep (DebugLoc' lab) x -> DebugLoc' lab #

type Rep1 DebugLoc' Source # 
type Rep (DebugLoc' lab) Source # 

data Stmt' lab Source #

Constructors

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

Instances

Functor Stmt' Source # 

Methods

fmap :: (a -> b) -> Stmt' a -> Stmt' b #

(<$) :: a -> Stmt' b -> Stmt' a #

Generic1 Stmt' Source # 

Associated Types

type Rep1 (Stmt' :: * -> *) :: * -> * #

Methods

from1 :: Stmt' a -> Rep1 Stmt' a #

to1 :: Rep1 Stmt' a -> Stmt' a #

HasLabel Stmt' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> Stmt' a -> m (Stmt' b) Source #

Show lab => Show (Stmt' lab) Source # 

Methods

showsPrec :: Int -> Stmt' lab -> ShowS #

show :: Stmt' lab -> String #

showList :: [Stmt' lab] -> ShowS #

Generic (Stmt' lab) Source # 

Associated Types

type Rep (Stmt' lab) :: * -> * #

Methods

from :: Stmt' lab -> Rep (Stmt' lab) x #

to :: Rep (Stmt' lab) x -> Stmt' lab #

type Rep1 Stmt' Source # 
type Rep (Stmt' lab) Source # 

stmtInstr :: Stmt' lab -> Instr' lab Source #

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

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

data ConstExpr' lab Source #

Constructors

ConstGEP Bool (Maybe Type) [Typed (Value' lab)]

Element type introduced in LLVM 3.7

ConstConv ConvOp (Typed (Value' lab)) Type 
ConstSelect (Typed (Value' lab)) (Typed (Value' lab)) (Typed (Value' lab)) 
ConstBlockAddr Symbol lab 
ConstFCmp FCmpOp (Typed (Value' lab)) (Typed (Value' lab)) 
ConstICmp ICmpOp (Typed (Value' lab)) (Typed (Value' lab)) 
ConstArith ArithOp (Typed (Value' lab)) (Value' lab) 
ConstBit BitOp (Typed (Value' lab)) (Value' lab) 

Instances

Functor ConstExpr' Source # 

Methods

fmap :: (a -> b) -> ConstExpr' a -> ConstExpr' b #

(<$) :: a -> ConstExpr' b -> ConstExpr' a #

Generic1 ConstExpr' Source # 

Associated Types

type Rep1 (ConstExpr' :: * -> *) :: * -> * #

HasLabel ConstExpr' Source #

Clever instance that actually uses the block name

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> ConstExpr' a -> m (ConstExpr' b) Source #

Show lab => Show (ConstExpr' lab) Source # 

Methods

showsPrec :: Int -> ConstExpr' lab -> ShowS #

show :: ConstExpr' lab -> String #

showList :: [ConstExpr' lab] -> ShowS #

Generic (ConstExpr' lab) Source # 

Associated Types

type Rep (ConstExpr' lab) :: * -> * #

Methods

from :: ConstExpr' lab -> Rep (ConstExpr' lab) x #

to :: Rep (ConstExpr' lab) x -> ConstExpr' lab #

type Rep1 ConstExpr' Source # 
type Rep1 ConstExpr' = D1 (MetaData "ConstExpr'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ConstGEP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Type))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) [] ((:.:) Typed (Rec1 Value'))))))) (C1 (MetaCons "ConstConv" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConvOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) ((:+:) (C1 (MetaCons "ConstSelect" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value')))))) (C1 (MetaCons "ConstBlockAddr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Symbol)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))))) ((:+:) ((:+:) (C1 (MetaCons "ConstFCmp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FCmpOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value')))))) (C1 (MetaCons "ConstICmp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ICmpOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))))))) ((:+:) (C1 (MetaCons "ConstArith" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ArithOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Value'))))) (C1 (MetaCons "ConstBit" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BitOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Typed (Rec1 Value'))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Value'))))))))
type Rep (ConstExpr' lab) Source # 
type Rep (ConstExpr' lab) = D1 (MetaData "ConstExpr'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ConstGEP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Type))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Typed (Value' lab)]))))) (C1 (MetaCons "ConstConv" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConvOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)))))) ((:+:) (C1 (MetaCons "ConstSelect" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))))) (C1 (MetaCons "ConstBlockAddr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Symbol)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lab)))))) ((:+:) ((:+:) (C1 (MetaCons "ConstFCmp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FCmpOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab))))))) (C1 (MetaCons "ConstICmp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ICmpOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))))))) ((:+:) (C1 (MetaCons "ConstArith" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ArithOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))) (C1 (MetaCons "ConstBit" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BitOp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Typed (Value' lab)))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value' lab)))))))))

data DebugInfo' lab Source #

Instances

Functor DebugInfo' Source # 

Methods

fmap :: (a -> b) -> DebugInfo' a -> DebugInfo' b #

(<$) :: a -> DebugInfo' b -> DebugInfo' a #

Generic1 DebugInfo' Source # 

Associated Types

type Rep1 (DebugInfo' :: * -> *) :: * -> * #

HasLabel DebugInfo' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DebugInfo' a -> m (DebugInfo' b) Source #

Show lab => Show (DebugInfo' lab) Source # 

Methods

showsPrec :: Int -> DebugInfo' lab -> ShowS #

show :: DebugInfo' lab -> String #

showList :: [DebugInfo' lab] -> ShowS #

Generic (DebugInfo' lab) Source # 

Associated Types

type Rep (DebugInfo' lab) :: * -> * #

Methods

from :: DebugInfo' lab -> Rep (DebugInfo' lab) x #

to :: Rep (DebugInfo' lab) x -> DebugInfo' lab #

type Rep1 DebugInfo' Source # 
type Rep1 DebugInfo' = D1 (MetaData "DebugInfo'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoBasicType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIBasicType))) ((:+:) (C1 (MetaCons "DebugInfoCompileUnit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DICompileUnit'))) (C1 (MetaCons "DebugInfoCompositeType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DICompositeType'))))) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoDerivedType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DIDerivedType'))) (C1 (MetaCons "DebugInfoEnumerator" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64))))) ((:+:) (C1 (MetaCons "DebugInfoExpression" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIExpression))) (C1 (MetaCons "DebugInfoFile" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFile)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoGlobalVariable" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DIGlobalVariable'))) (C1 (MetaCons "DebugInfoGlobalVariableExpression" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DIGlobalVariableExpression')))) ((:+:) (C1 (MetaCons "DebugInfoLexicalBlock" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DILexicalBlock'))) (C1 (MetaCons "DebugInfoLexicalBlockFile" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DILexicalBlockFile'))))) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoLocalVariable" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DILocalVariable'))) (C1 (MetaCons "DebugInfoSubprogram" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DISubprogram')))) ((:+:) (C1 (MetaCons "DebugInfoSubrange" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DISubrange))) (C1 (MetaCons "DebugInfoSubroutineType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 DISubroutineType')))))))
type Rep (DebugInfo' lab) Source # 
type Rep (DebugInfo' lab) = D1 (MetaData "DebugInfo'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoBasicType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIBasicType))) ((:+:) (C1 (MetaCons "DebugInfoCompileUnit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DICompileUnit' lab)))) (C1 (MetaCons "DebugInfoCompositeType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DICompositeType' lab)))))) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoDerivedType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DIDerivedType' lab)))) (C1 (MetaCons "DebugInfoEnumerator" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64))))) ((:+:) (C1 (MetaCons "DebugInfoExpression" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIExpression))) (C1 (MetaCons "DebugInfoFile" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFile)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoGlobalVariable" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DIGlobalVariable' lab)))) (C1 (MetaCons "DebugInfoGlobalVariableExpression" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DIGlobalVariableExpression' lab))))) ((:+:) (C1 (MetaCons "DebugInfoLexicalBlock" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DILexicalBlock' lab)))) (C1 (MetaCons "DebugInfoLexicalBlockFile" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DILexicalBlockFile' lab)))))) ((:+:) ((:+:) (C1 (MetaCons "DebugInfoLocalVariable" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DILocalVariable' lab)))) (C1 (MetaCons "DebugInfoSubprogram" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DISubprogram' lab))))) ((:+:) (C1 (MetaCons "DebugInfoSubrange" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DISubrange))) (C1 (MetaCons "DebugInfoSubroutineType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DISubroutineType' lab))))))))

data DICompileUnit' lab Source #

Instances

Functor DICompileUnit' Source # 

Methods

fmap :: (a -> b) -> DICompileUnit' a -> DICompileUnit' b #

(<$) :: a -> DICompileUnit' b -> DICompileUnit' a #

Generic1 DICompileUnit' Source # 

Associated Types

type Rep1 (DICompileUnit' :: * -> *) :: * -> * #

HasLabel DICompileUnit' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DICompileUnit' a -> m (DICompileUnit' b) Source #

Show lab => Show (DICompileUnit' lab) Source # 
Generic (DICompileUnit' lab) Source # 

Associated Types

type Rep (DICompileUnit' lab) :: * -> * #

Methods

from :: DICompileUnit' lab -> Rep (DICompileUnit' lab) x #

to :: Rep (DICompileUnit' lab) x -> DICompileUnit' lab #

type Rep1 DICompileUnit' Source # 
type Rep1 DICompileUnit' = D1 (MetaData "DICompileUnit'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DICompileUnit" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuLanguage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfLang)) (S1 (MetaSel (Just Symbol "dicuFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))) ((:*:) (S1 (MetaSel (Just Symbol "dicuProducer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dicuIsOptimized") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dicuRuntimeVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16))) ((:*:) (S1 (MetaSel (Just Symbol "dicuSplitDebugFilename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))) (S1 (MetaSel (Just Symbol "dicuEmissionKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIEmissionKind))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuEnums") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dicuRetainedTypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))) ((:*:) (S1 (MetaSel (Just Symbol "dicuSubprograms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dicuGlobals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuImports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dicuMacros") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))) ((:*:) (S1 (MetaSel (Just Symbol "dicuDWOId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "dicuSplitDebugInlining") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))))
type Rep (DICompileUnit' lab) Source # 
type Rep (DICompileUnit' lab) = D1 (MetaData "DICompileUnit'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DICompileUnit" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuLanguage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfLang)) (S1 (MetaSel (Just Symbol "dicuFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) ((:*:) (S1 (MetaSel (Just Symbol "dicuProducer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dicuIsOptimized") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dicuRuntimeVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16))) ((:*:) (S1 (MetaSel (Just Symbol "dicuSplitDebugFilename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))) (S1 (MetaSel (Just Symbol "dicuEmissionKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIEmissionKind))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuEnums") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dicuRetainedTypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) ((:*:) (S1 (MetaSel (Just Symbol "dicuSubprograms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dicuGlobals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dicuImports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dicuMacros") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) ((:*:) (S1 (MetaSel (Just Symbol "dicuDWOId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "dicuSplitDebugInlining") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))))

data DICompositeType' lab Source #

Instances

Functor DICompositeType' Source # 

Methods

fmap :: (a -> b) -> DICompositeType' a -> DICompositeType' b #

(<$) :: a -> DICompositeType' b -> DICompositeType' a #

Generic1 DICompositeType' Source # 

Associated Types

type Rep1 (DICompositeType' :: * -> *) :: * -> * #

HasLabel DICompositeType' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DICompositeType' a -> m (DICompositeType' b) Source #

Show lab => Show (DICompositeType' lab) Source # 
Generic (DICompositeType' lab) Source # 

Associated Types

type Rep (DICompositeType' lab) :: * -> * #

type Rep1 DICompositeType' Source # 
type Rep1 DICompositeType' = D1 (MetaData "DICompositeType'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DICompositeType" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfTag)) ((:*:) (S1 (MetaSel (Just Symbol "dictName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dictFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) (S1 (MetaSel (Just Symbol "dictScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))) ((:*:) (S1 (MetaSel (Just Symbol "dictBaseType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dictSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictAlign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "dictOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))) ((:*:) (S1 (MetaSel (Just Symbol "dictFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFlags)) (S1 (MetaSel (Just Symbol "dictElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictRuntimeLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfLang)) (S1 (MetaSel (Just Symbol "dictVTableHolder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))) ((:*:) (S1 (MetaSel (Just Symbol "dictTemplateParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dictIdentifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))))))))
type Rep (DICompositeType' lab) Source # 
type Rep (DICompositeType' lab) = D1 (MetaData "DICompositeType'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DICompositeType" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfTag)) ((:*:) (S1 (MetaSel (Just Symbol "dictName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dictFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) (S1 (MetaSel (Just Symbol "dictScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) ((:*:) (S1 (MetaSel (Just Symbol "dictBaseType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dictSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictAlign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "dictOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))) ((:*:) (S1 (MetaSel (Just Symbol "dictFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFlags)) (S1 (MetaSel (Just Symbol "dictElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dictRuntimeLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfLang)) (S1 (MetaSel (Just Symbol "dictVTableHolder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) ((:*:) (S1 (MetaSel (Just Symbol "dictTemplateParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dictIdentifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))))))))

data DIDerivedType' lab Source #

Instances

Functor DIDerivedType' Source # 

Methods

fmap :: (a -> b) -> DIDerivedType' a -> DIDerivedType' b #

(<$) :: a -> DIDerivedType' b -> DIDerivedType' a #

Generic1 DIDerivedType' Source # 

Associated Types

type Rep1 (DIDerivedType' :: * -> *) :: * -> * #

HasLabel DIDerivedType' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DIDerivedType' a -> m (DIDerivedType' b) Source #

Show lab => Show (DIDerivedType' lab) Source # 
Generic (DIDerivedType' lab) Source # 

Associated Types

type Rep (DIDerivedType' lab) :: * -> * #

Methods

from :: DIDerivedType' lab -> Rep (DIDerivedType' lab) x #

to :: Rep (DIDerivedType' lab) x -> DIDerivedType' lab #

type Rep1 DIDerivedType' Source # 
type Rep (DIDerivedType' lab) Source # 

data DIExpression Source #

Constructors

DIExpression 

Fields

Instances

Show DIExpression Source # 
Generic DIExpression Source # 

Associated Types

type Rep DIExpression :: * -> * #

type Rep DIExpression Source # 
type Rep DIExpression = D1 (MetaData "DIExpression" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DIExpression" PrefixI True) (S1 (MetaSel (Just Symbol "dieElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Word64])))

data DIFile Source #

Constructors

DIFile 

Instances

Show DIFile Source # 
Generic DIFile Source # 

Associated Types

type Rep DIFile :: * -> * #

Methods

from :: DIFile -> Rep DIFile x #

to :: Rep DIFile x -> DIFile #

type Rep DIFile Source # 
type Rep DIFile = D1 (MetaData "DIFile" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DIFile" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "difFilename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) (S1 (MetaSel (Just Symbol "difDirectory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))))

data DIGlobalVariable' lab Source #

Instances

Functor DIGlobalVariable' Source # 
Generic1 DIGlobalVariable' Source # 

Associated Types

type Rep1 (DIGlobalVariable' :: * -> *) :: * -> * #

HasLabel DIGlobalVariable' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DIGlobalVariable' a -> m (DIGlobalVariable' b) Source #

Show lab => Show (DIGlobalVariable' lab) Source # 
Generic (DIGlobalVariable' lab) Source # 

Associated Types

type Rep (DIGlobalVariable' lab) :: * -> * #

type Rep1 DIGlobalVariable' Source # 
type Rep1 DIGlobalVariable' = D1 (MetaData "DIGlobalVariable'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DIGlobalVariable" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "digvScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "digvName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))) ((:*:) (S1 (MetaSel (Just Symbol "digvLinkageName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) ((:*:) (S1 (MetaSel (Just Symbol "digvFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "digvLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "digvType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) ((:*:) (S1 (MetaSel (Just Symbol "digvIsLocal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "digvIsDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "digvVariable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) ((:*:) (S1 (MetaSel (Just Symbol "digvDeclaration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "digvAlignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word32))))))))
type Rep (DIGlobalVariable' lab) Source # 
type Rep (DIGlobalVariable' lab) = D1 (MetaData "DIGlobalVariable'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DIGlobalVariable" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "digvScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "digvName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))) ((:*:) (S1 (MetaSel (Just Symbol "digvLinkageName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) ((:*:) (S1 (MetaSel (Just Symbol "digvFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "digvLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "digvType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) ((:*:) (S1 (MetaSel (Just Symbol "digvIsLocal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "digvIsDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "digvVariable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) ((:*:) (S1 (MetaSel (Just Symbol "digvDeclaration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "digvAlignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word32))))))))

data DIGlobalVariableExpression' lab Source #

Instances

Functor DIGlobalVariableExpression' Source # 
Generic1 DIGlobalVariableExpression' Source # 
HasLabel DIGlobalVariableExpression' Source # 
Show lab => Show (DIGlobalVariableExpression' lab) Source # 
Generic (DIGlobalVariableExpression' lab) Source # 
type Rep1 DIGlobalVariableExpression' Source # 
type Rep1 DIGlobalVariableExpression' = D1 (MetaData "DIGlobalVariableExpression'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DIGlobalVariableExpression" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "digveVariable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "digveExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))))
type Rep (DIGlobalVariableExpression' lab) Source # 
type Rep (DIGlobalVariableExpression' lab) = D1 (MetaData "DIGlobalVariableExpression'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DIGlobalVariableExpression" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "digveVariable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "digveExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))))

data DILexicalBlock' lab Source #

Constructors

DILexicalBlock 

Instances

Functor DILexicalBlock' Source # 

Methods

fmap :: (a -> b) -> DILexicalBlock' a -> DILexicalBlock' b #

(<$) :: a -> DILexicalBlock' b -> DILexicalBlock' a #

Generic1 DILexicalBlock' Source # 

Associated Types

type Rep1 (DILexicalBlock' :: * -> *) :: * -> * #

HasLabel DILexicalBlock' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DILexicalBlock' a -> m (DILexicalBlock' b) Source #

Show lab => Show (DILexicalBlock' lab) Source # 
Generic (DILexicalBlock' lab) Source # 

Associated Types

type Rep (DILexicalBlock' lab) :: * -> * #

Methods

from :: DILexicalBlock' lab -> Rep (DILexicalBlock' lab) x #

to :: Rep (DILexicalBlock' lab) x -> DILexicalBlock' lab #

type Rep1 DILexicalBlock' Source # 
type Rep (DILexicalBlock' lab) Source # 
type Rep (DILexicalBlock' lab) = D1 (MetaData "DILexicalBlock'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DILexicalBlock" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dilbScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dilbFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) ((:*:) (S1 (MetaSel (Just Symbol "dilbLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) (S1 (MetaSel (Just Symbol "dilbColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16)))))

data DILexicalBlockFile' lab Source #

Instances

Functor DILexicalBlockFile' Source # 
Generic1 DILexicalBlockFile' Source # 
HasLabel DILexicalBlockFile' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DILexicalBlockFile' a -> m (DILexicalBlockFile' b) Source #

Show lab => Show (DILexicalBlockFile' lab) Source # 
Generic (DILexicalBlockFile' lab) Source # 

Associated Types

type Rep (DILexicalBlockFile' lab) :: * -> * #

type Rep1 DILexicalBlockFile' Source # 
type Rep1 DILexicalBlockFile' = D1 (MetaData "DILexicalBlockFile'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DILexicalBlockFile" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "dilbfScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ValMd')) ((:*:) (S1 (MetaSel (Just Symbol "dilbfFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dilbfDiscriminator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))))
type Rep (DILexicalBlockFile' lab) Source # 
type Rep (DILexicalBlockFile' lab) = D1 (MetaData "DILexicalBlockFile'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DILexicalBlockFile" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "dilbfScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ValMd' lab))) ((:*:) (S1 (MetaSel (Just Symbol "dilbfFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dilbfDiscriminator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))))

data DILocalVariable' lab Source #

Instances

Functor DILocalVariable' Source # 

Methods

fmap :: (a -> b) -> DILocalVariable' a -> DILocalVariable' b #

(<$) :: a -> DILocalVariable' b -> DILocalVariable' a #

Generic1 DILocalVariable' Source # 

Associated Types

type Rep1 (DILocalVariable' :: * -> *) :: * -> * #

HasLabel DILocalVariable' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DILocalVariable' a -> m (DILocalVariable' b) Source #

Show lab => Show (DILocalVariable' lab) Source # 
Generic (DILocalVariable' lab) Source # 

Associated Types

type Rep (DILocalVariable' lab) :: * -> * #

type Rep1 DILocalVariable' Source # 
type Rep (DILocalVariable' lab) Source # 

data DISubprogram' lab Source #

Instances

Functor DISubprogram' Source # 

Methods

fmap :: (a -> b) -> DISubprogram' a -> DISubprogram' b #

(<$) :: a -> DISubprogram' b -> DISubprogram' a #

Generic1 DISubprogram' Source # 

Associated Types

type Rep1 (DISubprogram' :: * -> *) :: * -> * #

HasLabel DISubprogram' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DISubprogram' a -> m (DISubprogram' b) Source #

Show lab => Show (DISubprogram' lab) Source # 
Generic (DISubprogram' lab) Source # 

Associated Types

type Rep (DISubprogram' lab) :: * -> * #

Methods

from :: DISubprogram' lab -> Rep (DISubprogram' lab) x #

to :: Rep (DISubprogram' lab) x -> DISubprogram' lab #

type Rep1 DISubprogram' Source # 
type Rep1 DISubprogram' = D1 (MetaData "DISubprogram'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DISubprogram" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dispName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))) ((:*:) (S1 (MetaSel (Just Symbol "dispLinkageName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dispFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) (S1 (MetaSel (Just Symbol "dispType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))) ((:*:) (S1 (MetaSel (Just Symbol "dispIsLocal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "dispIsDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "dispScopeLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispContainingType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dispVirtuality") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfVirtuality))) ((:*:) (S1 (MetaSel (Just Symbol "dispVirtualIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) (S1 (MetaSel (Just Symbol "dispThisAdjustment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFlags)) (S1 (MetaSel (Just Symbol "dispIsOptimized") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "dispTemplateParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) ((:*:) (S1 (MetaSel (Just Symbol "dispDeclaration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd'))) (S1 (MetaSel (Just Symbol "dispVariables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))))))))
type Rep (DISubprogram' lab) Source # 
type Rep (DISubprogram' lab) = D1 (MetaData "DISubprogram'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DISubprogram" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dispName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))) ((:*:) (S1 (MetaSel (Just Symbol "dispLinkageName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "dispFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) (S1 (MetaSel (Just Symbol "dispType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) ((:*:) (S1 (MetaSel (Just Symbol "dispIsLocal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "dispIsDefinition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "dispScopeLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispContainingType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dispVirtuality") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DwarfVirtuality))) ((:*:) (S1 (MetaSel (Just Symbol "dispVirtualIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) (S1 (MetaSel (Just Symbol "dispThisAdjustment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dispFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFlags)) (S1 (MetaSel (Just Symbol "dispIsOptimized") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "dispTemplateParams") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) ((:*:) (S1 (MetaSel (Just Symbol "dispDeclaration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) (S1 (MetaSel (Just Symbol "dispVariables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' lab))))))))))

data DISubrange Source #

Constructors

DISubrange 

Instances

Show DISubrange Source # 
Generic DISubrange Source # 

Associated Types

type Rep DISubrange :: * -> * #

type Rep DISubrange Source # 
type Rep DISubrange = D1 (MetaData "DISubrange" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DISubrange" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "disrCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)) (S1 (MetaSel (Just Symbol "disrLowerBound") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64))))

data DISubroutineType' lab Source #

Constructors

DISubroutineType 

Instances

Functor DISubroutineType' Source # 
Generic1 DISubroutineType' Source # 

Associated Types

type Rep1 (DISubroutineType' :: * -> *) :: * -> * #

HasLabel DISubroutineType' Source # 

Methods

relabel :: Applicative m => (Maybe Symbol -> a -> m b) -> DISubroutineType' a -> m (DISubroutineType' b) Source #

Show lab => Show (DISubroutineType' lab) Source # 
Generic (DISubroutineType' lab) Source # 

Associated Types

type Rep (DISubroutineType' lab) :: * -> * #

type Rep1 DISubroutineType' Source # 
type Rep1 DISubroutineType' = D1 (MetaData "DISubroutineType'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DISubroutineType" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "distFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFlags)) (S1 (MetaSel (Just Symbol "distTypeArray") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) Maybe (Rec1 ValMd')))))
type Rep (DISubroutineType' lab) Source # 
type Rep (DISubroutineType' lab) = D1 (MetaData "DISubroutineType'" "Text.LLVM.AST" "llvm-pretty-0.7.1.1-IpjkWQMSj2s5NoN5NnhwxP" False) (C1 (MetaCons "DISubroutineType" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "distFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DIFlags)) (S1 (MetaSel (Just Symbol "distTypeArray") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ValMd' 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

resolveGepFull Source #

Arguments

:: (Ident -> Maybe Type)

Type alias resolution

-> Type

Pointer type

-> [Typed (Value' lab)]

Path

-> Maybe Type

Type of result

Resolves the type of a GEP instruction. Type aliases are resolved using the given function. An invalid use of GEP or one relying on unknown type aliases will return Nothing

resolveGep :: Type -> [Typed (Value' lab)] -> IndexResult Source #

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)] -> IndexResult Source #

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