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

Safe HaskellSafe
LanguageHaskell2010

LLVM.AST.Instruction

Description

Synopsis

Documentation

data Terminator Source #

Instances
Eq Terminator Source # 
Instance details

Defined in LLVM.AST.Instruction

Data Terminator Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

Show Terminator Source # 
Instance details

Defined in LLVM.AST.Instruction

Generic Terminator Source # 
Instance details

Defined in LLVM.AST.Instruction

Associated Types

type Rep Terminator :: * -> * #

type Rep Terminator Source # 
Instance details

Defined in LLVM.AST.Instruction

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

data FastMathFlags Source #

Instances
Eq FastMathFlags Source # 
Instance details

Defined in LLVM.AST.Instruction

Data FastMathFlags Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

Read FastMathFlags Source # 
Instance details

Defined in LLVM.AST.Instruction

Show FastMathFlags Source # 
Instance details

Defined in LLVM.AST.Instruction

Generic FastMathFlags Source # 
Instance details

Defined in LLVM.AST.Instruction

Associated Types

type Rep FastMathFlags :: * -> * #

type Rep FastMathFlags Source # 
Instance details

Defined in LLVM.AST.Instruction

data MemoryOrdering Source #

Instances
Eq MemoryOrdering Source # 
Instance details

Defined in LLVM.AST.Instruction

Data MemoryOrdering Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

Read MemoryOrdering Source # 
Instance details

Defined in LLVM.AST.Instruction

Show MemoryOrdering Source # 
Instance details

Defined in LLVM.AST.Instruction

Generic MemoryOrdering Source # 
Instance details

Defined in LLVM.AST.Instruction

Associated Types

type Rep MemoryOrdering :: * -> * #

type Rep MemoryOrdering Source # 
Instance details

Defined in LLVM.AST.Instruction

type Rep MemoryOrdering = D1 (MetaData "MemoryOrdering" "LLVM.AST.Instruction" "llvm-hs-pure-7.0.0-inplace" 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 # 
Instance details

Defined in LLVM.AST.Instruction

Data SynchronizationScope Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

Read SynchronizationScope Source # 
Instance details

Defined in LLVM.AST.Instruction

Show SynchronizationScope Source # 
Instance details

Defined in LLVM.AST.Instruction

Generic SynchronizationScope Source # 
Instance details

Defined in LLVM.AST.Instruction

Associated Types

type Rep SynchronizationScope :: * -> * #

type Rep SynchronizationScope Source # 
Instance details

Defined in LLVM.AST.Instruction

type Rep SynchronizationScope = D1 (MetaData "SynchronizationScope" "LLVM.AST.Instruction" "llvm-hs-pure-7.0.0-inplace" 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 # 
Instance details

Defined in LLVM.AST.Instruction

Data LandingPadClause Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

Read LandingPadClause Source # 
Instance details

Defined in LLVM.AST.Instruction

Show LandingPadClause Source # 
Instance details

Defined in LLVM.AST.Instruction

Generic LandingPadClause Source # 
Instance details

Defined in LLVM.AST.Instruction

Associated Types

type Rep LandingPadClause :: * -> * #

type Rep LandingPadClause Source # 
Instance details

Defined in LLVM.AST.Instruction

data TailCallKind Source #

Constructors

Tail 
MustTail 
NoTail 
Instances
Eq TailCallKind Source # 
Instance details

Defined in LLVM.AST.Instruction

Data TailCallKind Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

Read TailCallKind Source # 
Instance details

Defined in LLVM.AST.Instruction

Show TailCallKind Source # 
Instance details

Defined in LLVM.AST.Instruction

Generic TailCallKind Source # 
Instance details

Defined in LLVM.AST.Instruction

Associated Types

type Rep TailCallKind :: * -> * #

type Rep TailCallKind Source # 
Instance details

Defined in LLVM.AST.Instruction

type Rep TailCallKind = D1 (MetaData "TailCallKind" "LLVM.AST.Instruction" "llvm-hs-pure-7.0.0-inplace" 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 # 
Instance details

Defined in LLVM.AST.Instruction

Data Instruction Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

Show Instruction Source # 
Instance details

Defined in LLVM.AST.Instruction

Generic Instruction Source # 
Instance details

Defined in LLVM.AST.Instruction

Associated Types

type Rep Instruction :: * -> * #

type Rep Instruction Source # 
Instance details

Defined in LLVM.AST.Instruction

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

Defined in LLVM.AST.Instruction

Methods

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

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

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

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction

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

Defined in LLVM.AST.Instruction

Methods

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

show :: Named a -> String #

showList :: [Named a] -> ShowS #

Generic (Named a) Source # 
Instance details

Defined in LLVM.AST.Instruction

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 # 
Instance details

Defined in LLVM.AST.Instruction