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

Safe HaskellSafe
LanguageHaskell98

LLVM.AST.Operand

Description

A type to represent operands to LLVM Instructions

Synopsis

Documentation

newtype MetadataNodeID Source #

A MetadataNodeID is a number for identifying a metadata node. Note this is different from "named metadata", which are represented with NamedMetadataDefinition.

Constructors

MetadataNodeID Word 

Instances

Eq MetadataNodeID Source # 
Data MetadataNodeID Source # 

Methods

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

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

toConstr :: MetadataNodeID -> Constr #

dataTypeOf :: MetadataNodeID -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MetadataNodeID Source # 
Read MetadataNodeID Source # 
Show MetadataNodeID Source # 
Generic MetadataNodeID Source # 

Associated Types

type Rep MetadataNodeID :: * -> * #

type Rep MetadataNodeID Source # 
type Rep MetadataNodeID = D1 * (MetaData "MetadataNodeID" "LLVM.AST.Operand" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" True) (C1 * (MetaCons "MetadataNodeID" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word)))

data MetadataNode Source #

Instances

Eq MetadataNode Source # 
Data MetadataNode Source # 

Methods

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

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

toConstr :: MetadataNode -> Constr #

dataTypeOf :: MetadataNode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MetadataNode Source # 
Read MetadataNode Source # 
Show MetadataNode Source # 
Generic MetadataNode Source # 

Associated Types

type Rep MetadataNode :: * -> * #

type Rep MetadataNode Source # 
type Rep MetadataNode = D1 * (MetaData "MetadataNode" "LLVM.AST.Operand" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * (C1 * (MetaCons "MetadataNode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Maybe Metadata]))) (C1 * (MetaCons "MetadataNodeReference" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MetadataNodeID))))

data Metadata Source #

Instances

Eq Metadata Source # 
Data Metadata Source # 

Methods

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

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

toConstr :: Metadata -> Constr #

dataTypeOf :: Metadata -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Metadata Source # 
Read Metadata Source # 
Show Metadata Source # 
Generic Metadata Source # 

Associated Types

type Rep Metadata :: * -> * #

Methods

from :: Metadata -> Rep Metadata x #

to :: Rep Metadata x -> Metadata #

type Rep Metadata Source # 

data Operand Source #

An Operand is roughly that which is an argument to an Instruction

Instances

Eq Operand Source # 

Methods

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

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

Data Operand Source # 

Methods

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

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

toConstr :: Operand -> Constr #

dataTypeOf :: Operand -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Operand Source # 
Read Operand Source # 
Show Operand Source # 
Generic Operand Source # 

Associated Types

type Rep Operand :: * -> * #

Methods

from :: Operand -> Rep Operand x #

to :: Rep Operand x -> Operand #

Typed CallableOperand Source # 
Typed Operand Source # 

Methods

typeOf :: Operand -> Type Source #

type Rep Operand Source # 

type CallableOperand = Either InlineAssembly Operand Source #

The Call instruction is special: the callee can be inline assembly