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

Safe HaskellSafe
LanguageHaskell98

LLVM.AST.Instruction

Description

Synopsis

Documentation

data Terminator Source #

Instances

Eq Terminator Source # 
Data Terminator Source # 

Methods

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

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

toConstr :: Terminator -> Constr #

dataTypeOf :: Terminator -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Terminator Source # 
Show Terminator Source # 
Generic Terminator Source # 

Associated Types

type Rep Terminator :: * -> * #

type Rep Terminator Source # 
type Rep Terminator = D1 * (MetaData "Terminator" "LLVM.AST.Instruction" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Ret" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "returnOperand") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Operand))) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))) (C1 * (MetaCons "CondBr" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "condition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "trueDest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name))) ((:*:) * (S1 * (MetaSel (Just Symbol "falseDest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) ((:+:) * (C1 * (MetaCons "Br" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "dest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))) ((:+:) * (C1 * (MetaCons "Switch" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "operand0'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "defaultDest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name))) ((:*:) * (S1 * (MetaSel (Just Symbol "dests") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(Constant, Name)])) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "IndirectBr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "possibleDests") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Name])) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Invoke" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "callingConvention'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CallingConvention)) (S1 * (MetaSel (Just Symbol "returnAttributes'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ParameterAttribute]))) ((:*:) * (S1 * (MetaSel (Just Symbol "function'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CallableOperand)) (S1 * (MetaSel (Just Symbol "arguments'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(Operand, [ParameterAttribute])])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "functionAttributes'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Either GroupID FunctionAttribute])) (S1 * (MetaSel (Just Symbol "returnDest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name))) ((:*:) * (S1 * (MetaSel (Just Symbol "exceptionDest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) ((:+:) * (C1 * (MetaCons "Resume" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))) (C1 * (MetaCons "Unreachable" PrefixI True) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "CleanupRet" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "cleanupPad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "unwindDest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Name))) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "CatchRet" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "catchPad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "successor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "CatchSwitch" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "parentPad'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "catchHandlers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty Name)))) ((:*:) * (S1 * (MetaSel (Just Symbol "defaultUnwindDest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Name))) (S1 * (MetaSel (Just Symbol "metadata'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))))

data FastMathFlags Source #

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 #

Ord FastMathFlags Source # 
Read FastMathFlags Source # 
Show FastMathFlags Source # 
Generic FastMathFlags Source # 

Associated Types

type Rep FastMathFlags :: * -> * #

type Rep FastMathFlags Source # 
type Rep FastMathFlags = D1 * (MetaData "FastMathFlags" "LLVM.AST.Instruction" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * (C1 * (MetaCons "NoFastMathFlags" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UnsafeAlgebra" PrefixI False) (U1 *)) (C1 * (MetaCons "FastMathFlags" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "noNaNs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "noInfs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "noSignedZeros") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "allowReciprocal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))))

data MemoryOrdering Source #

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 #

Ord MemoryOrdering Source # 
Read MemoryOrdering Source # 
Show MemoryOrdering Source # 
Generic MemoryOrdering Source # 

Associated Types

type Rep MemoryOrdering :: * -> * #

type Rep MemoryOrdering Source # 
type Rep MemoryOrdering = D1 * (MetaData "MemoryOrdering" "LLVM.AST.Instruction" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Unordered" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Monotonic" PrefixI False) (U1 *)) (C1 * (MetaCons "Acquire" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Release" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AcquireRelease" PrefixI False) (U1 *)) (C1 * (MetaCons "SequentiallyConsistent" PrefixI False) (U1 *)))))

data SynchronizationScope Source #

Constructors

SingleThread 
System 

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 #

Ord SynchronizationScope Source # 
Read SynchronizationScope Source # 
Show SynchronizationScope Source # 
Generic SynchronizationScope Source # 
type Rep SynchronizationScope Source # 
type Rep SynchronizationScope = D1 * (MetaData "SynchronizationScope" "LLVM.AST.Instruction" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * (C1 * (MetaCons "SingleThread" PrefixI False) (U1 *)) (C1 * (MetaCons "System" PrefixI False) (U1 *)))

type Atomicity = (SynchronizationScope, MemoryOrdering) Source #

An Atomicity describes constraints on the visibility of effects of an atomic instruction

data LandingPadClause Source #

For the redoubtably complex LandingPad instruction

Constructors

Catch Constant 
Filter Constant 

Instances

Eq LandingPadClause Source # 
Data LandingPadClause Source # 

Methods

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

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

toConstr :: LandingPadClause -> Constr #

dataTypeOf :: LandingPadClause -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LandingPadClause Source # 
Read LandingPadClause Source # 
Show LandingPadClause Source # 
Generic LandingPadClause Source # 
type Rep LandingPadClause Source # 
type Rep LandingPadClause = D1 * (MetaData "LandingPadClause" "LLVM.AST.Instruction" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * (C1 * (MetaCons "Catch" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))) (C1 * (MetaCons "Filter" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))

data TailCallKind Source #

Constructors

Tail 
MustTail 
NoTail 

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 #

Ord TailCallKind Source # 
Read TailCallKind Source # 
Show TailCallKind Source # 
Generic TailCallKind Source # 

Associated Types

type Rep TailCallKind :: * -> * #

type Rep TailCallKind Source # 
type Rep TailCallKind = D1 * (MetaData "TailCallKind" "LLVM.AST.Instruction" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * (C1 * (MetaCons "Tail" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MustTail" PrefixI False) (U1 *)) (C1 * (MetaCons "NoTail" PrefixI False) (U1 *))))

data Instruction Source #

Constructors

Add 
FAdd 
Sub 
FSub 
Mul 
FMul 
UDiv 
SDiv 
FDiv 
URem 
SRem 
FRem 
Shl 
LShr 
AShr 
And 
Or 
Xor 
Alloca 
Load 
Store 
GetElementPtr 
Fence 
CmpXchg 
AtomicRMW 
Trunc 
ZExt 
SExt 
FPToUI 
FPToSI 
UIToFP 
SIToFP 
FPTrunc 
FPExt 
PtrToInt 
IntToPtr 
BitCast 
AddrSpaceCast 
ICmp 
FCmp 
Phi 
Call 
Select 
VAArg 
ExtractElement 
InsertElement 
ShuffleVector 
ExtractValue 
InsertValue 
LandingPad 
CatchPad 
CleanupPad 

Instances

Eq Instruction Source # 
Data Instruction Source # 

Methods

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

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

toConstr :: Instruction -> Constr #

dataTypeOf :: Instruction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Instruction Source # 
Show Instruction Source # 
Generic Instruction Source # 

Associated Types

type Rep Instruction :: * -> * #

type Rep Instruction Source # 
type Rep Instruction = D1 * (MetaData "Instruction" "LLVM.AST.Instruction" "llvm-hs-pure-5.1.1-A50TaxGLKsoFnCqinrVaVN" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Add" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) ((:+:) * (C1 * (MetaCons "FAdd" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fastMathFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FastMathFlags)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "Sub" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))) ((:+:) * (C1 * (MetaCons "FSub" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fastMathFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FastMathFlags)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "Mul" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) (C1 * (MetaCons "FMul" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fastMathFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FastMathFlags)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "UDiv" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "SDiv" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "FDiv" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fastMathFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FastMathFlags)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "URem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "SRem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) ((:+:) * (C1 * (MetaCons "FRem" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fastMathFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FastMathFlags)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "Shl" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "LShr" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "AShr" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "And" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))) ((:+:) * (C1 * (MetaCons "Or" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "Xor" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "Alloca" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "allocatedType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "numElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Operand)))) ((:*:) * (S1 * (MetaSel (Just Symbol "alignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Load" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "volatile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "address") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "maybeAtomicity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Atomicity))) ((:*:) * (S1 * (MetaSel (Just Symbol "alignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) ((:+:) * (C1 * (MetaCons "Store" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "volatile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "address") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)))) ((:*:) * (S1 * (MetaSel (Just Symbol "maybeAtomicity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Atomicity))) ((:*:) * (S1 * (MetaSel (Just Symbol "alignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) (C1 * (MetaCons "GetElementPtr" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "inBounds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "address") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "indices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Operand])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Fence" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "atomicity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Atomicity)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))) (C1 * (MetaCons "CmpXchg" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "volatile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "address") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "expected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "replacement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "atomicity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Atomicity))) ((:*:) * (S1 * (MetaSel (Just Symbol "failureMemoryOrdering") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MemoryOrdering)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))) ((:+:) * (C1 * (MetaCons "AtomicRMW" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "volatile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "rmwOperation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RMWOperation)) (S1 * (MetaSel (Just Symbol "address") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)))) ((:*:) * (S1 * (MetaSel (Just Symbol "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "atomicity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Atomicity)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) (C1 * (MetaCons "Trunc" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ZExt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "SExt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "FPToUI" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))) ((:+:) * (C1 * (MetaCons "FPToSI" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "UIToFP" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "SIToFP" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "FPTrunc" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "FPExt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "PtrToInt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "IntToPtr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "BitCast" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) ((:+:) * (C1 * (MetaCons "AddrSpaceCast" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "ICmp" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "iPredicate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IntegerPredicate)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "FCmp" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fpPredicate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FloatingPointPredicate)) (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "Phi" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) ((:*:) * (S1 * (MetaSel (Just Symbol "incomingValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(Operand, Name)])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "Call" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tailCallKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TailCallKind))) ((:*:) * (S1 * (MetaSel (Just Symbol "callingConvention") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CallingConvention)) (S1 * (MetaSel (Just Symbol "returnAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ParameterAttribute])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "function") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CallableOperand)) (S1 * (MetaSel (Just Symbol "arguments") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(Operand, [ParameterAttribute])]))) ((:*:) * (S1 * (MetaSel (Just Symbol "functionAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Either GroupID FunctionAttribute])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))) ((:+:) * (C1 * (MetaCons "Select" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "condition'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "trueValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "falseValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "VAArg" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "argList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "ExtractElement" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "vector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "index") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "InsertElement" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "vector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "element") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "index") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) ((:+:) * (C1 * (MetaCons "ShuffleVector" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "mask") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "ExtractValue" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aggregate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "indices'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Word32])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "InsertValue" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "aggregate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) (S1 * (MetaSel (Just Symbol "element") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand))) ((:*:) * (S1 * (MetaSel (Just Symbol "indices'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Word32])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "LandingPad" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "cleanup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "clauses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LandingPadClause])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))) ((:+:) * (C1 * (MetaCons "CatchPad" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "catchSwitch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "args") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Operand])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata))))) (C1 * (MetaCons "CleanupPad" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "parentPad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Operand)) ((:*:) * (S1 * (MetaSel (Just Symbol "args") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Operand])) (S1 * (MetaSel (Just Symbol "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * InstructionMetadata)))))))))))

data Named a Source #

Instances of instructions may be given a name, allowing their results to be referenced as Operands. Sometimes instructions - e.g. a call to a function returning void - don't need names.

Constructors

Name := a 
Do a 

Instances

Eq a => Eq (Named a) Source # 

Methods

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

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

Data a => Data (Named a) Source # 

Methods

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

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

toConstr :: Named a -> Constr #

dataTypeOf :: Named a -> DataType #

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

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

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

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

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

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

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

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

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

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

Read a => Read (Named a) Source # 
Show a => Show (Named a) Source # 

Methods

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

show :: Named a -> String #

showList :: [Named a] -> ShowS #

Generic (Named a) Source # 

Associated Types

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

Methods

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

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

type Rep (Named a) Source #