{-# LINE 1 "src/LLVM/Internal/FFI/InstructionDefs.hsc" #-}
-- This module translates the instruction data in "llvm/Instruction.def" into a Haskell data structure,
-- so it may be accessed conveniently with Template Haskell code
module LLVM.Internal.FFI.InstructionDefs where

import LLVM.Prelude

import LLVM.Internal.FFI.LLVMCTypes









data InstructionKind = Terminator | Binary | Memory | Cast | FuncletPad | Other
  deriving (InstructionKind -> InstructionKind -> Bool
(InstructionKind -> InstructionKind -> Bool)
-> (InstructionKind -> InstructionKind -> Bool)
-> Eq InstructionKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstructionKind -> InstructionKind -> Bool
$c/= :: InstructionKind -> InstructionKind -> Bool
== :: InstructionKind -> InstructionKind -> Bool
$c== :: InstructionKind -> InstructionKind -> Bool
Eq, Eq InstructionKind
Eq InstructionKind =>
(InstructionKind -> InstructionKind -> Ordering)
-> (InstructionKind -> InstructionKind -> Bool)
-> (InstructionKind -> InstructionKind -> Bool)
-> (InstructionKind -> InstructionKind -> Bool)
-> (InstructionKind -> InstructionKind -> Bool)
-> (InstructionKind -> InstructionKind -> InstructionKind)
-> (InstructionKind -> InstructionKind -> InstructionKind)
-> Ord InstructionKind
InstructionKind -> InstructionKind -> Bool
InstructionKind -> InstructionKind -> Ordering
InstructionKind -> InstructionKind -> InstructionKind
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InstructionKind -> InstructionKind -> InstructionKind
$cmin :: InstructionKind -> InstructionKind -> InstructionKind
max :: InstructionKind -> InstructionKind -> InstructionKind
$cmax :: InstructionKind -> InstructionKind -> InstructionKind
>= :: InstructionKind -> InstructionKind -> Bool
$c>= :: InstructionKind -> InstructionKind -> Bool
> :: InstructionKind -> InstructionKind -> Bool
$c> :: InstructionKind -> InstructionKind -> Bool
<= :: InstructionKind -> InstructionKind -> Bool
$c<= :: InstructionKind -> InstructionKind -> Bool
< :: InstructionKind -> InstructionKind -> Bool
$c< :: InstructionKind -> InstructionKind -> Bool
compare :: InstructionKind -> InstructionKind -> Ordering
$ccompare :: InstructionKind -> InstructionKind -> Ordering
$cp1Ord :: Eq InstructionKind
Ord, Int -> InstructionKind -> ShowS
[InstructionKind] -> ShowS
InstructionKind -> String
(Int -> InstructionKind -> ShowS)
-> (InstructionKind -> String)
-> ([InstructionKind] -> ShowS)
-> Show InstructionKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstructionKind] -> ShowS
$cshowList :: [InstructionKind] -> ShowS
show :: InstructionKind -> String
$cshow :: InstructionKind -> String
showsPrec :: Int -> InstructionKind -> ShowS
$cshowsPrec :: Int -> InstructionKind -> ShowS
Show)

data InstructionDef = InstructionDef {
    InstructionDef -> CPPOpcode
cppOpcode :: CPPOpcode,
    InstructionDef -> String
cAPIName :: String,
    InstructionDef -> String
cAPIClassName :: String,
    InstructionDef -> InstructionKind
instructionKind :: InstructionKind
  }
  deriving (InstructionDef -> InstructionDef -> Bool
(InstructionDef -> InstructionDef -> Bool)
-> (InstructionDef -> InstructionDef -> Bool) -> Eq InstructionDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstructionDef -> InstructionDef -> Bool
$c/= :: InstructionDef -> InstructionDef -> Bool
== :: InstructionDef -> InstructionDef -> Bool
$c== :: InstructionDef -> InstructionDef -> Bool
Eq, Eq InstructionDef
Eq InstructionDef =>
(InstructionDef -> InstructionDef -> Ordering)
-> (InstructionDef -> InstructionDef -> Bool)
-> (InstructionDef -> InstructionDef -> Bool)
-> (InstructionDef -> InstructionDef -> Bool)
-> (InstructionDef -> InstructionDef -> Bool)
-> (InstructionDef -> InstructionDef -> InstructionDef)
-> (InstructionDef -> InstructionDef -> InstructionDef)
-> Ord InstructionDef
InstructionDef -> InstructionDef -> Bool
InstructionDef -> InstructionDef -> Ordering
InstructionDef -> InstructionDef -> InstructionDef
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InstructionDef -> InstructionDef -> InstructionDef
$cmin :: InstructionDef -> InstructionDef -> InstructionDef
max :: InstructionDef -> InstructionDef -> InstructionDef
$cmax :: InstructionDef -> InstructionDef -> InstructionDef
>= :: InstructionDef -> InstructionDef -> Bool
$c>= :: InstructionDef -> InstructionDef -> Bool
> :: InstructionDef -> InstructionDef -> Bool
$c> :: InstructionDef -> InstructionDef -> Bool
<= :: InstructionDef -> InstructionDef -> Bool
$c<= :: InstructionDef -> InstructionDef -> Bool
< :: InstructionDef -> InstructionDef -> Bool
$c< :: InstructionDef -> InstructionDef -> Bool
compare :: InstructionDef -> InstructionDef -> Ordering
$ccompare :: InstructionDef -> InstructionDef -> Ordering
$cp1Ord :: Eq InstructionDef
Ord, Int -> InstructionDef -> ShowS
[InstructionDef] -> ShowS
InstructionDef -> String
(Int -> InstructionDef -> ShowS)
-> (InstructionDef -> String)
-> ([InstructionDef] -> ShowS)
-> Show InstructionDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstructionDef] -> ShowS
$cshowList :: [InstructionDef] -> ShowS
show :: InstructionDef -> String
$cshow :: InstructionDef -> String
showsPrec :: Int -> InstructionDef -> ShowS
$cshowsPrec :: Int -> InstructionDef -> ShowS
Show)

instructionDefs :: [InstructionDef]
instructionDefs :: [InstructionDef]
instructionDefs = [ 
 CPPOpcode -> String -> String -> InstructionKind -> InstructionDef
InstructionDef CPPOpcode
o String
an String
acn InstructionKind
k
 | (o, an, acn :: String
acn, k :: InstructionKind
k) <-
   [ (CPPOpcode 1,"Ret","ReturnInst", Terminator)
   , (CPPOpcode 2,"Br","BranchInst", Terminator)
   , (CPPOpcode 3,"Switch","SwitchInst", Terminator)
   , (CPPOpcode 4,"IndirectBr","IndirectBrInst", Terminator)
   , (CPPOpcode 5,"Invoke","InvokeInst", Terminator)
   , (CPPOpcode 6,"Resume","ResumeInst", Terminator)
   , (CPPOpcode 7,"Unreachable","UnreachableInst", Terminator)
   , (CPPOpcode 8,"CleanupRet","CleanupReturnInst", Terminator)
   , (CPPOpcode 9,"CatchRet","CatchReturnInst", Terminator)
   , (CPPOpcode 10,"CatchSwitch","CatchSwitchInst", Terminator)
   , (CPPOpcode 11,"CallBr","CallBrInst", Terminator)
   , (CPPOpcode 12,"FNeg","UnaryOperator", Terminator)
   , (CPPOpcode 13,"Add","BinaryOperator", Binary)
   , (CPPOpcode 14,"FAdd","BinaryOperator", Binary)
   , (CPPOpcode 15,"Sub","BinaryOperator", Binary)
   , (CPPOpcode 16,"FSub","BinaryOperator", Binary)
   , (CPPOpcode 17,"Mul","BinaryOperator", Binary)
   , (CPPOpcode 18,"FMul","BinaryOperator", Binary)
   , (CPPOpcode 19,"UDiv","BinaryOperator", Binary)
   , (CPPOpcode 20,"SDiv","BinaryOperator", Binary)
   , (CPPOpcode 21,"FDiv","BinaryOperator", Binary)
   , (CPPOpcode 22,"URem","BinaryOperator", Binary)
   , (CPPOpcode 23,"SRem","BinaryOperator", Binary)
   , (CPPOpcode 24,"FRem","BinaryOperator", Binary)
   , (CPPOpcode 25,"Shl","BinaryOperator", Binary)
   , (CPPOpcode 26,"LShr","BinaryOperator", Binary)
   , (CPPOpcode 27,"AShr","BinaryOperator", Binary)
   , (CPPOpcode 28,"And","BinaryOperator", Binary)
   , (CUInt -> CPPOpcode
CPPOpcode 29,"Or","BinaryOperator", InstructionKind
Binary)
   , (CUInt -> CPPOpcode
CPPOpcode 30,"Xor","BinaryOperator", InstructionKind
Binary)
   , (CUInt -> CPPOpcode
CPPOpcode 31,"Alloca","AllocaInst", InstructionKind
Memory)
   , (CUInt -> CPPOpcode
CPPOpcode 32,"Load","LoadInst", InstructionKind
Memory)
   , (CUInt -> CPPOpcode
CPPOpcode 33,"Store","StoreInst", InstructionKind
Memory)
   , (CUInt -> CPPOpcode
CPPOpcode 34,"GetElementPtr","GetElementPtrInst", InstructionKind
Memory)
   , (CUInt -> CPPOpcode
CPPOpcode 35,"Fence","FenceInst", InstructionKind
Memory)
   , (CUInt -> CPPOpcode
CPPOpcode 36,"AtomicCmpXchg","AtomicCmpXchgInst", InstructionKind
Memory)
   , (CUInt -> CPPOpcode
CPPOpcode 37,"AtomicRMW","AtomicRMWInst", InstructionKind
Memory)
   , (CUInt -> CPPOpcode
CPPOpcode 38,"Trunc","TruncInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 39,"ZExt","ZExtInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 40,"SExt","SExtInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 41,"FPToUI","FPToUIInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 42,"FPToSI","FPToSIInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 43,"UIToFP","UIToFPInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 44,"SIToFP","SIToFPInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 45,"FPTrunc","FPTruncInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 46,"FPExt","FPExtInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 47,"PtrToInt","PtrToIntInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 48,"IntToPtr","IntToPtrInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 49,"BitCast","BitCastInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 50,"AddrSpaceCast","AddrSpaceCastInst", InstructionKind
Cast)
   , (CUInt -> CPPOpcode
CPPOpcode 51,"CleanupPad","CleanupPadInst", InstructionKind
FuncletPad)
   , (CUInt -> CPPOpcode
CPPOpcode 52,"CatchPad","CatchPadInst", InstructionKind
FuncletPad)
   , (CUInt -> CPPOpcode
CPPOpcode 53,"ICmp","ICmpInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 54,"FCmp","FCmpInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 55,"PHI","PHINode", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 56,"Call","CallInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 57,"Select","SelectInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 58,"UserOp1","Instruction", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 59,"UserOp2","Instruction", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 60,"VAArg","VAArgInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 61,"ExtractElement","ExtractElementInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 62,"InsertElement","InsertElementInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 63,"ShuffleVector","ShuffleVectorInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 64,"ExtractValue","ExtractValueInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 65,"InsertValue","InsertValueInst", InstructionKind
Other)
   , (CUInt -> CPPOpcode
CPPOpcode 66,"LandingPad","LandingPadInst", InstructionKind
Other) ] ,
{-# LINE 59 "src/LLVM/Internal/FFI/InstructionDefs.hsc" #-}
 an /= "UserOp1" && an /= "UserOp2"
 ]