llvm-hs-pure-5.1.0: Pure Haskell LLVM functionality (no FFI).

Safe HaskellSafe
LanguageHaskell98

LLVM.AST.Global

Description

Globals - top-level values in Modules - and supporting structures.

Synopsis

Documentation

data Global Source #

Instances

Eq Global Source # 

Methods

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

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

Data Global Source # 

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

Read Global Source # 
Show Global Source # 
Generic Global Source # 

Associated Types

type Rep Global :: * -> * #

Methods

from :: Global -> Rep Global x #

to :: Rep Global x -> Global #

type Rep Global Source # 
type Rep Global = D1 * (MetaData "Global" "LLVM.AST.Global" "llvm-hs-pure-5.1.0-ABIfIqE2ohGHl8oRFKMmj0" False) ((:+:) * (C1 * (MetaCons "GlobalVariable" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) ((:*:) * (S1 * (MetaSel (Just Symbol "linkage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Linkage)) (S1 * (MetaSel (Just Symbol "visibility") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Visibility)))) ((:*:) * (S1 * (MetaSel (Just Symbol "dllStorageClass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StorageClass))) ((:*:) * (S1 * (MetaSel (Just Symbol "threadLocalMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Model))) (S1 * (MetaSel (Just Symbol "unnamedAddr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe UnnamedAddr)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "isConstant") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "addrSpace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AddrSpace)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "initializer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Constant))) (S1 * (MetaSel (Just Symbol "section") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ShortByteString)))) ((:*:) * (S1 * (MetaSel (Just Symbol "comdat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ShortByteString))) (S1 * (MetaSel (Just Symbol "alignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32))))))) ((:+:) * (C1 * (MetaCons "GlobalAlias" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) (S1 * (MetaSel (Just Symbol "linkage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Linkage))) ((:*:) * (S1 * (MetaSel (Just Symbol "visibility") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Visibility)) (S1 * (MetaSel (Just Symbol "dllStorageClass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StorageClass))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "threadLocalMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Model))) (S1 * (MetaSel (Just Symbol "unnamedAddr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe UnnamedAddr)))) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) ((:*:) * (S1 * (MetaSel (Just Symbol "addrSpace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AddrSpace)) (S1 * (MetaSel (Just Symbol "aliasee") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))))) (C1 * (MetaCons "Function" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "linkage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Linkage)) (S1 * (MetaSel (Just Symbol "visibility") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Visibility))) ((:*:) * (S1 * (MetaSel (Just Symbol "dllStorageClass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe StorageClass))) (S1 * (MetaSel (Just Symbol "callingConvention") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CallingConvention)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "returnAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ParameterAttribute])) (S1 * (MetaSel (Just Symbol "returnType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type))) ((:*:) * (S1 * (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) (S1 * (MetaSel (Just Symbol "parameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ([Parameter], Bool)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "functionAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Either GroupID FunctionAttribute])) (S1 * (MetaSel (Just Symbol "section") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ShortByteString)))) ((:*:) * (S1 * (MetaSel (Just Symbol "comdat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ShortByteString))) (S1 * (MetaSel (Just Symbol "alignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "garbageCollectorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ShortByteString))) (S1 * (MetaSel (Just Symbol "prefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Constant)))) ((:*:) * (S1 * (MetaSel (Just Symbol "basicBlocks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [BasicBlock])) (S1 * (MetaSel (Just Symbol "personalityFunction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Constant))))))))))

data Parameter Source #

Instances

Eq Parameter Source # 
Data Parameter Source # 

Methods

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

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

toConstr :: Parameter -> Constr #

dataTypeOf :: Parameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Parameter Source # 
Show Parameter Source # 
Generic Parameter Source # 

Associated Types

type Rep Parameter :: * -> * #

type Rep Parameter Source # 

data BasicBlock Source #

http://llvm.org/doxygen/classllvm_1_1BasicBlock.html LLVM code in a function is a sequence of BasicBlocks each with a label, some instructions, and a terminator.

Instances

Eq BasicBlock Source # 
Data BasicBlock Source # 

Methods

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

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

toConstr :: BasicBlock -> Constr #

dataTypeOf :: BasicBlock -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BasicBlock Source # 
Show BasicBlock Source # 
Generic BasicBlock Source # 

Associated Types

type Rep BasicBlock :: * -> * #

type Rep BasicBlock Source # 

data UnnamedAddr Source #

Constructors

LocalAddr 
GlobalAddr 

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 #

Read UnnamedAddr Source # 
Show UnnamedAddr Source # 
Generic UnnamedAddr Source # 

Associated Types

type Rep UnnamedAddr :: * -> * #

type Rep UnnamedAddr Source # 
type Rep UnnamedAddr = D1 * (MetaData "UnnamedAddr" "LLVM.AST.Global" "llvm-hs-pure-5.1.0-ABIfIqE2ohGHl8oRFKMmj0" False) ((:+:) * (C1 * (MetaCons "LocalAddr" PrefixI False) (U1 *)) (C1 * (MetaCons "GlobalAddr" PrefixI False) (U1 *)))

functionDefaults :: Global Source #

helper for making Functions