llvm-pretty-0.12.0.0: A pretty printing library inspired by the llvm binding.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.LLVM.AST

Synopsis

Modules

data Module Source #

Constructors

Module 

Fields

Instances

Instances details
Data Module Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module #

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) #

gmapT :: (forall b. Data b => b -> b) -> Module -> Module #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

Monoid Module Source # 
Instance details

Defined in Text.LLVM.AST

Semigroup Module Source #

Combines fields pointwise.

Instance details

Defined in Text.LLVM.AST

Generic Module Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Show Module Source # 
Instance details

Defined in Text.LLVM.AST

Eq Module Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord Module Source # 
Instance details

Defined in Text.LLVM.AST

LLVMPretty Module Source # 
Instance details

Defined in Text.LLVM.PP

type Rep Module Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Module = D1 ('MetaData "Module" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "Module" 'PrefixI 'True) (((S1 ('MetaSel ('Just "modSourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "modTriple") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetTriple) :*: S1 ('MetaSel ('Just "modDataLayout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataLayout))) :*: (S1 ('MetaSel ('Just "modTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeDecl]) :*: (S1 ('MetaSel ('Just "modNamedMd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NamedMd]) :*: S1 ('MetaSel ('Just "modUnnamedMd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnnamedMd])))) :*: ((S1 ('MetaSel ('Just "modComdat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String SelectionKind)) :*: (S1 ('MetaSel ('Just "modGlobals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Global]) :*: S1 ('MetaSel ('Just "modDeclares") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Declare]))) :*: (S1 ('MetaSel ('Just "modDefines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Define]) :*: (S1 ('MetaSel ('Just "modInlineAsm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InlineAsm) :*: S1 ('MetaSel ('Just "modAliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GlobalAlias]))))))

Named Metadata

data NamedMd Source #

Constructors

NamedMd 

Fields

Instances

Instances details
Data NamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NamedMd -> c NamedMd #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NamedMd #

toConstr :: NamedMd -> Constr #

dataTypeOf :: NamedMd -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NamedMd) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NamedMd) #

gmapT :: (forall b. Data b => b -> b) -> NamedMd -> NamedMd #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NamedMd -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NamedMd -> r #

gmapQ :: (forall d. Data d => d -> u) -> NamedMd -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NamedMd -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NamedMd -> m NamedMd #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedMd -> m NamedMd #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedMd -> m NamedMd #

Generic NamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep NamedMd :: Type -> Type #

Methods

from :: NamedMd -> Rep NamedMd x #

to :: Rep NamedMd x -> NamedMd #

Show NamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Eq NamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord NamedMd Source # 
Instance details

Defined in Text.LLVM.AST

type Rep NamedMd Source # 
Instance details

Defined in Text.LLVM.AST

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

Unnamed Metadata

data UnnamedMd Source #

Constructors

UnnamedMd 

Fields

Instances

Instances details
Data UnnamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnnamedMd -> c UnnamedMd #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnnamedMd #

toConstr :: UnnamedMd -> Constr #

dataTypeOf :: UnnamedMd -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnnamedMd) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnnamedMd) #

gmapT :: (forall b. Data b => b -> b) -> UnnamedMd -> UnnamedMd #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnnamedMd -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnnamedMd -> r #

gmapQ :: (forall d. Data d => d -> u) -> UnnamedMd -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnnamedMd -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnnamedMd -> m UnnamedMd #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnnamedMd -> m UnnamedMd #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnnamedMd -> m UnnamedMd #

Generic UnnamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep UnnamedMd :: Type -> Type #

Show UnnamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Eq UnnamedMd Source # 
Instance details

Defined in Text.LLVM.AST

Ord UnnamedMd Source # 
Instance details

Defined in Text.LLVM.AST

type Rep UnnamedMd Source # 
Instance details

Defined in Text.LLVM.AST

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

Aliases

data GlobalAlias Source #

Instances

Instances details
Data GlobalAlias Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalAlias -> c GlobalAlias #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalAlias #

toConstr :: GlobalAlias -> Constr #

dataTypeOf :: GlobalAlias -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GlobalAlias) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalAlias) #

gmapT :: (forall b. Data b => b -> b) -> GlobalAlias -> GlobalAlias #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalAlias -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalAlias -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalAlias -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalAlias -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalAlias -> m GlobalAlias #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalAlias -> m GlobalAlias #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalAlias -> m GlobalAlias #

Generic GlobalAlias Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep GlobalAlias :: Type -> Type #

Show GlobalAlias Source # 
Instance details

Defined in Text.LLVM.AST

Eq GlobalAlias Source # 
Instance details

Defined in Text.LLVM.AST

Ord GlobalAlias Source # 
Instance details

Defined in Text.LLVM.AST

type Rep GlobalAlias Source # 
Instance details

Defined in Text.LLVM.AST

type Rep GlobalAlias = D1 ('MetaData "GlobalAlias" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "GlobalAlias" 'PrefixI 'True) ((S1 ('MetaSel ('Just "aliasLinkage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Linkage)) :*: S1 ('MetaSel ('Just "aliasVisibility") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Visibility))) :*: (S1 ('MetaSel ('Just "aliasName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Symbol) :*: (S1 ('MetaSel ('Just "aliasType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Just "aliasTarget") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))))

Data Layout

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

Instances details
Data LayoutSpec Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayoutSpec -> c LayoutSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LayoutSpec #

toConstr :: LayoutSpec -> Constr #

dataTypeOf :: LayoutSpec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LayoutSpec) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayoutSpec) #

gmapT :: (forall b. Data b => b -> b) -> LayoutSpec -> LayoutSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayoutSpec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayoutSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> LayoutSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LayoutSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayoutSpec -> m LayoutSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutSpec -> m LayoutSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutSpec -> m LayoutSpec #

Generic LayoutSpec Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep LayoutSpec :: Type -> Type #

Show LayoutSpec Source # 
Instance details

Defined in Text.LLVM.AST

Eq LayoutSpec Source # 
Instance details

Defined in Text.LLVM.AST

Ord LayoutSpec Source # 
Instance details

Defined in Text.LLVM.AST

type Rep LayoutSpec Source # 
Instance details

Defined in Text.LLVM.AST

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

data Mangling Source #

Instances

Instances details
Data Mangling Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mangling -> c Mangling #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Mangling #

toConstr :: Mangling -> Constr #

dataTypeOf :: Mangling -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Mangling) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mangling) #

gmapT :: (forall b. Data b => b -> b) -> Mangling -> Mangling #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mangling -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mangling -> r #

gmapQ :: (forall d. Data d => d -> u) -> Mangling -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Mangling -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mangling -> m Mangling #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mangling -> m Mangling #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mangling -> m Mangling #

Enum Mangling Source # 
Instance details

Defined in Text.LLVM.AST

Generic Mangling Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Mangling :: Type -> Type #

Methods

from :: Mangling -> Rep Mangling x #

to :: Rep Mangling x -> Mangling #

Show Mangling Source # 
Instance details

Defined in Text.LLVM.AST

Eq Mangling Source # 
Instance details

Defined in Text.LLVM.AST

Ord Mangling Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Mangling Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Mangling = D1 ('MetaData "Mangling" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((C1 ('MetaCons "ElfMangling" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MipsMangling" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MachOMangling" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WindowsCoffMangling" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Parse the data layout string.

Inline Assembly

Comdat

data SelectionKind Source #

Instances

Instances details
Data SelectionKind Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectionKind -> c SelectionKind #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectionKind #

toConstr :: SelectionKind -> Constr #

dataTypeOf :: SelectionKind -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectionKind) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectionKind) #

gmapT :: (forall b. Data b => b -> b) -> SelectionKind -> SelectionKind #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectionKind -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectionKind -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectionKind -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectionKind -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectionKind -> m SelectionKind #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectionKind -> m SelectionKind #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectionKind -> m SelectionKind #

Enum SelectionKind Source # 
Instance details

Defined in Text.LLVM.AST

Generic SelectionKind Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep SelectionKind :: Type -> Type #

Show SelectionKind Source # 
Instance details

Defined in Text.LLVM.AST

Eq SelectionKind Source # 
Instance details

Defined in Text.LLVM.AST

Ord SelectionKind Source # 
Instance details

Defined in Text.LLVM.AST

type Rep SelectionKind Source # 
Instance details

Defined in Text.LLVM.AST

type Rep SelectionKind = D1 ('MetaData "SelectionKind" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((C1 ('MetaCons "ComdatAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ComdatExactMatch" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ComdatLargest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ComdatNoDuplicates" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ComdatSameSize" 'PrefixI 'False) (U1 :: Type -> Type))))

Identifiers

newtype Ident Source #

Constructors

Ident String 

Instances

Instances details
Data Ident Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident -> c Ident #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ident #

toConstr :: Ident -> Constr #

dataTypeOf :: Ident -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ident) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident) #

gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

IsString Ident Source # 
Instance details

Defined in Text.LLVM.AST

Methods

fromString :: String -> Ident #

Generic Ident Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

Show Ident Source # 
Instance details

Defined in Text.LLVM.AST

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Eq Ident Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Text.LLVM.AST

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 #

IsValue Ident Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Ident -> Value Source #

LLVMPretty Ident Source # 
Instance details

Defined in Text.LLVM.PP

Methods

llvmPP :: Fmt Ident Source #

Lift Ident Source # 
Instance details

Defined in Text.LLVM.AST

Methods

lift :: Quote m => Ident -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Ident -> Code m Ident #

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

type Rep Ident Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Ident = D1 ('MetaData "Ident" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'True) (C1 ('MetaCons "Ident" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Symbols

newtype Symbol Source #

Constructors

Symbol String 

Instances

Instances details
Data Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Symbol -> c Symbol #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Symbol #

toConstr :: Symbol -> Constr #

dataTypeOf :: Symbol -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Symbol) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Symbol) #

gmapT :: (forall b. Data b => b -> b) -> Symbol -> Symbol #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Symbol -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Symbol -> r #

gmapQ :: (forall d. Data d => d -> u) -> Symbol -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Symbol -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Symbol -> m Symbol #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Symbol -> m Symbol #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Symbol -> m Symbol #

IsString Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Methods

fromString :: String -> Symbol #

Monoid Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Semigroup Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Generic Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Symbol :: Type -> Type #

Methods

from :: Symbol -> Rep Symbol x #

to :: Rep Symbol x -> Symbol #

Show Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Eq Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord Symbol Source # 
Instance details

Defined in Text.LLVM.AST

IsValue Symbol Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Symbol -> Value Source #

LLVMPretty Symbol Source # 
Instance details

Defined in Text.LLVM.PP

Lift Symbol Source # 
Instance details

Defined in Text.LLVM.AST

Methods

lift :: Quote m => Symbol -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Symbol -> Code m Symbol #

type Rep Symbol Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Symbol = D1 ('MetaData "Symbol" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'True) (C1 ('MetaCons "Symbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Types

data PrimType Source #

Instances

Instances details
Data PrimType Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimType -> c PrimType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimType #

toConstr :: PrimType -> Constr #

dataTypeOf :: PrimType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimType) #

gmapT :: (forall b. Data b => b -> b) -> PrimType -> PrimType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrimType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimType -> m PrimType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimType -> m PrimType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimType -> m PrimType #

Generic PrimType Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep PrimType :: Type -> Type #

Methods

from :: PrimType -> Rep PrimType x #

to :: Rep PrimType x -> PrimType #

Show PrimType Source # 
Instance details

Defined in Text.LLVM.AST

Eq PrimType Source # 
Instance details

Defined in Text.LLVM.AST

Ord PrimType Source # 
Instance details

Defined in Text.LLVM.AST

Lift PrimType Source # 
Instance details

Defined in Text.LLVM.AST

Methods

lift :: Quote m => PrimType -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PrimType -> Code m PrimType #

type Rep PrimType Source # 
Instance details

Defined in Text.LLVM.AST

type Rep PrimType = D1 ('MetaData "PrimType" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((C1 ('MetaCons "Label" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Void" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Integer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))) :+: (C1 ('MetaCons "FloatType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FloatType)) :+: (C1 ('MetaCons "X86mmx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Metadata" 'PrefixI 'False) (U1 :: Type -> Type))))

data FloatType Source #

Instances

Instances details
Data FloatType Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloatType -> c FloatType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloatType #

toConstr :: FloatType -> Constr #

dataTypeOf :: FloatType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FloatType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloatType) #

gmapT :: (forall b. Data b => b -> b) -> FloatType -> FloatType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloatType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloatType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloatType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloatType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloatType -> m FloatType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloatType -> m FloatType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloatType -> m FloatType #

Enum FloatType Source # 
Instance details

Defined in Text.LLVM.AST

Generic FloatType Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep FloatType :: Type -> Type #

Show FloatType Source # 
Instance details

Defined in Text.LLVM.AST

Eq FloatType Source # 
Instance details

Defined in Text.LLVM.AST

Ord FloatType Source # 
Instance details

Defined in Text.LLVM.AST

Lift FloatType Source # 
Instance details

Defined in Text.LLVM.AST

Methods

lift :: Quote m => FloatType -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FloatType -> Code m FloatType #

type Rep FloatType Source # 
Instance details

Defined in Text.LLVM.AST

type Rep FloatType = D1 ('MetaData "FloatType" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((C1 ('MetaCons "Half" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Float" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Double" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Fp128" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "X86_fp80" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PPC_fp128" 'PrefixI 'False) (U1 :: Type -> Type))))

data Type' ident Source #

Constructors

PrimType PrimType 
Alias ident 
Array Word64 (Type' ident) 
FunTy (Type' ident) [Type' ident] Bool 
PtrTo (Type' ident)

A pointer to a memory location of a particular type. See also PtrOpaque, which represents a pointer without a pointee type.

LLVM pointers can also have an optional address space attribute, but this is not currently represented in the llvm-pretty AST.

PtrOpaque

A pointer to a memory location. Unlike PtrTo, a PtrOpaque does not have a pointee type. Instead, instructions interacting through opaque pointers specify the type of the underlying memory they are interacting with.

LLVM pointers can also have an optional address space attribute, but this is not currently represented in the llvm-pretty AST.

PtrOpaque should not be confused with Opaque, which is a completely separate type with a similar-sounding name.

Struct [Type' ident] 
PackedStruct [Type' ident] 
Vector Word64 (Type' ident) 
Opaque

An opaque structure type, used to represent structure types that do not have a body specified. This is similar to C's notion of a forward-declared structure.

Opaque should not be confused with PtrOpaque, which is a completely separate type with a similar-sounding name.

Instances

Instances details
Functor Type' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Generic1 Type' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 Type' :: k -> Type #

Methods

from1 :: forall (a :: k). Type' a -> Rep1 Type' a #

to1 :: forall (a :: k). Rep1 Type' a -> Type' a #

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

Defined in Text.LLVM

Methods

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

Data ident => Data (Type' ident) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type' ident -> c (Type' ident) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Type' ident) #

toConstr :: Type' ident -> Constr #

dataTypeOf :: Type' ident -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Type' ident)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Type' ident)) #

gmapT :: (forall b. Data b => b -> b) -> Type' ident -> Type' ident #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type' ident -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type' ident -> r #

gmapQ :: (forall d. Data d => d -> u) -> Type' ident -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Type' ident -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type' ident -> m (Type' ident) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type' ident -> m (Type' ident) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type' ident -> m (Type' ident) #

Generic (Type' ident) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: Type' ident -> String #

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

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

Defined in Text.LLVM.AST

Methods

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

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

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

Defined in Text.LLVM.AST

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 #

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

type Rep1 Type' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 Type' = D1 ('MetaData "Type'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (((C1 ('MetaCons "PrimType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType)) :+: C1 ('MetaCons "Alias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Type')) :+: (C1 ('MetaCons "FunTy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Type') :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (List :.: Rec1 Type') :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: C1 ('MetaCons "PtrTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Type'))))) :+: ((C1 ('MetaCons "PtrOpaque" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Struct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (List :.: Rec1 Type'))) :+: (C1 ('MetaCons "PackedStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (List :.: Rec1 Type')) :+: (C1 ('MetaCons "Vector" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Type')) :+: C1 ('MetaCons "Opaque" 'PrefixI 'False) (U1 :: Type -> Type)))))
type Rep (Type' ident) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (Type' ident) = D1 ('MetaData "Type'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (((C1 ('MetaCons "PrimType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType)) :+: C1 ('MetaCons "Alias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ident))) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type' ident))) :+: (C1 ('MetaCons "FunTy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type' ident)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type' ident]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: C1 ('MetaCons "PtrTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type' ident)))))) :+: ((C1 ('MetaCons "PtrOpaque" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Struct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type' ident]))) :+: (C1 ('MetaCons "PackedStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type' ident])) :+: (C1 ('MetaCons "Vector" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type' ident))) :+: C1 ('MetaCons "Opaque" 'PrefixI 'False) (U1 :: Type -> Type)))))

updateAliasesA :: Applicative f => (a -> f (Type' b)) -> Type' a -> f (Type' b) Source #

Applicatively traverse a type, updating or removing aliases.

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

Traverse a type, updating or removing aliases.

eqTypeModuloOpaquePtrs :: Eq ident => Type' ident -> Type' ident -> Bool Source #

Check two Types for equality, but treat PtrOpaque types as being equal to PtrTo ty types (for any type ty). This is a coarser notion of equality than what is provided by the Eq instance for Type.

cmpTypeModuloOpaquePtrs :: Ord ident => Type' ident -> Type' ident -> Ordering Source #

Compare two Types, but treat PtrOpaque types as being equal to PtrTo ty types (for any type ty). This is a coarser notion of ordering than what is provided by the Ord instance for Type.

fixupOpaquePtrs :: Data a => a -> a Source #

Ensure that if there are any occurrences of opaque pointers, then all non-opaque pointers are converted to opaque ones.

This is useful because LLVM tools like llvm-as are stricter than llvm-pretty in that the former forbids mixing opaque and non-opaque pointers, whereas the latter allows this. As a result, the result of pretty-printing an llvm-pretty AST might not be suitable for llvm-as's needs unless you first call this function to ensure that the two types of pointers are not intermixed.

This is implemented using Data.Data combinators under the hood, which could potentially require a full traversal of the AST. Because of the performance implications of this, we do not call fixupOpaquePtrs in llvm-pretty's pretty-printer. If you wish to combine opaque and non-opaque pointers in your AST, the burden is on you to call this function before pretty-printing.

Null values

data NullResult lab Source #

Constructors

HasNull (Value' lab) 
ResolveNull Ident 

Instances

Instances details
Functor NullResult Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Generic1 NullResult Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 NullResult :: k -> Type #

Methods

from1 :: forall (a :: k). NullResult a -> Rep1 NullResult a #

to1 :: forall (a :: k). Rep1 NullResult a -> NullResult a #

Data lab => Data (NullResult lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NullResult lab -> c (NullResult lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NullResult lab) #

toConstr :: NullResult lab -> Constr #

dataTypeOf :: NullResult lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NullResult lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NullResult lab)) #

gmapT :: (forall b. Data b => b -> b) -> NullResult lab -> NullResult lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NullResult lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NullResult lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> NullResult lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NullResult lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NullResult lab -> m (NullResult lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NullResult lab -> m (NullResult lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NullResult lab -> m (NullResult lab) #

Generic (NullResult lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (NullResult lab) :: Type -> Type #

Methods

from :: NullResult lab -> Rep (NullResult lab) x #

to :: Rep (NullResult lab) x -> NullResult lab #

Show lab => Show (NullResult lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

showsPrec :: Int -> NullResult lab -> ShowS #

show :: NullResult lab -> String #

showList :: [NullResult lab] -> ShowS #

Eq lab => Eq (NullResult lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: NullResult lab -> NullResult lab -> Bool #

(/=) :: NullResult lab -> NullResult lab -> Bool #

Ord lab => Ord (NullResult lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: NullResult lab -> NullResult lab -> Ordering #

(<) :: NullResult lab -> NullResult lab -> Bool #

(<=) :: NullResult lab -> NullResult lab -> Bool #

(>) :: NullResult lab -> NullResult lab -> Bool #

(>=) :: NullResult lab -> NullResult lab -> Bool #

max :: NullResult lab -> NullResult lab -> NullResult lab #

min :: NullResult lab -> NullResult lab -> NullResult lab #

type Rep1 NullResult Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 NullResult = D1 ('MetaData "NullResult" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "HasNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Value')) :+: C1 ('MetaCons "ResolveNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)))
type Rep (NullResult lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (NullResult lab) = D1 ('MetaData "NullResult" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "HasNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Value' lab))) :+: C1 ('MetaCons "ResolveNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)))

Type Elimination

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

Eliminator for array, pointer and vector types.

Top-level Type Aliases

data TypeDecl Source #

Constructors

TypeDecl 

Fields

Instances

Instances details
Data TypeDecl Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeDecl -> c TypeDecl #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeDecl #

toConstr :: TypeDecl -> Constr #

dataTypeOf :: TypeDecl -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeDecl) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeDecl) #

gmapT :: (forall b. Data b => b -> b) -> TypeDecl -> TypeDecl #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeDecl -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeDecl -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypeDecl -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeDecl -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeDecl -> m TypeDecl #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDecl -> m TypeDecl #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDecl -> m TypeDecl #

Generic TypeDecl Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep TypeDecl :: Type -> Type #

Methods

from :: TypeDecl -> Rep TypeDecl x #

to :: Rep TypeDecl x -> TypeDecl #

Show TypeDecl Source # 
Instance details

Defined in Text.LLVM.AST

Eq TypeDecl Source # 
Instance details

Defined in Text.LLVM.AST

Ord TypeDecl Source # 
Instance details

Defined in Text.LLVM.AST

type Rep TypeDecl Source # 
Instance details

Defined in Text.LLVM.AST

type Rep TypeDecl = D1 ('MetaData "TypeDecl" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "TypeDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "typeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Just "typeValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))

Globals

data Global Source #

Instances

Instances details
Data Global Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Global -> c Global #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Global #

toConstr :: Global -> Constr #

dataTypeOf :: Global -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Global) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Global) #

gmapT :: (forall b. Data b => b -> b) -> Global -> Global #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Global -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Global -> r #

gmapQ :: (forall d. Data d => d -> u) -> Global -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Global -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Global -> m Global #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Global -> m Global #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Global -> m Global #

Generic Global Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Global :: Type -> Type #

Methods

from :: Global -> Rep Global x #

to :: Rep Global x -> Global #

Show Global Source # 
Instance details

Defined in Text.LLVM.AST

Eq Global Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord Global Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Global Source # 
Instance details

Defined in Text.LLVM.AST

data GlobalAttrs Source #

Instances

Instances details
Data GlobalAttrs Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalAttrs -> c GlobalAttrs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalAttrs #

toConstr :: GlobalAttrs -> Constr #

dataTypeOf :: GlobalAttrs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GlobalAttrs) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalAttrs) #

gmapT :: (forall b. Data b => b -> b) -> GlobalAttrs -> GlobalAttrs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalAttrs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalAttrs -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalAttrs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalAttrs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalAttrs -> m GlobalAttrs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalAttrs -> m GlobalAttrs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalAttrs -> m GlobalAttrs #

Generic GlobalAttrs Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep GlobalAttrs :: Type -> Type #

Show GlobalAttrs Source # 
Instance details

Defined in Text.LLVM.AST

Eq GlobalAttrs Source # 
Instance details

Defined in Text.LLVM.AST

Ord GlobalAttrs Source # 
Instance details

Defined in Text.LLVM.AST

type Rep GlobalAttrs Source # 
Instance details

Defined in Text.LLVM.AST

type Rep GlobalAttrs = D1 ('MetaData "GlobalAttrs" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "GlobalAttrs" 'PrefixI 'True) (S1 ('MetaSel ('Just "gaLinkage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Linkage)) :*: (S1 ('MetaSel ('Just "gaVisibility") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Visibility)) :*: S1 ('MetaSel ('Just "gaConstant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

Declarations

data Declare Source #

Instances

Instances details
Data Declare Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Declare -> c Declare #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Declare #

toConstr :: Declare -> Constr #

dataTypeOf :: Declare -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Declare) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Declare) #

gmapT :: (forall b. Data b => b -> b) -> Declare -> Declare #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Declare -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Declare -> r #

gmapQ :: (forall d. Data d => d -> u) -> Declare -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Declare -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Declare -> m Declare #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Declare -> m Declare #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Declare -> m Declare #

Generic Declare Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Declare :: Type -> Type #

Methods

from :: Declare -> Rep Declare x #

to :: Rep Declare x -> Declare #

Show Declare Source # 
Instance details

Defined in Text.LLVM.AST

Eq Declare Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord Declare Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Declare Source # 
Instance details

Defined in Text.LLVM.AST

decFunType :: Declare -> Type Source #

The function type of this declaration

Function Definitions

data Define Source #

Instances

Instances details
Data Define Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Define -> c Define #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Define #

toConstr :: Define -> Constr #

dataTypeOf :: Define -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Define) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Define) #

gmapT :: (forall b. Data b => b -> b) -> Define -> Define #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Define -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Define -> r #

gmapQ :: (forall d. Data d => d -> u) -> Define -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Define -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Define -> m Define #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Define -> m Define #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Define -> m Define #

Generic Define Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Define :: Type -> Type #

Methods

from :: Define -> Rep Define x #

to :: Rep Define x -> Define #

Show Define Source # 
Instance details

Defined in Text.LLVM.AST

Eq Define Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord Define Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Define Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Define = D1 ('MetaData "Define" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "Define" 'PrefixI 'True) (((S1 ('MetaSel ('Just "defLinkage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Linkage)) :*: (S1 ('MetaSel ('Just "defVisibility") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Visibility)) :*: S1 ('MetaSel ('Just "defRetType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Just "defName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Symbol) :*: (S1 ('MetaSel ('Just "defArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Typed Ident]) :*: S1 ('MetaSel ('Just "defVarArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "defAttrs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunAttr]) :*: (S1 ('MetaSel ('Just "defSection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "defGC") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GC)))) :*: (S1 ('MetaSel ('Just "defBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BasicBlock]) :*: (S1 ('MetaSel ('Just "defMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FnMdAttachments) :*: S1 ('MetaSel ('Just "defComdat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))))

Function Attributes and attribute groups

data FunAttr Source #

Instances

Instances details
Data FunAttr Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunAttr -> c FunAttr #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunAttr #

toConstr :: FunAttr -> Constr #

dataTypeOf :: FunAttr -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunAttr) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunAttr) #

gmapT :: (forall b. Data b => b -> b) -> FunAttr -> FunAttr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunAttr -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunAttr -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunAttr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunAttr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunAttr -> m FunAttr #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunAttr -> m FunAttr #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunAttr -> m FunAttr #

Generic FunAttr Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep FunAttr :: Type -> Type #

Methods

from :: FunAttr -> Rep FunAttr x #

to :: Rep FunAttr x -> FunAttr #

Show FunAttr Source # 
Instance details

Defined in Text.LLVM.AST

Eq FunAttr Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord FunAttr Source # 
Instance details

Defined in Text.LLVM.AST

type Rep FunAttr Source # 
Instance details

Defined in Text.LLVM.AST

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

Basic Block Labels

data BlockLabel Source #

Constructors

Named Ident 
Anon Int 

Instances

Instances details
Data BlockLabel Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockLabel -> c BlockLabel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BlockLabel #

toConstr :: BlockLabel -> Constr #

dataTypeOf :: BlockLabel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BlockLabel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BlockLabel) #

gmapT :: (forall b. Data b => b -> b) -> BlockLabel -> BlockLabel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockLabel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockLabel -> r #

gmapQ :: (forall d. Data d => d -> u) -> BlockLabel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockLabel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockLabel -> m BlockLabel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockLabel -> m BlockLabel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockLabel -> m BlockLabel #

IsString BlockLabel Source # 
Instance details

Defined in Text.LLVM.AST

Generic BlockLabel Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep BlockLabel :: Type -> Type #

Show BlockLabel Source # 
Instance details

Defined in Text.LLVM.AST

Eq BlockLabel Source # 
Instance details

Defined in Text.LLVM.AST

Ord BlockLabel Source # 
Instance details

Defined in Text.LLVM.AST

IsValue Value Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Value -> Value Source #

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

type Rep BlockLabel Source # 
Instance details

Defined in Text.LLVM.AST

type Rep BlockLabel = D1 ('MetaData "BlockLabel" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "Named" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "Anon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Basic Blocks

data BasicBlock' lab Source #

Constructors

BasicBlock 

Fields

Instances

Instances details
Functor BasicBlock' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Generic1 BasicBlock' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 BasicBlock' :: k -> Type #

Methods

from1 :: forall (a :: k). BasicBlock' a -> Rep1 BasicBlock' a #

to1 :: forall (a :: k). Rep1 BasicBlock' a -> BasicBlock' a #

Data lab => Data (BasicBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicBlock' lab -> c (BasicBlock' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BasicBlock' lab) #

toConstr :: BasicBlock' lab -> Constr #

dataTypeOf :: BasicBlock' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BasicBlock' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BasicBlock' lab)) #

gmapT :: (forall b. Data b => b -> b) -> BasicBlock' lab -> BasicBlock' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicBlock' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicBlock' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicBlock' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicBlock' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicBlock' lab -> m (BasicBlock' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicBlock' lab -> m (BasicBlock' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicBlock' lab -> m (BasicBlock' lab) #

Generic (BasicBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: BasicBlock' lab -> String #

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

Eq lab => Eq (BasicBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: BasicBlock' lab -> BasicBlock' lab -> Bool #

(/=) :: BasicBlock' lab -> BasicBlock' lab -> Bool #

Ord lab => Ord (BasicBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: BasicBlock' lab -> BasicBlock' lab -> Ordering #

(<) :: BasicBlock' lab -> BasicBlock' lab -> Bool #

(<=) :: BasicBlock' lab -> BasicBlock' lab -> Bool #

(>) :: BasicBlock' lab -> BasicBlock' lab -> Bool #

(>=) :: BasicBlock' lab -> BasicBlock' lab -> Bool #

max :: BasicBlock' lab -> BasicBlock' lab -> BasicBlock' lab #

min :: BasicBlock' lab -> BasicBlock' lab -> BasicBlock' lab #

type Rep1 BasicBlock' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 BasicBlock' = D1 ('MetaData "BasicBlock'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "BasicBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "bbLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe) :*: S1 ('MetaSel ('Just "bbStmts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (List :.: Rec1 Stmt')))
type Rep (BasicBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

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

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

Attributes

data Linkage Source #

Symbol Linkage

Instances

Instances details
Data Linkage Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Linkage -> c Linkage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Linkage #

toConstr :: Linkage -> Constr #

dataTypeOf :: Linkage -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Linkage) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Linkage) #

gmapT :: (forall b. Data b => b -> b) -> Linkage -> Linkage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Linkage -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Linkage -> r #

gmapQ :: (forall d. Data d => d -> u) -> Linkage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Linkage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Linkage -> m Linkage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Linkage -> m Linkage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Linkage -> m Linkage #

Enum Linkage Source # 
Instance details

Defined in Text.LLVM.AST

Generic Linkage Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Linkage :: Type -> Type #

Methods

from :: Linkage -> Rep Linkage x #

to :: Rep Linkage x -> Linkage #

Show Linkage Source # 
Instance details

Defined in Text.LLVM.AST

Eq Linkage Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord Linkage Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Linkage Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Linkage = D1 ('MetaData "Linkage" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((((C1 ('MetaCons "Private" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinkerPrivate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LinkerPrivateWeak" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinkerPrivateWeakDefAuto" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Internal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AvailableExternally" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Linkonce" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Weak" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Common" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Appending" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExternWeak" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinkonceODR" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WeakODR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "External" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DLLImport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DLLExport" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Visibility Source #

Instances

Instances details
Data Visibility Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Visibility -> c Visibility #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Visibility #

toConstr :: Visibility -> Constr #

dataTypeOf :: Visibility -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Visibility) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visibility) #

gmapT :: (forall b. Data b => b -> b) -> Visibility -> Visibility #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Visibility -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Visibility -> r #

gmapQ :: (forall d. Data d => d -> u) -> Visibility -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Visibility -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

Generic Visibility Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Visibility :: Type -> Type #

Show Visibility Source # 
Instance details

Defined in Text.LLVM.AST

Eq Visibility Source # 
Instance details

Defined in Text.LLVM.AST

Ord Visibility Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Visibility Source # 
Instance details

Defined in Text.LLVM.AST

type Rep Visibility = D1 ('MetaData "Visibility" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DefaultVisibility" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HiddenVisibility" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProtectedVisibility" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype GC Source #

Constructors

GC 

Fields

Instances

Instances details
Data GC Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GC -> c GC #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GC #

toConstr :: GC -> Constr #

dataTypeOf :: GC -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GC) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GC) #

gmapT :: (forall b. Data b => b -> b) -> GC -> GC #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GC -> r #

gmapQ :: (forall d. Data d => d -> u) -> GC -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GC -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GC -> m GC #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GC -> m GC #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GC -> m GC #

Generic GC Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep GC :: Type -> Type #

Methods

from :: GC -> Rep GC x #

to :: Rep GC x -> GC #

Show GC Source # 
Instance details

Defined in Text.LLVM.AST

Methods

showsPrec :: Int -> GC -> ShowS #

show :: GC -> String #

showList :: [GC] -> ShowS #

Eq GC Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord GC Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: GC -> GC -> Ordering #

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

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

(>) :: GC -> GC -> Bool #

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

max :: GC -> GC -> GC #

min :: GC -> GC -> GC #

type Rep GC Source # 
Instance details

Defined in Text.LLVM.AST

type Rep GC = D1 ('MetaData "GC" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'True) (C1 ('MetaCons "GC" 'PrefixI 'True) (S1 ('MetaSel ('Just "getGC") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Typed Things

data Typed a Source #

Constructors

Typed 

Fields

Instances

Instances details
Foldable Typed Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

foldMap :: Monoid m => (a -> m) -> Typed a -> 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 # 
Instance details

Defined in Text.LLVM.AST

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) #

Functor Typed Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Generic1 Typed Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 Typed :: k -> Type #

Methods

from1 :: forall (a :: k). Typed a -> Rep1 Typed a #

to1 :: forall (a :: k). Rep1 Typed a -> Typed a #

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

Defined in Text.LLVM

Methods

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

Data a => Data (Typed a) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Typed a -> c (Typed a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Typed a) #

toConstr :: Typed a -> Constr #

dataTypeOf :: Typed a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Typed a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Typed a)) #

gmapT :: (forall b. Data b => b -> b) -> Typed a -> Typed a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typed a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Typed a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Typed a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Typed a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Typed a -> m (Typed a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Typed a -> m (Typed a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Typed a -> m (Typed a) #

Generic (Typed a) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

Show a => Show (Typed a) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

show :: Typed a -> String #

showList :: [Typed a] -> ShowS #

Eq a => Eq (Typed a) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: Typed a -> Typed a -> Bool #

(/=) :: Typed a -> Typed a -> Bool #

Ord a => Ord (Typed a) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: Typed a -> Typed a -> Ordering #

(<) :: Typed a -> Typed a -> Bool #

(<=) :: Typed a -> Typed a -> Bool #

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

(>=) :: Typed a -> Typed a -> Bool #

max :: Typed a -> Typed a -> Typed a #

min :: Typed a -> Typed a -> Typed a #

IsValue a => IsValue (Typed a) Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Typed a -> Value Source #

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

type Rep1 Typed Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 Typed = D1 ('MetaData "Typed" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "Typed" 'PrefixI 'True) (S1 ('MetaSel ('Just "typedType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Just "typedValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (Typed a) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (Typed a) = D1 ('MetaData "Typed" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "Typed" 'PrefixI 'True) (S1 ('MetaSel ('Just "typedType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Just "typedValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

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

Instructions

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

Instances details
Data ArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithOp -> c ArithOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArithOp #

toConstr :: ArithOp -> Constr #

dataTypeOf :: ArithOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArithOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArithOp) #

gmapT :: (forall b. Data b => b -> b) -> ArithOp -> ArithOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArithOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithOp -> m ArithOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithOp -> m ArithOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithOp -> m ArithOp #

Generic ArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep ArithOp :: Type -> Type #

Methods

from :: ArithOp -> Rep ArithOp x #

to :: Rep ArithOp x -> ArithOp #

Show ArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Eq ArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord ArithOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep ArithOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep ArithOp = D1 ('MetaData "ArithOp" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (((C1 ('MetaCons "Add" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "FAdd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sub" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: (C1 ('MetaCons "FSub" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Mul" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "FMul" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "UDiv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "SDiv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "FDiv" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "URem" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SRem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FRem" 'PrefixI 'False) (U1 :: Type -> Type)))))

data UnaryArithOp Source #

Constructors

FNeg

Floating point negation.

Instances

Instances details
Data UnaryArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnaryArithOp -> c UnaryArithOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnaryArithOp #

toConstr :: UnaryArithOp -> Constr #

dataTypeOf :: UnaryArithOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnaryArithOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnaryArithOp) #

gmapT :: (forall b. Data b => b -> b) -> UnaryArithOp -> UnaryArithOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnaryArithOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnaryArithOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> UnaryArithOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnaryArithOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnaryArithOp -> m UnaryArithOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryArithOp -> m UnaryArithOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryArithOp -> m UnaryArithOp #

Generic UnaryArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep UnaryArithOp :: Type -> Type #

Show UnaryArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Eq UnaryArithOp Source # 
Instance details

Defined in Text.LLVM.AST

Ord UnaryArithOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep UnaryArithOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep UnaryArithOp = D1 ('MetaData "UnaryArithOp" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "FNeg" 'PrefixI 'False) (U1 :: Type -> Type))

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 

Instances

Instances details
Data BitOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitOp -> c BitOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BitOp #

toConstr :: BitOp -> Constr #

dataTypeOf :: BitOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BitOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BitOp) #

gmapT :: (forall b. Data b => b -> b) -> BitOp -> BitOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitOp -> m BitOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitOp -> m BitOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitOp -> m BitOp #

Generic BitOp Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep BitOp :: Type -> Type #

Methods

from :: BitOp -> Rep BitOp x #

to :: Rep BitOp x -> BitOp #

Show BitOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

showsPrec :: Int -> BitOp -> ShowS #

show :: BitOp -> String #

showList :: [BitOp] -> ShowS #

Eq BitOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord BitOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: BitOp -> BitOp -> Ordering #

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

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

(>) :: BitOp -> BitOp -> Bool #

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

max :: BitOp -> BitOp -> BitOp #

min :: BitOp -> BitOp -> BitOp #

type Rep BitOp Source # 
Instance details

Defined in Text.LLVM.AST

data ConvOp Source #

Conversions from one type to another.

Instances

Instances details
Data ConvOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConvOp -> c ConvOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConvOp #

toConstr :: ConvOp -> Constr #

dataTypeOf :: ConvOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConvOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConvOp) #

gmapT :: (forall b. Data b => b -> b) -> ConvOp -> ConvOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConvOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConvOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConvOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConvOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConvOp -> m ConvOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConvOp -> m ConvOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConvOp -> m ConvOp #

Enum ConvOp Source # 
Instance details

Defined in Text.LLVM.AST

Generic ConvOp Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep ConvOp :: Type -> Type #

Methods

from :: ConvOp -> Rep ConvOp x #

to :: Rep ConvOp x -> ConvOp #

Show ConvOp Source # 
Instance details

Defined in Text.LLVM.AST

Eq ConvOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord ConvOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep ConvOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep ConvOp = D1 ('MetaData "ConvOp" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (((C1 ('MetaCons "Trunc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZExt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SExt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "FpTrunc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FpExt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FpToUi" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "FpToSi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UiToFp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SiToFp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PtrToInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IntToPtr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BitCast" 'PrefixI 'False) (U1 :: Type -> Type)))))

data AtomicRWOp Source #

Instances

Instances details
Data AtomicRWOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AtomicRWOp -> c AtomicRWOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AtomicRWOp #

toConstr :: AtomicRWOp -> Constr #

dataTypeOf :: AtomicRWOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AtomicRWOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AtomicRWOp) #

gmapT :: (forall b. Data b => b -> b) -> AtomicRWOp -> AtomicRWOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AtomicRWOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AtomicRWOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> AtomicRWOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AtomicRWOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AtomicRWOp -> m AtomicRWOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AtomicRWOp -> m AtomicRWOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AtomicRWOp -> m AtomicRWOp #

Enum AtomicRWOp Source # 
Instance details

Defined in Text.LLVM.AST

Generic AtomicRWOp Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep AtomicRWOp :: Type -> Type #

Show AtomicRWOp Source # 
Instance details

Defined in Text.LLVM.AST

Eq AtomicRWOp Source # 
Instance details

Defined in Text.LLVM.AST

Ord AtomicRWOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep AtomicRWOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep AtomicRWOp = D1 ('MetaData "AtomicRWOp" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (((C1 ('MetaCons "AtomicXchg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AtomicAdd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AtomicSub" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AtomicAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AtomicNand" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AtomicOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AtomicXor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AtomicMax" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "AtomicMin" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AtomicUMax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AtomicUMin" 'PrefixI 'False) (U1 :: Type -> Type)))))

data AtomicOrdering Source #

Instances

Instances details
Data AtomicOrdering Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AtomicOrdering -> c AtomicOrdering #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AtomicOrdering #

toConstr :: AtomicOrdering -> Constr #

dataTypeOf :: AtomicOrdering -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AtomicOrdering) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AtomicOrdering) #

gmapT :: (forall b. Data b => b -> b) -> AtomicOrdering -> AtomicOrdering #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AtomicOrdering -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AtomicOrdering -> r #

gmapQ :: (forall d. Data d => d -> u) -> AtomicOrdering -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AtomicOrdering -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AtomicOrdering -> m AtomicOrdering #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AtomicOrdering -> m AtomicOrdering #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AtomicOrdering -> m AtomicOrdering #

Enum AtomicOrdering Source # 
Instance details

Defined in Text.LLVM.AST

Generic AtomicOrdering Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep AtomicOrdering :: Type -> Type #

Show AtomicOrdering Source # 
Instance details

Defined in Text.LLVM.AST

Eq AtomicOrdering Source # 
Instance details

Defined in Text.LLVM.AST

Ord AtomicOrdering Source # 
Instance details

Defined in Text.LLVM.AST

type Rep AtomicOrdering Source # 
Instance details

Defined in Text.LLVM.AST

type Rep AtomicOrdering = D1 ('MetaData "AtomicOrdering" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((C1 ('MetaCons "Unordered" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Monotonic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Acquire" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Release" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AcqRel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SeqCst" 'PrefixI 'False) (U1 :: Type -> Type))))

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.
UnaryArith UnaryArithOp (Typed (Value' lab))
  • Unary arithmetic operation.
  • Middle of basic block.
  • The result is the same as the parameter.
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.
CallBr Type (Value' lab) [Typed (Value' lab)] lab [lab]
  • Call a function in asm-goto style: return type; function operand; arguments; default basic block destination; other basic block destinations.
  • Middle of basic block.
  • The result is as indicated by the provided type.
  • Introduced in LLVM 9.
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 Type (Typed (Value' lab)) (Maybe AtomicOrdering) (Maybe Align)
  • Read a value from the given address: type being loaded; address to read from; atomic ordering; 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 AtomicOrdering) (Maybe Align)
  • Write a value to memory: value to store; pointer to location where to store; atomic ordering; assumptions about the alignment of the given pointer.
  • Middle of basic block.
  • Effect.
Fence (Maybe String) AtomicOrdering
  • Introduce a happens-before relationship between operations: synchronization scope; type of ordering.
  • Middle of basic block.
CmpXchg Bool Bool (Typed (Value' lab)) (Typed (Value' lab)) (Typed (Value' lab)) (Maybe String) AtomicOrdering AtomicOrdering
  • Atomically compare and maybe exchange values in memory: whether the exchange is weak; whether the exchange is volatile; pointer to read; value to compare it with; new value to write if the two prior values are equal; synchronization scope; synchronization ordering on success; synchronization ordering on failure.
  • Returns a pair of the original value and whether an exchange occurred.
  • Middle of basic block.
  • Effect.
AtomicRW Bool AtomicRWOp (Typed (Value' lab)) (Typed (Value' lab)) (Maybe String) AtomicOrdering
  • Perform an atomic load, operation, and store: whether the operation is volatile; operation to apply to the read value and the provided value; pointer to read; value to combine it with, using the given operation; synchronization scope; synchronization ordering.
  • Returns the original value at the given location.
  • 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 Type (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); type to use as a basis for calculations; pointer to parent structure; path to a sub-component of a structure.
  • Middle of basic block.
  • Returns the address of the requested member.

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

The indexes are in units of 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 (Maybe (Typed (Value' lab))) Bool [Clause' lab] 
Resume (Typed (Value' lab)) 
Freeze (Typed (Value' lab))
  • Used to stop propagation of undef and poison values.
  • Middle of basic block.

Instances

Instances details
Functor Instr' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel Instr' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Data lab => Data (Instr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Instr' lab -> c (Instr' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Instr' lab) #

toConstr :: Instr' lab -> Constr #

dataTypeOf :: Instr' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Instr' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Instr' lab)) #

gmapT :: (forall b. Data b => b -> b) -> Instr' lab -> Instr' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Instr' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Instr' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> Instr' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Instr' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Instr' lab -> m (Instr' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Instr' lab -> m (Instr' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Instr' lab -> m (Instr' lab) #

Generic (Instr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: Instr' lab -> String #

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

Eq lab => Eq (Instr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: Instr' lab -> Instr' lab -> Bool #

(/=) :: Instr' lab -> Instr' lab -> Bool #

Ord lab => Ord (Instr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: Instr' lab -> Instr' lab -> Ordering #

(<) :: Instr' lab -> Instr' lab -> Bool #

(<=) :: Instr' lab -> Instr' lab -> Bool #

(>) :: Instr' lab -> Instr' lab -> Bool #

(>=) :: Instr' lab -> Instr' lab -> Bool #

max :: Instr' lab -> Instr' lab -> Instr' lab #

min :: Instr' lab -> Instr' lab -> Instr' lab #

type Rep (Instr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

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

data Clause' lab Source #

Constructors

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

Instances

Instances details
Functor Clause' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel Clause' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 Clause' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 Clause' :: k -> Type #

Methods

from1 :: forall (a :: k). Clause' a -> Rep1 Clause' a #

to1 :: forall (a :: k). Rep1 Clause' a -> Clause' a #

Data lab => Data (Clause' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Clause' lab -> c (Clause' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Clause' lab) #

toConstr :: Clause' lab -> Constr #

dataTypeOf :: Clause' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Clause' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Clause' lab)) #

gmapT :: (forall b. Data b => b -> b) -> Clause' lab -> Clause' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Clause' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Clause' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> Clause' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Clause' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Clause' lab -> m (Clause' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause' lab -> m (Clause' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause' lab -> m (Clause' lab) #

Generic (Clause' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: Clause' lab -> String #

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

Eq lab => Eq (Clause' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: Clause' lab -> Clause' lab -> Bool #

(/=) :: Clause' lab -> Clause' lab -> Bool #

Ord lab => Ord (Clause' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: Clause' lab -> Clause' lab -> Ordering #

(<) :: Clause' lab -> Clause' lab -> Bool #

(<=) :: Clause' lab -> Clause' lab -> Bool #

(>) :: Clause' lab -> Clause' lab -> Bool #

(>=) :: Clause' lab -> Clause' lab -> Bool #

max :: Clause' lab -> Clause' lab -> Clause' lab #

min :: Clause' lab -> Clause' lab -> Clause' lab #

type Rep1 Clause' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 Clause' = D1 ('MetaData "Clause'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "Catch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Typed :.: Rec1 Value')) :+: C1 ('MetaCons "Filter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Typed :.: Rec1 Value')))
type Rep (Clause' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (Clause' lab) = D1 ('MetaData "Clause'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "Catch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Typed (Value' lab)))) :+: C1 ('MetaCons "Filter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Data ICmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ICmpOp -> c ICmpOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ICmpOp #

toConstr :: ICmpOp -> Constr #

dataTypeOf :: ICmpOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ICmpOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ICmpOp) #

gmapT :: (forall b. Data b => b -> b) -> ICmpOp -> ICmpOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ICmpOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ICmpOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ICmpOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ICmpOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ICmpOp -> m ICmpOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ICmpOp -> m ICmpOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ICmpOp -> m ICmpOp #

Enum ICmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Generic ICmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep ICmpOp :: Type -> Type #

Methods

from :: ICmpOp -> Rep ICmpOp x #

to :: Rep ICmpOp x -> ICmpOp #

Show ICmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Eq ICmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord ICmpOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep ICmpOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep ICmpOp = D1 ('MetaData "ICmpOp" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (((C1 ('MetaCons "Ieq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ine" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Iugt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Iuge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Iult" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Iule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Isgt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Isge" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Islt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Isle" 'PrefixI 'False) (U1 :: Type -> Type)))))

data FCmpOp Source #

Floating-point comparison operators.

Instances

Instances details
Data FCmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FCmpOp -> c FCmpOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FCmpOp #

toConstr :: FCmpOp -> Constr #

dataTypeOf :: FCmpOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FCmpOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FCmpOp) #

gmapT :: (forall b. Data b => b -> b) -> FCmpOp -> FCmpOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FCmpOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FCmpOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> FCmpOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FCmpOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FCmpOp -> m FCmpOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FCmpOp -> m FCmpOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FCmpOp -> m FCmpOp #

Enum FCmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Generic FCmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep FCmpOp :: Type -> Type #

Methods

from :: FCmpOp -> Rep FCmpOp x #

to :: Rep FCmpOp x -> FCmpOp #

Show FCmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Eq FCmpOp Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord FCmpOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep FCmpOp Source # 
Instance details

Defined in Text.LLVM.AST

type Rep FCmpOp = D1 ('MetaData "FCmpOp" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((((C1 ('MetaCons "Ffalse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Foeq" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fogt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Foge" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Folt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fole" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ford" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Fueq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fugt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fuge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fult" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Fule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fune" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Funo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ftrue" 'PrefixI 'False) (U1 :: Type -> Type)))))

Values

data Value' lab Source #

Instances

Instances details
Functor Value' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

IsValue Value Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Value -> Value Source #

HasLabel Value' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 Value' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 Value' :: k -> Type #

Methods

from1 :: forall (a :: k). Value' a -> Rep1 Value' a #

to1 :: forall (a :: k). Rep1 Value' a -> Value' a #

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

Defined in Text.LLVM

Methods

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

Data lab => Data (Value' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value' lab -> c (Value' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Value' lab) #

toConstr :: Value' lab -> Constr #

dataTypeOf :: Value' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Value' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Value' lab)) #

gmapT :: (forall b. Data b => b -> b) -> Value' lab -> Value' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value' lab -> m (Value' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value' lab -> m (Value' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value' lab -> m (Value' lab) #

Generic (Value' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: Value' lab -> String #

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

Eq lab => Eq (Value' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: Value' lab -> Value' lab -> Bool #

(/=) :: Value' lab -> Value' lab -> Bool #

Ord lab => Ord (Value' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: Value' lab -> Value' lab -> Ordering #

(<) :: Value' lab -> Value' lab -> Bool #

(<=) :: Value' lab -> Value' lab -> Bool #

(>) :: Value' lab -> Value' lab -> Bool #

(>=) :: Value' lab -> Value' lab -> Bool #

max :: Value' lab -> Value' lab -> Value' lab #

min :: Value' lab -> Value' lab -> Value' lab #

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

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

Defined in Text.LLVM

Methods

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

type Rep1 Value' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

type Rep (Value' lab) = D1 ('MetaData "Value'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((((C1 ('MetaCons "ValInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "ValBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "ValFloat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: (C1 ('MetaCons "ValDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "ValFP80" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FP80Value))))) :+: ((C1 ('MetaCons "ValIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "ValSymbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Symbol))) :+: (C1 ('MetaCons "ValNull" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ValArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value' lab])) :+: C1 ('MetaCons "ValVector" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Value' lab])))))) :+: (((C1 ('MetaCons "ValStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Typed (Value' lab)])) :+: C1 ('MetaCons "ValPackedStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Typed (Value' lab)]))) :+: (C1 ('MetaCons "ValString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word8])) :+: (C1 ('MetaCons "ValConstExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConstExpr' lab))) :+: C1 ('MetaCons "ValUndef" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ValLabel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 lab)) :+: C1 ('MetaCons "ValZeroInit" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ValAsm" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "ValMd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValMd' lab))) :+: C1 ('MetaCons "ValPoison" 'PrefixI 'False) (U1 :: Type -> Type))))))

data FP80Value Source #

Instances

Instances details
Data FP80Value Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FP80Value -> c FP80Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FP80Value #

toConstr :: FP80Value -> Constr #

dataTypeOf :: FP80Value -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FP80Value) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FP80Value) #

gmapT :: (forall b. Data b => b -> b) -> FP80Value -> FP80Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FP80Value -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FP80Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> FP80Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FP80Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FP80Value -> m FP80Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FP80Value -> m FP80Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FP80Value -> m FP80Value #

Generic FP80Value Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep FP80Value :: Type -> Type #

Show FP80Value Source # 
Instance details

Defined in Text.LLVM.AST

Eq FP80Value Source # 
Instance details

Defined in Text.LLVM.AST

Ord FP80Value Source # 
Instance details

Defined in Text.LLVM.AST

type Rep FP80Value Source # 
Instance details

Defined in Text.LLVM.AST

type Rep FP80Value = D1 ('MetaData "FP80Value" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "FP80_LongDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

data ValMd' lab Source #

Instances

Instances details
Functor ValMd' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel ValMd' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 ValMd' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 ValMd' :: k -> Type #

Methods

from1 :: forall (a :: k). ValMd' a -> Rep1 ValMd' a #

to1 :: forall (a :: k). Rep1 ValMd' a -> ValMd' a #

Data lab => Data (ValMd' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ValMd' lab -> c (ValMd' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ValMd' lab) #

toConstr :: ValMd' lab -> Constr #

dataTypeOf :: ValMd' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ValMd' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ValMd' lab)) #

gmapT :: (forall b. Data b => b -> b) -> ValMd' lab -> ValMd' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ValMd' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ValMd' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> ValMd' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ValMd' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ValMd' lab -> m (ValMd' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ValMd' lab -> m (ValMd' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ValMd' lab -> m (ValMd' lab) #

Generic (ValMd' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: ValMd' lab -> String #

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

Eq lab => Eq (ValMd' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: ValMd' lab -> ValMd' lab -> Bool #

(/=) :: ValMd' lab -> ValMd' lab -> Bool #

Ord lab => Ord (ValMd' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: ValMd' lab -> ValMd' lab -> Ordering #

(<) :: ValMd' lab -> ValMd' lab -> Bool #

(<=) :: ValMd' lab -> ValMd' lab -> Bool #

(>) :: ValMd' lab -> ValMd' lab -> Bool #

(>=) :: ValMd' lab -> ValMd' lab -> Bool #

max :: ValMd' lab -> ValMd' lab -> ValMd' lab #

min :: ValMd' lab -> ValMd' lab -> ValMd' lab #

type Rep1 ValMd' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (ValMd' lab) Source # 
Instance details

Defined in Text.LLVM.AST

data DebugLoc' lab Source #

Constructors

DebugLoc 

Fields

Instances

Instances details
Functor DebugLoc' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DebugLoc' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DebugLoc' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DebugLoc' :: k -> Type #

Methods

from1 :: forall (a :: k). DebugLoc' a -> Rep1 DebugLoc' a #

to1 :: forall (a :: k). Rep1 DebugLoc' a -> DebugLoc' a #

Data lab => Data (DebugLoc' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DebugLoc' lab -> c (DebugLoc' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DebugLoc' lab) #

toConstr :: DebugLoc' lab -> Constr #

dataTypeOf :: DebugLoc' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DebugLoc' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DebugLoc' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DebugLoc' lab -> DebugLoc' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DebugLoc' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DebugLoc' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DebugLoc' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DebugLoc' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DebugLoc' lab -> m (DebugLoc' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DebugLoc' lab -> m (DebugLoc' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DebugLoc' lab -> m (DebugLoc' lab) #

Generic (DebugLoc' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: DebugLoc' lab -> String #

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

Eq lab => Eq (DebugLoc' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: DebugLoc' lab -> DebugLoc' lab -> Bool #

(/=) :: DebugLoc' lab -> DebugLoc' lab -> Bool #

Ord lab => Ord (DebugLoc' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: DebugLoc' lab -> DebugLoc' lab -> Ordering #

(<) :: DebugLoc' lab -> DebugLoc' lab -> Bool #

(<=) :: DebugLoc' lab -> DebugLoc' lab -> Bool #

(>) :: DebugLoc' lab -> DebugLoc' lab -> Bool #

(>=) :: DebugLoc' lab -> DebugLoc' lab -> Bool #

max :: DebugLoc' lab -> DebugLoc' lab -> DebugLoc' lab #

min :: DebugLoc' lab -> DebugLoc' lab -> DebugLoc' lab #

type Rep1 DebugLoc' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DebugLoc' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DebugLoc' lab) = D1 ('MetaData "DebugLoc'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DebugLoc" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dlLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "dlCol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "dlScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValMd' lab)) :*: (S1 ('MetaSel ('Just "dlIA") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dlImplicit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

Value Elimination

Statements

data Stmt' lab Source #

Constructors

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

Instances

Instances details
Functor Stmt' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel Stmt' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 Stmt' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 Stmt' :: k -> Type #

Methods

from1 :: forall (a :: k). Stmt' a -> Rep1 Stmt' a #

to1 :: forall (a :: k). Rep1 Stmt' a -> Stmt' a #

Data lab => Data (Stmt' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stmt' lab -> c (Stmt' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Stmt' lab) #

toConstr :: Stmt' lab -> Constr #

dataTypeOf :: Stmt' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Stmt' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Stmt' lab)) #

gmapT :: (forall b. Data b => b -> b) -> Stmt' lab -> Stmt' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stmt' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stmt' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> Stmt' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stmt' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stmt' lab -> m (Stmt' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt' lab -> m (Stmt' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt' lab -> m (Stmt' lab) #

Generic (Stmt' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: Stmt' lab -> String #

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

Eq lab => Eq (Stmt' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: Stmt' lab -> Stmt' lab -> Bool #

(/=) :: Stmt' lab -> Stmt' lab -> Bool #

Ord lab => Ord (Stmt' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: Stmt' lab -> Stmt' lab -> Ordering #

(<) :: Stmt' lab -> Stmt' lab -> Bool #

(<=) :: Stmt' lab -> Stmt' lab -> Bool #

(>) :: Stmt' lab -> Stmt' lab -> Bool #

(>=) :: Stmt' lab -> Stmt' lab -> Bool #

max :: Stmt' lab -> Stmt' lab -> Stmt' lab #

min :: Stmt' lab -> Stmt' lab -> Stmt' lab #

type Rep1 Stmt' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (Stmt' lab) Source # 
Instance details

Defined in Text.LLVM.AST

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

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

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

Constant Expressions

data ConstExpr' lab Source #

Constructors

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

Since LLVM 3.7, constant getelementptr expressions include an explicit type to use as a basis for calculations. For older versions of LLVM, this type can be reconstructed by inspecting the pointee type of the parent pointer value.

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

Instances

Instances details
Functor ConstExpr' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel ConstExpr' Source #

Clever instance that actually uses the block name

Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 ConstExpr' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 ConstExpr' :: k -> Type #

Methods

from1 :: forall (a :: k). ConstExpr' a -> Rep1 ConstExpr' a #

to1 :: forall (a :: k). Rep1 ConstExpr' a -> ConstExpr' a #

Data lab => Data (ConstExpr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstExpr' lab -> c (ConstExpr' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConstExpr' lab) #

toConstr :: ConstExpr' lab -> Constr #

dataTypeOf :: ConstExpr' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConstExpr' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConstExpr' lab)) #

gmapT :: (forall b. Data b => b -> b) -> ConstExpr' lab -> ConstExpr' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstExpr' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstExpr' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConstExpr' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstExpr' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstExpr' lab -> m (ConstExpr' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstExpr' lab -> m (ConstExpr' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstExpr' lab -> m (ConstExpr' lab) #

Generic (ConstExpr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: ConstExpr' lab -> String #

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

Eq lab => Eq (ConstExpr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: ConstExpr' lab -> ConstExpr' lab -> Bool #

(/=) :: ConstExpr' lab -> ConstExpr' lab -> Bool #

Ord lab => Ord (ConstExpr' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: ConstExpr' lab -> ConstExpr' lab -> Ordering #

(<) :: ConstExpr' lab -> ConstExpr' lab -> Bool #

(<=) :: ConstExpr' lab -> ConstExpr' lab -> Bool #

(>) :: ConstExpr' lab -> ConstExpr' lab -> Bool #

(>=) :: ConstExpr' lab -> ConstExpr' lab -> Bool #

max :: ConstExpr' lab -> ConstExpr' lab -> ConstExpr' lab #

min :: ConstExpr' lab -> ConstExpr' lab -> ConstExpr' lab #

type Rep1 ConstExpr' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

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

DWARF Debug Info

data DebugInfo' lab Source #

Instances

Instances details
Functor DebugInfo' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DebugInfo' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DebugInfo' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DebugInfo' :: k -> Type #

Methods

from1 :: forall (a :: k). DebugInfo' a -> Rep1 DebugInfo' a #

to1 :: forall (a :: k). Rep1 DebugInfo' a -> DebugInfo' a #

Data lab => Data (DebugInfo' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DebugInfo' lab -> c (DebugInfo' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DebugInfo' lab) #

toConstr :: DebugInfo' lab -> Constr #

dataTypeOf :: DebugInfo' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DebugInfo' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DebugInfo' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DebugInfo' lab -> DebugInfo' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DebugInfo' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DebugInfo' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DebugInfo' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DebugInfo' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DebugInfo' lab -> m (DebugInfo' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DebugInfo' lab -> m (DebugInfo' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DebugInfo' lab -> m (DebugInfo' lab) #

Generic (DebugInfo' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

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

Defined in Text.LLVM.AST

Methods

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

show :: DebugInfo' lab -> String #

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

Eq lab => Eq (DebugInfo' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: DebugInfo' lab -> DebugInfo' lab -> Bool #

(/=) :: DebugInfo' lab -> DebugInfo' lab -> Bool #

Ord lab => Ord (DebugInfo' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: DebugInfo' lab -> DebugInfo' lab -> Ordering #

(<) :: DebugInfo' lab -> DebugInfo' lab -> Bool #

(<=) :: DebugInfo' lab -> DebugInfo' lab -> Bool #

(>) :: DebugInfo' lab -> DebugInfo' lab -> Bool #

(>=) :: DebugInfo' lab -> DebugInfo' lab -> Bool #

max :: DebugInfo' lab -> DebugInfo' lab -> DebugInfo' lab #

min :: DebugInfo' lab -> DebugInfo' lab -> DebugInfo' lab #

type Rep1 DebugInfo' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DebugInfo' = D1 ('MetaData "DebugInfo'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((((C1 ('MetaCons "DebugInfoBasicType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIBasicType)) :+: C1 ('MetaCons "DebugInfoCompileUnit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DICompileUnit'))) :+: (C1 ('MetaCons "DebugInfoCompositeType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DICompositeType')) :+: (C1 ('MetaCons "DebugInfoDerivedType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DIDerivedType')) :+: C1 ('MetaCons "DebugInfoEnumerator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))) :+: ((C1 ('MetaCons "DebugInfoExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIExpression)) :+: (C1 ('MetaCons "DebugInfoFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFile)) :+: C1 ('MetaCons "DebugInfoGlobalVariable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DIGlobalVariable')))) :+: (C1 ('MetaCons "DebugInfoGlobalVariableExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DIGlobalVariableExpression')) :+: (C1 ('MetaCons "DebugInfoLexicalBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DILexicalBlock')) :+: C1 ('MetaCons "DebugInfoLexicalBlockFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DILexicalBlockFile')))))) :+: (((C1 ('MetaCons "DebugInfoLocalVariable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DILocalVariable')) :+: C1 ('MetaCons "DebugInfoSubprogram" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DISubprogram'))) :+: (C1 ('MetaCons "DebugInfoSubrange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DISubrange')) :+: (C1 ('MetaCons "DebugInfoSubroutineType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DISubroutineType')) :+: C1 ('MetaCons "DebugInfoNameSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DINameSpace'))))) :+: ((C1 ('MetaCons "DebugInfoTemplateTypeParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DITemplateTypeParameter')) :+: (C1 ('MetaCons "DebugInfoTemplateValueParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DITemplateValueParameter')) :+: C1 ('MetaCons "DebugInfoImportedEntity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DIImportedEntity')))) :+: (C1 ('MetaCons "DebugInfoLabel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DILabel')) :+: (C1 ('MetaCons "DebugInfoArgList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 DIArgList')) :+: C1 ('MetaCons "DebugInfoAssignID" 'PrefixI 'False) (U1 :: Type -> Type))))))
type Rep (DebugInfo' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DebugInfo' lab) = D1 ('MetaData "DebugInfo'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) ((((C1 ('MetaCons "DebugInfoBasicType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIBasicType)) :+: C1 ('MetaCons "DebugInfoCompileUnit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DICompileUnit' lab)))) :+: (C1 ('MetaCons "DebugInfoCompositeType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DICompositeType' lab))) :+: (C1 ('MetaCons "DebugInfoDerivedType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DIDerivedType' lab))) :+: C1 ('MetaCons "DebugInfoEnumerator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))) :+: ((C1 ('MetaCons "DebugInfoExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIExpression)) :+: (C1 ('MetaCons "DebugInfoFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFile)) :+: C1 ('MetaCons "DebugInfoGlobalVariable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DIGlobalVariable' lab))))) :+: (C1 ('MetaCons "DebugInfoGlobalVariableExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DIGlobalVariableExpression' lab))) :+: (C1 ('MetaCons "DebugInfoLexicalBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DILexicalBlock' lab))) :+: C1 ('MetaCons "DebugInfoLexicalBlockFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DILexicalBlockFile' lab))))))) :+: (((C1 ('MetaCons "DebugInfoLocalVariable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DILocalVariable' lab))) :+: C1 ('MetaCons "DebugInfoSubprogram" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DISubprogram' lab)))) :+: (C1 ('MetaCons "DebugInfoSubrange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DISubrange' lab))) :+: (C1 ('MetaCons "DebugInfoSubroutineType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DISubroutineType' lab))) :+: C1 ('MetaCons "DebugInfoNameSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DINameSpace' lab)))))) :+: ((C1 ('MetaCons "DebugInfoTemplateTypeParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DITemplateTypeParameter' lab))) :+: (C1 ('MetaCons "DebugInfoTemplateValueParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DITemplateValueParameter' lab))) :+: C1 ('MetaCons "DebugInfoImportedEntity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DIImportedEntity' lab))))) :+: (C1 ('MetaCons "DebugInfoLabel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DILabel' lab))) :+: (C1 ('MetaCons "DebugInfoArgList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DIArgList' lab))) :+: C1 ('MetaCons "DebugInfoAssignID" 'PrefixI 'False) (U1 :: Type -> Type))))))

data DILabel' lab Source #

Constructors

DILabel 

Fields

Instances

Instances details
Functor DILabel' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DILabel' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DILabel' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DILabel' :: k -> Type #

Methods

from1 :: forall (a :: k). DILabel' a -> Rep1 DILabel' a #

to1 :: forall (a :: k). Rep1 DILabel' a -> DILabel' a #

Data lab => Data (DILabel' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DILabel' lab -> c (DILabel' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DILabel' lab) #

toConstr :: DILabel' lab -> Constr #

dataTypeOf :: DILabel' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DILabel' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DILabel' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DILabel' lab -> DILabel' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DILabel' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DILabel' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DILabel' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DILabel' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DILabel' lab -> m (DILabel' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DILabel' lab -> m (DILabel' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DILabel' lab -> m (DILabel' lab) #

Generic (DILabel' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DILabel' lab) :: Type -> Type #

Methods

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

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

Show lab => Show (DILabel' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

show :: DILabel' lab -> String #

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

Eq lab => Eq (DILabel' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: DILabel' lab -> DILabel' lab -> Bool #

(/=) :: DILabel' lab -> DILabel' lab -> Bool #

Ord lab => Ord (DILabel' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: DILabel' lab -> DILabel' lab -> Ordering #

(<) :: DILabel' lab -> DILabel' lab -> Bool #

(<=) :: DILabel' lab -> DILabel' lab -> Bool #

(>) :: DILabel' lab -> DILabel' lab -> Bool #

(>=) :: DILabel' lab -> DILabel' lab -> Bool #

max :: DILabel' lab -> DILabel' lab -> DILabel' lab #

min :: DILabel' lab -> DILabel' lab -> DILabel' lab #

type Rep1 DILabel' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DILabel' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DILabel' lab) = D1 ('MetaData "DILabel'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DILabel" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dilScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dilName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "dilFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dilLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))))

data DIImportedEntity' lab Source #

Instances

Instances details
Functor DIImportedEntity' Source # 
Instance details

Defined in Text.LLVM.AST

HasLabel DIImportedEntity' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DIImportedEntity' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DIImportedEntity' :: k -> Type #

Methods

from1 :: forall (a :: k). DIImportedEntity' a -> Rep1 DIImportedEntity' a #

to1 :: forall (a :: k). Rep1 DIImportedEntity' a -> DIImportedEntity' a #

Data lab => Data (DIImportedEntity' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIImportedEntity' lab -> c (DIImportedEntity' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DIImportedEntity' lab) #

toConstr :: DIImportedEntity' lab -> Constr #

dataTypeOf :: DIImportedEntity' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DIImportedEntity' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DIImportedEntity' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DIImportedEntity' lab -> DIImportedEntity' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIImportedEntity' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIImportedEntity' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIImportedEntity' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIImportedEntity' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIImportedEntity' lab -> m (DIImportedEntity' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIImportedEntity' lab -> m (DIImportedEntity' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIImportedEntity' lab -> m (DIImportedEntity' lab) #

Generic (DIImportedEntity' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DIImportedEntity' lab) :: Type -> Type #

Show lab => Show (DIImportedEntity' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DIImportedEntity' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DIImportedEntity' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DIImportedEntity' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DIImportedEntity' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DIImportedEntity' lab) = D1 ('MetaData "DIImportedEntity'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DIImportedEntity" 'PrefixI 'True) ((S1 ('MetaSel ('Just "diieTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfTag) :*: (S1 ('MetaSel ('Just "diieScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "diieEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) :*: (S1 ('MetaSel ('Just "diieFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "diieLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "diieName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))))

data DITemplateTypeParameter' lab Source #

Instances

Instances details
Functor DITemplateTypeParameter' Source # 
Instance details

Defined in Text.LLVM.AST

HasLabel DITemplateTypeParameter' Source # 
Instance details

Defined in Text.LLVM.Labels

Generic1 DITemplateTypeParameter' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DITemplateTypeParameter' :: k -> Type #

Data lab => Data (DITemplateTypeParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DITemplateTypeParameter' lab -> c (DITemplateTypeParameter' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DITemplateTypeParameter' lab) #

toConstr :: DITemplateTypeParameter' lab -> Constr #

dataTypeOf :: DITemplateTypeParameter' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DITemplateTypeParameter' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DITemplateTypeParameter' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DITemplateTypeParameter' lab -> DITemplateTypeParameter' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DITemplateTypeParameter' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DITemplateTypeParameter' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DITemplateTypeParameter' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DITemplateTypeParameter' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DITemplateTypeParameter' lab -> m (DITemplateTypeParameter' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DITemplateTypeParameter' lab -> m (DITemplateTypeParameter' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DITemplateTypeParameter' lab -> m (DITemplateTypeParameter' lab) #

Generic (DITemplateTypeParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DITemplateTypeParameter' lab) :: Type -> Type #

Show lab => Show (DITemplateTypeParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DITemplateTypeParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DITemplateTypeParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DITemplateTypeParameter' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DITemplateTypeParameter' = D1 ('MetaData "DITemplateTypeParameter'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DITemplateTypeParameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "dittpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "dittpType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd') :*: S1 ('MetaSel ('Just "dittpIsDefault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))
type Rep (DITemplateTypeParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DITemplateTypeParameter' lab) = D1 ('MetaData "DITemplateTypeParameter'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DITemplateTypeParameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "dittpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "dittpType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dittpIsDefault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

data DITemplateValueParameter' lab Source #

Instances

Instances details
Functor DITemplateValueParameter' Source # 
Instance details

Defined in Text.LLVM.AST

HasLabel DITemplateValueParameter' Source # 
Instance details

Defined in Text.LLVM.Labels

Generic1 DITemplateValueParameter' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DITemplateValueParameter' :: k -> Type #

Data lab => Data (DITemplateValueParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DITemplateValueParameter' lab -> c (DITemplateValueParameter' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DITemplateValueParameter' lab) #

toConstr :: DITemplateValueParameter' lab -> Constr #

dataTypeOf :: DITemplateValueParameter' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DITemplateValueParameter' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DITemplateValueParameter' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DITemplateValueParameter' lab -> DITemplateValueParameter' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DITemplateValueParameter' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DITemplateValueParameter' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DITemplateValueParameter' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DITemplateValueParameter' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DITemplateValueParameter' lab -> m (DITemplateValueParameter' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DITemplateValueParameter' lab -> m (DITemplateValueParameter' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DITemplateValueParameter' lab -> m (DITemplateValueParameter' lab) #

Generic (DITemplateValueParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DITemplateValueParameter' lab) :: Type -> Type #

Show lab => Show (DITemplateValueParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DITemplateValueParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DITemplateValueParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DITemplateValueParameter' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DITemplateValueParameter' = D1 ('MetaData "DITemplateValueParameter'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DITemplateValueParameter" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ditvpTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfTag) :*: S1 ('MetaSel ('Just "ditvpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "ditvpType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd') :*: (S1 ('MetaSel ('Just "ditvpIsDefault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "ditvpValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ValMd')))))
type Rep (DITemplateValueParameter' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DITemplateValueParameter' lab) = D1 ('MetaData "DITemplateValueParameter'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DITemplateValueParameter" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ditvpTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfTag) :*: S1 ('MetaSel ('Just "ditvpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "ditvpType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "ditvpIsDefault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "ditvpValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValMd' lab))))))

data DINameSpace' lab Source #

Constructors

DINameSpace 

Instances

Instances details
Functor DINameSpace' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DINameSpace' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DINameSpace' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DINameSpace' :: k -> Type #

Methods

from1 :: forall (a :: k). DINameSpace' a -> Rep1 DINameSpace' a #

to1 :: forall (a :: k). Rep1 DINameSpace' a -> DINameSpace' a #

Data lab => Data (DINameSpace' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DINameSpace' lab -> c (DINameSpace' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DINameSpace' lab) #

toConstr :: DINameSpace' lab -> Constr #

dataTypeOf :: DINameSpace' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DINameSpace' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DINameSpace' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DINameSpace' lab -> DINameSpace' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DINameSpace' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DINameSpace' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DINameSpace' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DINameSpace' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DINameSpace' lab -> m (DINameSpace' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DINameSpace' lab -> m (DINameSpace' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DINameSpace' lab -> m (DINameSpace' lab) #

Generic (DINameSpace' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DINameSpace' lab) :: Type -> Type #

Methods

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

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

Show lab => Show (DINameSpace' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DINameSpace' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: DINameSpace' lab -> DINameSpace' lab -> Bool #

(/=) :: DINameSpace' lab -> DINameSpace' lab -> Bool #

Ord lab => Ord (DINameSpace' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DINameSpace' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DINameSpace' = D1 ('MetaData "DINameSpace'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DINameSpace" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dinsName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "dinsScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ValMd')) :*: (S1 ('MetaSel ('Just "dinsFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ValMd') :*: S1 ('MetaSel ('Just "dinsLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))))
type Rep (DINameSpace' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DINameSpace' lab) = D1 ('MetaData "DINameSpace'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DINameSpace" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dinsName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "dinsScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dinsFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValMd' lab)) :*: S1 ('MetaSel ('Just "dinsLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))))

data DIBasicType Source #

Instances

Instances details
Data DIBasicType Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIBasicType -> c DIBasicType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DIBasicType #

toConstr :: DIBasicType -> Constr #

dataTypeOf :: DIBasicType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DIBasicType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DIBasicType) #

gmapT :: (forall b. Data b => b -> b) -> DIBasicType -> DIBasicType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIBasicType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIBasicType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIBasicType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIBasicType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIBasicType -> m DIBasicType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIBasicType -> m DIBasicType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIBasicType -> m DIBasicType #

Generic DIBasicType Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep DIBasicType :: Type -> Type #

Show DIBasicType Source # 
Instance details

Defined in Text.LLVM.AST

Eq DIBasicType Source # 
Instance details

Defined in Text.LLVM.AST

Ord DIBasicType Source # 
Instance details

Defined in Text.LLVM.AST

type Rep DIBasicType Source # 
Instance details

Defined in Text.LLVM.AST

data DICompileUnit' lab Source #

Instances

Instances details
Functor DICompileUnit' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DICompileUnit' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DICompileUnit' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DICompileUnit' :: k -> Type #

Methods

from1 :: forall (a :: k). DICompileUnit' a -> Rep1 DICompileUnit' a #

to1 :: forall (a :: k). Rep1 DICompileUnit' a -> DICompileUnit' a #

Data lab => Data (DICompileUnit' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DICompileUnit' lab -> c (DICompileUnit' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DICompileUnit' lab) #

toConstr :: DICompileUnit' lab -> Constr #

dataTypeOf :: DICompileUnit' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DICompileUnit' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DICompileUnit' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DICompileUnit' lab -> DICompileUnit' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DICompileUnit' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DICompileUnit' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DICompileUnit' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DICompileUnit' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DICompileUnit' lab -> m (DICompileUnit' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DICompileUnit' lab -> m (DICompileUnit' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DICompileUnit' lab -> m (DICompileUnit' lab) #

Generic (DICompileUnit' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

Show lab => Show (DICompileUnit' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DICompileUnit' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DICompileUnit' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DICompileUnit' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

type Rep (DICompileUnit' lab) = D1 ('MetaData "DICompileUnit'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DICompileUnit" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "dicuLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfLang) :*: S1 ('MetaSel ('Just "dicuFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) :*: (S1 ('MetaSel ('Just "dicuProducer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "dicuIsOptimized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "dicuFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))) :*: ((S1 ('MetaSel ('Just "dicuRuntimeVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Just "dicuSplitDebugFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))) :*: (S1 ('MetaSel ('Just "dicuEmissionKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIEmissionKind) :*: (S1 ('MetaSel ('Just "dicuEnums") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dicuRetainedTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))))) :*: (((S1 ('MetaSel ('Just "dicuSubprograms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dicuGlobals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) :*: (S1 ('MetaSel ('Just "dicuImports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dicuMacros") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dicuDWOId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))) :*: ((S1 ('MetaSel ('Just "dicuSplitDebugInlining") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "dicuDebugInfoForProf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "dicuNameTableKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: (S1 ('MetaSel ('Just "dicuRangesBaseAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "dicuSysRoot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "dicuSDK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))))))

data DICompositeType' lab Source #

Instances

Instances details
Functor DICompositeType' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DICompositeType' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DICompositeType' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DICompositeType' :: k -> Type #

Methods

from1 :: forall (a :: k). DICompositeType' a -> Rep1 DICompositeType' a #

to1 :: forall (a :: k). Rep1 DICompositeType' a -> DICompositeType' a #

Data lab => Data (DICompositeType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DICompositeType' lab -> c (DICompositeType' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DICompositeType' lab) #

toConstr :: DICompositeType' lab -> Constr #

dataTypeOf :: DICompositeType' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DICompositeType' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DICompositeType' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DICompositeType' lab -> DICompositeType' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DICompositeType' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DICompositeType' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DICompositeType' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DICompositeType' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DICompositeType' lab -> m (DICompositeType' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DICompositeType' lab -> m (DICompositeType' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DICompositeType' lab -> m (DICompositeType' lab) #

Generic (DICompositeType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Show lab => Show (DICompositeType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DICompositeType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DICompositeType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DICompositeType' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

type Rep (DICompositeType' lab) = D1 ('MetaData "DICompositeType'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DICompositeType" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "dictTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfTag) :*: S1 ('MetaSel ('Just "dictName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "dictFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dictLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "dictScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))) :*: ((S1 ('MetaSel ('Just "dictBaseType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dictSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "dictAlign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "dictOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "dictFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFlags))))) :*: (((S1 ('MetaSel ('Just "dictElements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dictRuntimeLang") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfLang)) :*: (S1 ('MetaSel ('Just "dictVTableHolder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dictTemplateParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dictIdentifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))) :*: ((S1 ('MetaSel ('Just "dictDiscriminator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dictDataLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dictAssociated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) :*: (S1 ('MetaSel ('Just "dictAllocated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dictRank") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dictAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))))))

data DIDerivedType' lab Source #

Constructors

DIDerivedType 

Fields

Instances

Instances details
Functor DIDerivedType' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DIDerivedType' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DIDerivedType' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DIDerivedType' :: k -> Type #

Methods

from1 :: forall (a :: k). DIDerivedType' a -> Rep1 DIDerivedType' a #

to1 :: forall (a :: k). Rep1 DIDerivedType' a -> DIDerivedType' a #

Data lab => Data (DIDerivedType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIDerivedType' lab -> c (DIDerivedType' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DIDerivedType' lab) #

toConstr :: DIDerivedType' lab -> Constr #

dataTypeOf :: DIDerivedType' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DIDerivedType' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DIDerivedType' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DIDerivedType' lab -> DIDerivedType' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIDerivedType' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIDerivedType' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIDerivedType' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIDerivedType' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIDerivedType' lab -> m (DIDerivedType' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIDerivedType' lab -> m (DIDerivedType' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIDerivedType' lab -> m (DIDerivedType' lab) #

Generic (DIDerivedType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

Show lab => Show (DIDerivedType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DIDerivedType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DIDerivedType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DIDerivedType' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DIDerivedType' = D1 ('MetaData "DIDerivedType'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DIDerivedType" 'PrefixI 'True) (((S1 ('MetaSel ('Just "didtTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfTag) :*: (S1 ('MetaSel ('Just "didtName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "didtFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd'))) :*: (S1 ('MetaSel ('Just "didtLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "didtScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd') :*: S1 ('MetaSel ('Just "didtBaseType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd')))) :*: ((S1 ('MetaSel ('Just "didtSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "didtAlign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "didtOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "didtFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFlags) :*: S1 ('MetaSel ('Just "didtExtraData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd')) :*: (S1 ('MetaSel ('Just "didtDwarfAddressSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word32)) :*: S1 ('MetaSel ('Just "didtAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd'))))))
type Rep (DIDerivedType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DIDerivedType' lab) = D1 ('MetaData "DIDerivedType'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DIDerivedType" 'PrefixI 'True) (((S1 ('MetaSel ('Just "didtTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfTag) :*: (S1 ('MetaSel ('Just "didtName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "didtFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) :*: (S1 ('MetaSel ('Just "didtLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "didtScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "didtBaseType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))) :*: ((S1 ('MetaSel ('Just "didtSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "didtAlign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "didtOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "didtFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFlags) :*: S1 ('MetaSel ('Just "didtExtraData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) :*: (S1 ('MetaSel ('Just "didtDwarfAddressSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word32)) :*: S1 ('MetaSel ('Just "didtAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))))))

data DIExpression Source #

Constructors

DIExpression 

Fields

Instances

Instances details
Data DIExpression Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIExpression -> c DIExpression #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DIExpression #

toConstr :: DIExpression -> Constr #

dataTypeOf :: DIExpression -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DIExpression) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DIExpression) #

gmapT :: (forall b. Data b => b -> b) -> DIExpression -> DIExpression #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIExpression -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIExpression -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIExpression -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIExpression -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIExpression -> m DIExpression #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIExpression -> m DIExpression #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIExpression -> m DIExpression #

Generic DIExpression Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep DIExpression :: Type -> Type #

Show DIExpression Source # 
Instance details

Defined in Text.LLVM.AST

Eq DIExpression Source # 
Instance details

Defined in Text.LLVM.AST

Ord DIExpression Source # 
Instance details

Defined in Text.LLVM.AST

type Rep DIExpression Source # 
Instance details

Defined in Text.LLVM.AST

type Rep DIExpression = D1 ('MetaData "DIExpression" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DIExpression" 'PrefixI 'True) (S1 ('MetaSel ('Just "dieElements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word64])))

data DIFile Source #

Constructors

DIFile 

Instances

Instances details
Data DIFile Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIFile -> c DIFile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DIFile #

toConstr :: DIFile -> Constr #

dataTypeOf :: DIFile -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DIFile) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DIFile) #

gmapT :: (forall b. Data b => b -> b) -> DIFile -> DIFile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIFile -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIFile -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIFile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIFile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIFile -> m DIFile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIFile -> m DIFile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIFile -> m DIFile #

Generic DIFile Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep DIFile :: Type -> Type #

Methods

from :: DIFile -> Rep DIFile x #

to :: Rep DIFile x -> DIFile #

Show DIFile Source # 
Instance details

Defined in Text.LLVM.AST

Eq DIFile Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

Ord DIFile Source # 
Instance details

Defined in Text.LLVM.AST

type Rep DIFile Source # 
Instance details

Defined in Text.LLVM.AST

type Rep DIFile = D1 ('MetaData "DIFile" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DIFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "difFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "difDirectory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))

data DIGlobalVariable' lab Source #

Instances

Instances details
Functor DIGlobalVariable' Source # 
Instance details

Defined in Text.LLVM.AST

HasLabel DIGlobalVariable' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DIGlobalVariable' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DIGlobalVariable' :: k -> Type #

Methods

from1 :: forall (a :: k). DIGlobalVariable' a -> Rep1 DIGlobalVariable' a #

to1 :: forall (a :: k). Rep1 DIGlobalVariable' a -> DIGlobalVariable' a #

Data lab => Data (DIGlobalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIGlobalVariable' lab -> c (DIGlobalVariable' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DIGlobalVariable' lab) #

toConstr :: DIGlobalVariable' lab -> Constr #

dataTypeOf :: DIGlobalVariable' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DIGlobalVariable' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DIGlobalVariable' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DIGlobalVariable' lab -> DIGlobalVariable' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIGlobalVariable' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIGlobalVariable' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIGlobalVariable' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIGlobalVariable' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIGlobalVariable' lab -> m (DIGlobalVariable' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIGlobalVariable' lab -> m (DIGlobalVariable' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIGlobalVariable' lab -> m (DIGlobalVariable' lab) #

Generic (DIGlobalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Show lab => Show (DIGlobalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DIGlobalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DIGlobalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DIGlobalVariable' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

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

data DIGlobalVariableExpression' lab Source #

Instances

Instances details
Functor DIGlobalVariableExpression' Source # 
Instance details

Defined in Text.LLVM.AST

HasLabel DIGlobalVariableExpression' Source # 
Instance details

Defined in Text.LLVM.Labels

Generic1 DIGlobalVariableExpression' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DIGlobalVariableExpression' :: k -> Type #

Data lab => Data (DIGlobalVariableExpression' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIGlobalVariableExpression' lab -> c (DIGlobalVariableExpression' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DIGlobalVariableExpression' lab) #

toConstr :: DIGlobalVariableExpression' lab -> Constr #

dataTypeOf :: DIGlobalVariableExpression' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DIGlobalVariableExpression' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DIGlobalVariableExpression' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DIGlobalVariableExpression' lab -> DIGlobalVariableExpression' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIGlobalVariableExpression' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIGlobalVariableExpression' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIGlobalVariableExpression' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIGlobalVariableExpression' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIGlobalVariableExpression' lab -> m (DIGlobalVariableExpression' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIGlobalVariableExpression' lab -> m (DIGlobalVariableExpression' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIGlobalVariableExpression' lab -> m (DIGlobalVariableExpression' lab) #

Generic (DIGlobalVariableExpression' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DIGlobalVariableExpression' lab) :: Type -> Type #

Show lab => Show (DIGlobalVariableExpression' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DIGlobalVariableExpression' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DIGlobalVariableExpression' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DIGlobalVariableExpression' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DIGlobalVariableExpression' = D1 ('MetaData "DIGlobalVariableExpression'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DIGlobalVariableExpression" 'PrefixI 'True) (S1 ('MetaSel ('Just "digveVariable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd') :*: S1 ('MetaSel ('Just "digveExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd')))
type Rep (DIGlobalVariableExpression' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DIGlobalVariableExpression' lab) = D1 ('MetaData "DIGlobalVariableExpression'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DIGlobalVariableExpression" 'PrefixI 'True) (S1 ('MetaSel ('Just "digveVariable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "digveExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))

data DILexicalBlock' lab Source #

Constructors

DILexicalBlock 

Instances

Instances details
Functor DILexicalBlock' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DILexicalBlock' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DILexicalBlock' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DILexicalBlock' :: k -> Type #

Methods

from1 :: forall (a :: k). DILexicalBlock' a -> Rep1 DILexicalBlock' a #

to1 :: forall (a :: k). Rep1 DILexicalBlock' a -> DILexicalBlock' a #

Data lab => Data (DILexicalBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DILexicalBlock' lab -> c (DILexicalBlock' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DILexicalBlock' lab) #

toConstr :: DILexicalBlock' lab -> Constr #

dataTypeOf :: DILexicalBlock' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DILexicalBlock' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DILexicalBlock' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DILexicalBlock' lab -> DILexicalBlock' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DILexicalBlock' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DILexicalBlock' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DILexicalBlock' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DILexicalBlock' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DILexicalBlock' lab -> m (DILexicalBlock' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DILexicalBlock' lab -> m (DILexicalBlock' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DILexicalBlock' lab -> m (DILexicalBlock' lab) #

Generic (DILexicalBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

Show lab => Show (DILexicalBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DILexicalBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DILexicalBlock' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DILexicalBlock' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

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

data DILexicalBlockFile' lab Source #

Instances

Instances details
Functor DILexicalBlockFile' Source # 
Instance details

Defined in Text.LLVM.AST

HasLabel DILexicalBlockFile' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DILexicalBlockFile' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DILexicalBlockFile' :: k -> Type #

Methods

from1 :: forall (a :: k). DILexicalBlockFile' a -> Rep1 DILexicalBlockFile' a #

to1 :: forall (a :: k). Rep1 DILexicalBlockFile' a -> DILexicalBlockFile' a #

Data lab => Data (DILexicalBlockFile' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DILexicalBlockFile' lab -> c (DILexicalBlockFile' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DILexicalBlockFile' lab) #

toConstr :: DILexicalBlockFile' lab -> Constr #

dataTypeOf :: DILexicalBlockFile' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DILexicalBlockFile' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DILexicalBlockFile' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DILexicalBlockFile' lab -> DILexicalBlockFile' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DILexicalBlockFile' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DILexicalBlockFile' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DILexicalBlockFile' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DILexicalBlockFile' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DILexicalBlockFile' lab -> m (DILexicalBlockFile' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DILexicalBlockFile' lab -> m (DILexicalBlockFile' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DILexicalBlockFile' lab -> m (DILexicalBlockFile' lab) #

Generic (DILexicalBlockFile' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Show lab => Show (DILexicalBlockFile' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DILexicalBlockFile' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DILexicalBlockFile' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DILexicalBlockFile' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

type Rep (DILexicalBlockFile' lab) = D1 ('MetaData "DILexicalBlockFile'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DILexicalBlockFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "dilbfScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValMd' lab)) :*: (S1 ('MetaSel ('Just "dilbfFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dilbfDiscriminator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))))

data DILocalVariable' lab Source #

Constructors

DILocalVariable 

Fields

Instances

Instances details
Functor DILocalVariable' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DILocalVariable' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DILocalVariable' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DILocalVariable' :: k -> Type #

Methods

from1 :: forall (a :: k). DILocalVariable' a -> Rep1 DILocalVariable' a #

to1 :: forall (a :: k). Rep1 DILocalVariable' a -> DILocalVariable' a #

Data lab => Data (DILocalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DILocalVariable' lab -> c (DILocalVariable' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DILocalVariable' lab) #

toConstr :: DILocalVariable' lab -> Constr #

dataTypeOf :: DILocalVariable' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DILocalVariable' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DILocalVariable' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DILocalVariable' lab -> DILocalVariable' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DILocalVariable' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DILocalVariable' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DILocalVariable' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DILocalVariable' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DILocalVariable' lab -> m (DILocalVariable' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DILocalVariable' lab -> m (DILocalVariable' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DILocalVariable' lab -> m (DILocalVariable' lab) #

Generic (DILocalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Show lab => Show (DILocalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DILocalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DILocalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DILocalVariable' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DILocalVariable' lab) Source # 
Instance details

Defined in Text.LLVM.AST

data DISubprogram' lab Source #

Instances

Instances details
Functor DISubprogram' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DISubprogram' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DISubprogram' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DISubprogram' :: k -> Type #

Methods

from1 :: forall (a :: k). DISubprogram' a -> Rep1 DISubprogram' a #

to1 :: forall (a :: k). Rep1 DISubprogram' a -> DISubprogram' a #

Data lab => Data (DISubprogram' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DISubprogram' lab -> c (DISubprogram' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DISubprogram' lab) #

toConstr :: DISubprogram' lab -> Constr #

dataTypeOf :: DISubprogram' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DISubprogram' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DISubprogram' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DISubprogram' lab -> DISubprogram' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DISubprogram' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DISubprogram' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DISubprogram' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DISubprogram' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DISubprogram' lab -> m (DISubprogram' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DISubprogram' lab -> m (DISubprogram' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DISubprogram' lab -> m (DISubprogram' lab) #

Generic (DISubprogram' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Methods

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

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

Show lab => Show (DISubprogram' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DISubprogram' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: DISubprogram' lab -> DISubprogram' lab -> Bool #

(/=) :: DISubprogram' lab -> DISubprogram' lab -> Bool #

Ord lab => Ord (DISubprogram' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DISubprogram' Source # 
Instance details

Defined in Text.LLVM.AST

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

Defined in Text.LLVM.AST

type Rep (DISubprogram' lab) = D1 ('MetaData "DISubprogram'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DISubprogram" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "dispScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dispName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "dispLinkageName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "dispFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dispLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))) :*: ((S1 ('MetaSel ('Just "dispType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dispIsLocal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "dispIsDefinition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "dispScopeLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "dispContainingType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))))) :*: (((S1 ('MetaSel ('Just "dispVirtuality") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DwarfVirtuality) :*: S1 ('MetaSel ('Just "dispVirtualIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "dispThisAdjustment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "dispFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFlags) :*: S1 ('MetaSel ('Just "dispIsOptimized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "dispUnit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dispTemplateParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dispDeclaration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))) :*: (S1 ('MetaSel ('Just "dispRetainedNodes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: (S1 ('MetaSel ('Just "dispThrownTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "dispAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))))))

data DISubrange' lab Source #

The DISubrange is a Value subrange specification, usually associated with arrays or enumerations.

  • Early LLVM: only disrCount and disrLowerBound were present, where both were a direct signed 64-bit value. This corresponds to "format 0" in the bitcode encoding (see reference below).
  • LLVM 7: disrCount changed to metadata representation (Value'). The metadata representation should only be a signed 64-bit integer, a Variable, or an Expression. This corresponds to "format 1" in the bitcode encoding.
  • LLVM 11: disrLowerBound was changed to a metadata representation and disrUpperBound and disrStride were added (primarily driven by the addition of Fortran support in llvm). All three should only be represented as a signed 64-bit integer, a Variable, or an Expression. This corresponds to "format 2" in the bitcode encoding. See https://github.com/llvm/llvm-project/commit/d20bf5a for this change.

Also see https://github.com/llvm/llvm-project/blob/bbe8cd1/llvm/lib/Bitcode/Reader/MetadataLoader.cpp#L1435-L1461 for how this is read from the bitcode encoding and the use of the format values mentioned above.

Constructors

DISubrange 

Instances

Instances details
Functor DISubrange' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DISubrange' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DISubrange' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DISubrange' :: k -> Type #

Methods

from1 :: forall (a :: k). DISubrange' a -> Rep1 DISubrange' a #

to1 :: forall (a :: k). Rep1 DISubrange' a -> DISubrange' a #

Data lab => Data (DISubrange' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DISubrange' lab -> c (DISubrange' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DISubrange' lab) #

toConstr :: DISubrange' lab -> Constr #

dataTypeOf :: DISubrange' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DISubrange' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DISubrange' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DISubrange' lab -> DISubrange' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DISubrange' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DISubrange' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DISubrange' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DISubrange' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DISubrange' lab -> m (DISubrange' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DISubrange' lab -> m (DISubrange' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DISubrange' lab -> m (DISubrange' lab) #

Generic (DISubrange' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DISubrange' lab) :: Type -> Type #

Methods

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

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

Show lab => Show (DISubrange' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

show :: DISubrange' lab -> String #

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

Eq lab => Eq (DISubrange' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: DISubrange' lab -> DISubrange' lab -> Bool #

(/=) :: DISubrange' lab -> DISubrange' lab -> Bool #

Ord lab => Ord (DISubrange' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: DISubrange' lab -> DISubrange' lab -> Ordering #

(<) :: DISubrange' lab -> DISubrange' lab -> Bool #

(<=) :: DISubrange' lab -> DISubrange' lab -> Bool #

(>) :: DISubrange' lab -> DISubrange' lab -> Bool #

(>=) :: DISubrange' lab -> DISubrange' lab -> Bool #

max :: DISubrange' lab -> DISubrange' lab -> DISubrange' lab #

min :: DISubrange' lab -> DISubrange' lab -> DISubrange' lab #

type Rep1 DISubrange' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DISubrange' = D1 ('MetaData "DISubrange'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DISubrange" 'PrefixI 'True) ((S1 ('MetaSel ('Just "disrCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd') :*: S1 ('MetaSel ('Just "disrLowerBound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd')) :*: (S1 ('MetaSel ('Just "disrUpperBound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd') :*: S1 ('MetaSel ('Just "disrStride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd'))))
type Rep (DISubrange' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DISubrange' lab) = D1 ('MetaData "DISubrange'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DISubrange" 'PrefixI 'True) ((S1 ('MetaSel ('Just "disrCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "disrLowerBound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))) :*: (S1 ('MetaSel ('Just "disrUpperBound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))) :*: S1 ('MetaSel ('Just "disrStride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab))))))

data DISubroutineType' lab Source #

Constructors

DISubroutineType 

Instances

Instances details
Functor DISubroutineType' Source # 
Instance details

Defined in Text.LLVM.AST

HasLabel DISubroutineType' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DISubroutineType' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DISubroutineType' :: k -> Type #

Methods

from1 :: forall (a :: k). DISubroutineType' a -> Rep1 DISubroutineType' a #

to1 :: forall (a :: k). Rep1 DISubroutineType' a -> DISubroutineType' a #

Data lab => Data (DISubroutineType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DISubroutineType' lab -> c (DISubroutineType' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DISubroutineType' lab) #

toConstr :: DISubroutineType' lab -> Constr #

dataTypeOf :: DISubroutineType' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DISubroutineType' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DISubroutineType' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DISubroutineType' lab -> DISubroutineType' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DISubroutineType' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DISubroutineType' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DISubroutineType' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DISubroutineType' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DISubroutineType' lab -> m (DISubroutineType' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DISubroutineType' lab -> m (DISubroutineType' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DISubroutineType' lab -> m (DISubroutineType' lab) #

Generic (DISubroutineType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

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

Show lab => Show (DISubroutineType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Eq lab => Eq (DISubroutineType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Ord lab => Ord (DISubroutineType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DISubroutineType' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DISubroutineType' = D1 ('MetaData "DISubroutineType'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DISubroutineType" 'PrefixI 'True) (S1 ('MetaSel ('Just "distFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFlags) :*: S1 ('MetaSel ('Just "distTypeArray") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ValMd')))
type Rep (DISubroutineType' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DISubroutineType' lab) = D1 ('MetaData "DISubroutineType'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'False) (C1 ('MetaCons "DISubroutineType" 'PrefixI 'True) (S1 ('MetaSel ('Just "distFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DIFlags) :*: S1 ('MetaSel ('Just "distTypeArray") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ValMd' lab)))))

newtype DIArgList' lab Source #

Constructors

DIArgList 

Fields

Instances

Instances details
Functor DIArgList' Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

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

HasLabel DIArgList' Source # 
Instance details

Defined in Text.LLVM.Labels

Methods

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

Generic1 DIArgList' Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep1 DIArgList' :: k -> Type #

Methods

from1 :: forall (a :: k). DIArgList' a -> Rep1 DIArgList' a #

to1 :: forall (a :: k). Rep1 DIArgList' a -> DIArgList' a #

Data lab => Data (DIArgList' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DIArgList' lab -> c (DIArgList' lab) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DIArgList' lab) #

toConstr :: DIArgList' lab -> Constr #

dataTypeOf :: DIArgList' lab -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DIArgList' lab)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DIArgList' lab)) #

gmapT :: (forall b. Data b => b -> b) -> DIArgList' lab -> DIArgList' lab #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DIArgList' lab -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DIArgList' lab -> r #

gmapQ :: (forall d. Data d => d -> u) -> DIArgList' lab -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DIArgList' lab -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DIArgList' lab -> m (DIArgList' lab) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DIArgList' lab -> m (DIArgList' lab) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DIArgList' lab -> m (DIArgList' lab) #

Generic (DIArgList' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep (DIArgList' lab) :: Type -> Type #

Methods

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

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

Show lab => Show (DIArgList' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

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

show :: DIArgList' lab -> String #

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

Eq lab => Eq (DIArgList' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: DIArgList' lab -> DIArgList' lab -> Bool #

(/=) :: DIArgList' lab -> DIArgList' lab -> Bool #

Ord lab => Ord (DIArgList' lab) Source # 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: DIArgList' lab -> DIArgList' lab -> Ordering #

(<) :: DIArgList' lab -> DIArgList' lab -> Bool #

(<=) :: DIArgList' lab -> DIArgList' lab -> Bool #

(>) :: DIArgList' lab -> DIArgList' lab -> Bool #

(>=) :: DIArgList' lab -> DIArgList' lab -> Bool #

max :: DIArgList' lab -> DIArgList' lab -> DIArgList' lab #

min :: DIArgList' lab -> DIArgList' lab -> DIArgList' lab #

type Rep1 DIArgList' Source # 
Instance details

Defined in Text.LLVM.AST

type Rep1 DIArgList' = D1 ('MetaData "DIArgList'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'True) (C1 ('MetaCons "DIArgList" 'PrefixI 'True) (S1 ('MetaSel ('Just "dialArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (List :.: Rec1 ValMd')))
type Rep (DIArgList' lab) Source # 
Instance details

Defined in Text.LLVM.AST

type Rep (DIArgList' lab) = D1 ('MetaData "DIArgList'" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-3IOlow5XxzhDT5KTgFPPkh" 'True) (C1 ('MetaCons "DIArgList" 'PrefixI 'True) (S1 ('MetaSel ('Just "dialArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ValMd' lab])))

Aggregate Utilities

data IndexResult Source #

Constructors

Invalid

An invalid use of GEP

HasType Type

A resolved type

Resolve Ident (Type -> IndexResult)

Continue, after resolving an alias

Instances

Instances details
Generic IndexResult Source # 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep IndexResult :: Type -> Type #

type Rep IndexResult Source # 
Instance details

Defined in Text.LLVM.AST

resolveGepFull Source #

Arguments

:: (Ident -> Maybe Type)

Type alias resolution

-> Type

Base type used for calculations

-> Typed (Value' lab)

Pointer value

-> [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) -> [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.