llvm-hs-5.1.1: General purpose LLVM bindings

Safe HaskellNone
LanguageHaskell98

LLVM.Internal.FFI.LLVMCTypes

Contents

Description

Define types which correspond cleanly with some simple types on the C/C++ side. Encapsulate hsc macro weirdness here, supporting higher-level tricks elsewhere.

Synopsis

Documentation

newtype OwnerTransfered a Source #

If an FFI function returns a value wrapped in OwnerTransfered, this value needs to be freed after it has been processed. Usually this is done automatically in the DecodeM instance.

Constructors

OwnerTransfered a 

newtype CPPOpcode Source #

Constructors

CPPOpcode CUInt 

Instances

Eq CPPOpcode Source # 
Data CPPOpcode Source # 

Methods

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

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

toConstr :: CPPOpcode -> Constr #

dataTypeOf :: CPPOpcode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CPPOpcode Source # 
Show CPPOpcode Source # 
Generic CPPOpcode Source # 

Associated Types

type Rep CPPOpcode :: * -> * #

type Rep CPPOpcode Source # 
type Rep CPPOpcode = D1 * (MetaData "CPPOpcode" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "CPPOpcode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype ICmpPredicate Source #

Constructors

ICmpPredicate CUInt 

Instances

Eq ICmpPredicate Source # 
Data ICmpPredicate Source # 

Methods

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

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

toConstr :: ICmpPredicate -> Constr #

dataTypeOf :: ICmpPredicate -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ICmpPredicate Source # 
Show ICmpPredicate Source # 
Generic ICmpPredicate Source # 

Associated Types

type Rep ICmpPredicate :: * -> * #

type Rep ICmpPredicate Source # 
type Rep ICmpPredicate = D1 * (MetaData "ICmpPredicate" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "ICmpPredicate" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype FCmpPredicate Source #

Constructors

FCmpPredicate CUInt 

Instances

Eq FCmpPredicate Source # 
Data FCmpPredicate Source # 

Methods

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

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

toConstr :: FCmpPredicate -> Constr #

dataTypeOf :: FCmpPredicate -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FCmpPredicate Source # 
Show FCmpPredicate Source # 
Generic FCmpPredicate Source # 

Associated Types

type Rep FCmpPredicate :: * -> * #

type Rep FCmpPredicate Source # 
type Rep FCmpPredicate = D1 * (MetaData "FCmpPredicate" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "FCmpPredicate" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype FastMathFlags Source #

Constructors

FastMathFlags CUInt 

Instances

Eq FastMathFlags Source # 
Data FastMathFlags Source # 

Methods

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

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

toConstr :: FastMathFlags -> Constr #

dataTypeOf :: FastMathFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num FastMathFlags Source # 
Ord FastMathFlags Source # 
Show FastMathFlags Source # 
Generic FastMathFlags Source # 

Associated Types

type Rep FastMathFlags :: * -> * #

Bits FastMathFlags Source # 
type Rep FastMathFlags Source # 
type Rep FastMathFlags = D1 * (MetaData "FastMathFlags" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "FastMathFlags" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype MemoryOrdering Source #

Constructors

MemoryOrdering CUInt 

Instances

Eq MemoryOrdering Source # 
Data MemoryOrdering Source # 

Methods

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

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

toConstr :: MemoryOrdering -> Constr #

dataTypeOf :: MemoryOrdering -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MemoryOrdering Source # 
Generic MemoryOrdering Source # 

Associated Types

type Rep MemoryOrdering :: * -> * #

type Rep MemoryOrdering Source # 
type Rep MemoryOrdering = D1 * (MetaData "MemoryOrdering" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "MemoryOrdering" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype UnnamedAddr Source #

Constructors

UnnamedAddr CUInt 

Instances

Eq UnnamedAddr Source # 
Data UnnamedAddr Source # 

Methods

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

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

toConstr :: UnnamedAddr -> Constr #

dataTypeOf :: UnnamedAddr -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UnnamedAddr Source # 
Generic UnnamedAddr Source # 

Associated Types

type Rep UnnamedAddr :: * -> * #

type Rep UnnamedAddr Source # 
type Rep UnnamedAddr = D1 * (MetaData "UnnamedAddr" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "UnnamedAddr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype SynchronizationScope Source #

Instances

Eq SynchronizationScope Source # 
Data SynchronizationScope Source # 

Methods

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

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

toConstr :: SynchronizationScope -> Constr #

dataTypeOf :: SynchronizationScope -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SynchronizationScope Source # 
Generic SynchronizationScope Source # 
type Rep SynchronizationScope Source # 
type Rep SynchronizationScope = D1 * (MetaData "SynchronizationScope" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "SynchronizationScope" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype TailCallKind Source #

Constructors

TailCallKind CUInt 

Instances

Eq TailCallKind Source # 
Data TailCallKind Source # 

Methods

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

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

toConstr :: TailCallKind -> Constr #

dataTypeOf :: TailCallKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TailCallKind Source # 
Generic TailCallKind Source # 

Associated Types

type Rep TailCallKind :: * -> * #

type Rep TailCallKind Source # 
type Rep TailCallKind = D1 * (MetaData "TailCallKind" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "TailCallKind" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype Linkage Source #

Constructors

Linkage CUInt 

Instances

Eq Linkage Source # 

Methods

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

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

Data Linkage Source # 

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 :: (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 #

Read Linkage Source # 
Show Linkage Source # 
Generic Linkage Source # 

Associated Types

type Rep Linkage :: * -> * #

Methods

from :: Linkage -> Rep Linkage x #

to :: Rep Linkage x -> Linkage #

type Rep Linkage Source # 
type Rep Linkage = D1 * (MetaData "Linkage" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "Linkage" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype Visibility Source #

Constructors

Visibility CUInt 

Instances

Eq Visibility Source # 
Data Visibility Source # 

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 :: (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 #

Read Visibility Source # 
Show Visibility Source # 
Generic Visibility Source # 

Associated Types

type Rep Visibility :: * -> * #

type Rep Visibility Source # 
type Rep Visibility = D1 * (MetaData "Visibility" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "Visibility" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype COMDATSelectionKind Source #

Instances

Eq COMDATSelectionKind Source # 
Data COMDATSelectionKind Source # 

Methods

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

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

toConstr :: COMDATSelectionKind -> Constr #

dataTypeOf :: COMDATSelectionKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Read COMDATSelectionKind Source # 
Show COMDATSelectionKind Source # 
Generic COMDATSelectionKind Source # 
type Rep COMDATSelectionKind Source # 
type Rep COMDATSelectionKind = D1 * (MetaData "COMDATSelectionKind" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "COMDATSelectionKind" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype DLLStorageClass Source #

Constructors

DLLStorageClass CUInt 

Instances

Eq DLLStorageClass Source # 
Data DLLStorageClass Source # 

Methods

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

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

toConstr :: DLLStorageClass -> Constr #

dataTypeOf :: DLLStorageClass -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DLLStorageClass Source # 
Show DLLStorageClass Source # 
Generic DLLStorageClass Source # 
type Rep DLLStorageClass Source # 
type Rep DLLStorageClass = D1 * (MetaData "DLLStorageClass" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "DLLStorageClass" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype CallingConvention Source #

Constructors

CallingConvention CUInt 

Instances

Eq CallingConvention Source # 
Data CallingConvention Source # 

Methods

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

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

toConstr :: CallingConvention -> Constr #

dataTypeOf :: CallingConvention -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CallingConvention Source # 
Show CallingConvention Source # 
Generic CallingConvention Source # 
type Rep CallingConvention Source # 
type Rep CallingConvention = D1 * (MetaData "CallingConvention" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "CallingConvention" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype ThreadLocalMode Source #

Constructors

ThreadLocalMode CUInt 

Instances

Eq ThreadLocalMode Source # 
Data ThreadLocalMode Source # 

Methods

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

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

toConstr :: ThreadLocalMode -> Constr #

dataTypeOf :: ThreadLocalMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ThreadLocalMode Source # 
Show ThreadLocalMode Source # 
Generic ThreadLocalMode Source # 
type Rep ThreadLocalMode Source # 
type Rep ThreadLocalMode = D1 * (MetaData "ThreadLocalMode" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "ThreadLocalMode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype ValueSubclassId Source #

Constructors

ValueSubclassId CUInt 

Instances

Eq ValueSubclassId Source # 
Data ValueSubclassId Source # 

Methods

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

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

toConstr :: ValueSubclassId -> Constr #

dataTypeOf :: ValueSubclassId -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ValueSubclassId Source # 
Show ValueSubclassId Source # 
Generic ValueSubclassId Source # 
type Rep ValueSubclassId Source # 
type Rep ValueSubclassId = D1 * (MetaData "ValueSubclassId" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "ValueSubclassId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype DiagnosticKind Source #

Constructors

DiagnosticKind CUInt 

Instances

Eq DiagnosticKind Source # 
Data DiagnosticKind Source # 

Methods

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

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

toConstr :: DiagnosticKind -> Constr #

dataTypeOf :: DiagnosticKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DiagnosticKind Source # 
Show DiagnosticKind Source # 
Generic DiagnosticKind Source # 

Associated Types

type Rep DiagnosticKind :: * -> * #

type Rep DiagnosticKind Source # 
type Rep DiagnosticKind = D1 * (MetaData "DiagnosticKind" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "DiagnosticKind" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype AsmDialect Source #

Constructors

AsmDialect CUInt 

Instances

Eq AsmDialect Source # 
Data AsmDialect Source # 

Methods

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

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

toConstr :: AsmDialect -> Constr #

dataTypeOf :: AsmDialect -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AsmDialect Source # 
Show AsmDialect Source # 
Generic AsmDialect Source # 

Associated Types

type Rep AsmDialect :: * -> * #

type Rep AsmDialect Source # 
type Rep AsmDialect = D1 * (MetaData "AsmDialect" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "AsmDialect" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype RMWOperation Source #

Constructors

RMWOperation CUInt 

Instances

Eq RMWOperation Source # 
Data RMWOperation Source # 

Methods

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

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

toConstr :: RMWOperation -> Constr #

dataTypeOf :: RMWOperation -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RMWOperation Source # 
Show RMWOperation Source # 
Generic RMWOperation Source # 

Associated Types

type Rep RMWOperation :: * -> * #

type Rep RMWOperation Source # 
type Rep RMWOperation = D1 * (MetaData "RMWOperation" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "RMWOperation" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype RelocModel Source #

Constructors

RelocModel CUInt 

Instances

Eq RelocModel Source # 
Data RelocModel Source # 

Methods

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

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

toConstr :: RelocModel -> Constr #

dataTypeOf :: RelocModel -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RelocModel Source # 
Show RelocModel Source # 
Generic RelocModel Source # 

Associated Types

type Rep RelocModel :: * -> * #

type Rep RelocModel Source # 
type Rep RelocModel = D1 * (MetaData "RelocModel" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "RelocModel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype CodeModel Source #

Constructors

CodeModel CUInt 

Instances

Eq CodeModel Source # 
Data CodeModel Source # 

Methods

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

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

toConstr :: CodeModel -> Constr #

dataTypeOf :: CodeModel -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CodeModel Source # 
Show CodeModel Source # 
Generic CodeModel Source # 

Associated Types

type Rep CodeModel :: * -> * #

type Rep CodeModel Source # 
type Rep CodeModel = D1 * (MetaData "CodeModel" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "CodeModel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype CodeGenOptLevel Source #

Constructors

CodeGenOptLevel CUInt 

Instances

Eq CodeGenOptLevel Source # 
Data CodeGenOptLevel Source # 

Methods

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

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

toConstr :: CodeGenOptLevel -> Constr #

dataTypeOf :: CodeGenOptLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CodeGenOptLevel Source # 
Show CodeGenOptLevel Source # 
Generic CodeGenOptLevel Source # 
type Rep CodeGenOptLevel Source # 
type Rep CodeGenOptLevel = D1 * (MetaData "CodeGenOptLevel" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "CodeGenOptLevel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype CodeGenFileType Source #

Constructors

CodeGenFileType CUInt 

Instances

Eq CodeGenFileType Source # 
Data CodeGenFileType Source # 

Methods

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

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

toConstr :: CodeGenFileType -> Constr #

dataTypeOf :: CodeGenFileType -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CodeGenFileType Source # 
Show CodeGenFileType Source # 
Generic CodeGenFileType Source # 
type Rep CodeGenFileType Source # 
type Rep CodeGenFileType = D1 * (MetaData "CodeGenFileType" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "CodeGenFileType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype FloatABIType Source #

Constructors

FloatABIType CUInt 

Instances

Eq FloatABIType Source # 
Data FloatABIType Source # 

Methods

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

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

toConstr :: FloatABIType -> Constr #

dataTypeOf :: FloatABIType -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FloatABIType Source # 
Show FloatABIType Source # 
Generic FloatABIType Source # 

Associated Types

type Rep FloatABIType :: * -> * #

type Rep FloatABIType Source # 
type Rep FloatABIType = D1 * (MetaData "FloatABIType" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "FloatABIType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype FPOpFusionMode Source #

Constructors

FPOpFusionMode CUInt 

Instances

Eq FPOpFusionMode Source # 
Data FPOpFusionMode Source # 

Methods

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

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

toConstr :: FPOpFusionMode -> Constr #

dataTypeOf :: FPOpFusionMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FPOpFusionMode Source # 
Show FPOpFusionMode Source # 
Generic FPOpFusionMode Source # 

Associated Types

type Rep FPOpFusionMode :: * -> * #

type Rep FPOpFusionMode Source # 
type Rep FPOpFusionMode = D1 * (MetaData "FPOpFusionMode" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "FPOpFusionMode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype ThreadModel Source #

Constructors

ThreadModel CUInt 

Instances

Eq ThreadModel Source # 
Data ThreadModel Source # 

Methods

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

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

toConstr :: ThreadModel -> Constr #

dataTypeOf :: ThreadModel -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ThreadModel Source # 
Show ThreadModel Source # 
Generic ThreadModel Source # 

Associated Types

type Rep ThreadModel :: * -> * #

type Rep ThreadModel Source # 
type Rep ThreadModel = D1 * (MetaData "ThreadModel" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "ThreadModel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype EABI Source #

Constructors

EABI CUInt 

Instances

Eq EABI Source # 

Methods

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

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

Data EABI Source # 

Methods

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

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

toConstr :: EABI -> Constr #

dataTypeOf :: EABI -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EABI Source # 
Show EABI Source # 

Methods

showsPrec :: Int -> EABI -> ShowS #

show :: EABI -> String #

showList :: [EABI] -> ShowS #

Generic EABI Source # 

Associated Types

type Rep EABI :: * -> * #

Methods

from :: EABI -> Rep EABI x #

to :: Rep EABI x -> EABI #

type Rep EABI Source # 
type Rep EABI = D1 * (MetaData "EABI" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "EABI" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype DebuggerKind Source #

Constructors

DebuggerKind CUInt 

Instances

Eq DebuggerKind Source # 
Data DebuggerKind Source # 

Methods

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

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

toConstr :: DebuggerKind -> Constr #

dataTypeOf :: DebuggerKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DebuggerKind Source # 
Show DebuggerKind Source # 
Generic DebuggerKind Source # 

Associated Types

type Rep DebuggerKind :: * -> * #

type Rep DebuggerKind Source # 
type Rep DebuggerKind = D1 * (MetaData "DebuggerKind" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "DebuggerKind" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype FPDenormalMode Source #

Constructors

FPDenormalMode CUInt 

Instances

Eq FPDenormalMode Source # 
Data FPDenormalMode Source # 

Methods

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

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

toConstr :: FPDenormalMode -> Constr #

dataTypeOf :: FPDenormalMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FPDenormalMode Source # 
Show FPDenormalMode Source # 
Generic FPDenormalMode Source # 

Associated Types

type Rep FPDenormalMode :: * -> * #

type Rep FPDenormalMode Source # 
type Rep FPDenormalMode = D1 * (MetaData "FPDenormalMode" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "FPDenormalMode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype ExceptionHandling Source #

Constructors

ExceptionHandling CUInt 

Instances

Eq ExceptionHandling Source # 
Data ExceptionHandling Source # 

Methods

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

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

toConstr :: ExceptionHandling -> Constr #

dataTypeOf :: ExceptionHandling -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ExceptionHandling Source # 
Show ExceptionHandling Source # 
Generic ExceptionHandling Source # 
type Rep ExceptionHandling Source # 
type Rep ExceptionHandling = D1 * (MetaData "ExceptionHandling" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "ExceptionHandling" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype TargetOptionFlag Source #

Constructors

TargetOptionFlag CUInt 

Instances

Eq TargetOptionFlag Source # 
Data TargetOptionFlag Source # 

Methods

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

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

toConstr :: TargetOptionFlag -> Constr #

dataTypeOf :: TargetOptionFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TargetOptionFlag Source # 
Show TargetOptionFlag Source # 
Generic TargetOptionFlag Source # 
type Rep TargetOptionFlag Source # 
type Rep TargetOptionFlag = D1 * (MetaData "TargetOptionFlag" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "TargetOptionFlag" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype MCTargetOptionFlag Source #

Instances

Eq MCTargetOptionFlag Source # 
Data MCTargetOptionFlag Source # 

Methods

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

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

toConstr :: MCTargetOptionFlag -> Constr #

dataTypeOf :: MCTargetOptionFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MCTargetOptionFlag Source # 
Show MCTargetOptionFlag Source # 
Generic MCTargetOptionFlag Source # 
type Rep MCTargetOptionFlag Source # 
type Rep MCTargetOptionFlag = D1 * (MetaData "MCTargetOptionFlag" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "MCTargetOptionFlag" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype DebugCompressionType Source #

Instances

Eq DebugCompressionType Source # 
Data DebugCompressionType Source # 

Methods

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

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

toConstr :: DebugCompressionType -> Constr #

dataTypeOf :: DebugCompressionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DebugCompressionType Source # 
Show DebugCompressionType Source # 
Generic DebugCompressionType Source # 
type Rep DebugCompressionType Source # 
type Rep DebugCompressionType = D1 * (MetaData "DebugCompressionType" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "DebugCompressionType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype TypeKind Source #

Constructors

TypeKind CUInt 

Instances

Eq TypeKind Source # 
Data TypeKind Source # 

Methods

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

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

toConstr :: TypeKind -> Constr #

dataTypeOf :: TypeKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TypeKind Source # 
Show TypeKind Source # 
Generic TypeKind Source # 

Associated Types

type Rep TypeKind :: * -> * #

Methods

from :: TypeKind -> Rep TypeKind x #

to :: Rep TypeKind x -> TypeKind #

type Rep TypeKind Source # 
type Rep TypeKind = D1 * (MetaData "TypeKind" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "TypeKind" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype ParameterAttributeKind Source #

Instances

Eq ParameterAttributeKind Source # 
Data ParameterAttributeKind Source # 

Methods

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

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

toConstr :: ParameterAttributeKind -> Constr #

dataTypeOf :: ParameterAttributeKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ParameterAttributeKind Source # 
Show ParameterAttributeKind Source # 
Generic ParameterAttributeKind Source # 
type Rep ParameterAttributeKind Source # 
type Rep ParameterAttributeKind = D1 * (MetaData "ParameterAttributeKind" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "ParameterAttributeKind" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype FunctionAttributeKind Source #

Instances

Eq FunctionAttributeKind Source # 
Data FunctionAttributeKind Source # 

Methods

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

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

toConstr :: FunctionAttributeKind -> Constr #

dataTypeOf :: FunctionAttributeKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FunctionAttributeKind Source # 
Show FunctionAttributeKind Source # 
Generic FunctionAttributeKind Source # 
type Rep FunctionAttributeKind Source # 
type Rep FunctionAttributeKind = D1 * (MetaData "FunctionAttributeKind" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "FunctionAttributeKind" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype FloatSemantics Source #

Constructors

FloatSemantics CUInt 

Instances

Eq FloatSemantics Source # 
Data FloatSemantics Source # 

Methods

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

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

toConstr :: FloatSemantics -> Constr #

dataTypeOf :: FloatSemantics -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FloatSemantics Source # 
Show FloatSemantics Source # 
Generic FloatSemantics Source # 

Associated Types

type Rep FloatSemantics :: * -> * #

type Rep FloatSemantics Source # 
type Rep FloatSemantics = D1 * (MetaData "FloatSemantics" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "FloatSemantics" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype VerifierFailureAction Source #

Instances

Eq VerifierFailureAction Source # 
Data VerifierFailureAction Source # 

Methods

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

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

toConstr :: VerifierFailureAction -> Constr #

dataTypeOf :: VerifierFailureAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Num VerifierFailureAction Source # 
Read VerifierFailureAction Source # 
Show VerifierFailureAction Source # 
Generic VerifierFailureAction Source # 
Bits VerifierFailureAction Source # 
type Rep VerifierFailureAction Source # 
type Rep VerifierFailureAction = D1 * (MetaData "VerifierFailureAction" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "VerifierFailureAction" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype LibFunc Source #

Constructors

LibFunc CUInt 

Instances

Eq LibFunc Source # 

Methods

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

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

Data LibFunc Source # 

Methods

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

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

toConstr :: LibFunc -> Constr #

dataTypeOf :: LibFunc -> DataType #

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

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

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

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

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

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

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

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

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

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

Num LibFunc Source # 
Read LibFunc Source # 
Show LibFunc Source # 
Generic LibFunc Source # 

Associated Types

type Rep LibFunc :: * -> * #

Methods

from :: LibFunc -> Rep LibFunc x #

to :: Rep LibFunc x -> LibFunc #

Storable LibFunc Source # 
Bits LibFunc Source # 
Monad m => DecodeM m LibraryFunction LibFunc Source # 
Monad m => EncodeM m LibraryFunction LibFunc Source # 
type Rep LibFunc Source # 
type Rep LibFunc = D1 * (MetaData "LibFunc" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "LibFunc" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

newtype JITSymbolFlags Source #

Constructors

JITSymbolFlags CUInt 

Instances

Eq JITSymbolFlags Source # 
Data JITSymbolFlags Source # 

Methods

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

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

toConstr :: JITSymbolFlags -> Constr #

dataTypeOf :: JITSymbolFlags -> DataType #

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

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

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

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

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

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

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

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

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

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

Num JITSymbolFlags Source # 
Read JITSymbolFlags Source # 
Show JITSymbolFlags Source # 
Generic JITSymbolFlags Source # 

Associated Types

type Rep JITSymbolFlags :: * -> * #

Storable JITSymbolFlags Source # 
Bits JITSymbolFlags Source # 
Monad m => DecodeM m JITSymbolFlags JITSymbolFlags Source # 
Monad m => EncodeM m JITSymbolFlags JITSymbolFlags Source # 
type Rep JITSymbolFlags Source # 
type Rep JITSymbolFlags = D1 * (MetaData "JITSymbolFlags" "LLVM.Internal.FFI.LLVMCTypes" "llvm-hs-5.1.1-7Kptcc672C6DCDxaJ6lVWI" True) (C1 * (MetaCons "JITSymbolFlags" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CUInt)))

Orphan instances

Data CUInt Source # 

Methods

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

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

toConstr :: CUInt -> Constr #

dataTypeOf :: CUInt -> DataType #

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

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

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

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

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

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

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

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

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

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