{-# OPTIONS_GHC -optc-DCOMMA=, #-}
{-# OPTIONS_GHC -optc-DOR_TT=T #-}
{-# OPTIONS_GHC -optc-DOR_TF=T #-}
{-# OPTIONS_GHC -optc-DOR_FT=T #-}
{-# OPTIONS_GHC -optc-DOR_FF=F #-}
{-# LINE 1 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}
{-# LANGUAGE
  GeneralizedNewtypeDeriving,
  PatternSynonyms
  #-}
-- | Define types which correspond cleanly with some simple types on the C/C++ side.
-- Encapsulate hsc macro weirdness here, supporting higher-level tricks elsewhere.
module LLVM.Internal.FFI.LLVMCTypes where

import LLVM.Prelude


{-# LINE 14 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}




















import Language.Haskell.TH.Quote

import Data.Bits
import Foreign.C
import Foreign.Storable






pattern DwOp_LLVM_fragment :: Word64
pattern $bDwOp_LLVM_fragment :: Word64
$mDwOp_LLVM_fragment :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_LLVM_fragment =   4096
pattern DwOp_stack_value :: Word64
pattern $bDwOp_stack_value :: Word64
$mDwOp_stack_value :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_stack_value =   159
pattern DwOp_swap :: Word64
pattern $bDwOp_swap :: Word64
$mDwOp_swap :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_swap =   22
pattern DwOp_constu :: Word64
pattern $bDwOp_constu :: Word64
$mDwOp_constu :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_constu =   16
pattern DwOp_lit0 :: Word64
pattern $bDwOp_lit0 :: Word64
$mDwOp_lit0 :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_lit0 =   48
pattern DwOp_plus_uconst :: Word64
pattern $bDwOp_plus_uconst :: Word64
$mDwOp_plus_uconst :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_plus_uconst =   35
pattern DwOp_plus :: Word64
pattern $bDwOp_plus :: Word64
$mDwOp_plus :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_plus =   34
pattern DwOp_minus :: Word64
pattern $bDwOp_minus :: Word64
$mDwOp_minus :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_minus =   28
pattern DwOp_mul :: Word64
pattern $bDwOp_mul :: Word64
$mDwOp_mul :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_mul =   30
pattern DwOp_div :: Word64
pattern $bDwOp_div :: Word64
$mDwOp_div :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_div =   27
pattern DwOp_mod :: Word64
pattern $bDwOp_mod :: Word64
$mDwOp_mod :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_mod =   29
pattern DwOp_not :: Word64
pattern $bDwOp_not :: Word64
$mDwOp_not :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_not =   32
pattern DwOp_or :: Word64
pattern $bDwOp_or :: Word64
$mDwOp_or :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_or =   33
pattern DwOp_xor :: Word64
pattern $bDwOp_xor :: Word64
$mDwOp_xor :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_xor =   39
pattern DwOp_and :: Word64
pattern $bDwOp_and :: Word64
$mDwOp_and :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_and =   26
pattern DwOp_shr :: Word64
pattern DwOp_shr =   37
pattern DwOp_shra :: Word64
pattern $bDwOp_shra :: Word64
$mDwOp_shra :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_shra =   38
pattern DwOp_shl :: Word64
pattern $bDwOp_shl :: Word64
$mDwOp_shl :: forall r. Word64 -> (Void# -> r) -> (Void# -> r) -> r
DwOp_shl =   36
pattern DwOp_dup :: Word64
pattern DwOp_dup =   18
pattern DwOp_deref :: Word64
pattern DwOp_deref =   6
pattern DwOp_xderef :: Word64
pattern DwOp_xderef =   24

{-# LINE 74 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype Encoding = Encoding CUInt
  deriving (Data, Show)


pattern DwAtE_address :: Encoding
pattern DwAtE_address =  Encoding 1
pattern DwAtE_boolean :: Encoding
pattern DwAtE_boolean =  Encoding 2
pattern DwAtE_complex_float :: Encoding
pattern DwAtE_complex_float =  Encoding 3
pattern DwAtE_float :: Encoding
pattern DwAtE_float =  Encoding 4
pattern DwAtE_signed :: Encoding
pattern DwAtE_signed =  Encoding 5
pattern DwAtE_signed_char :: Encoding
pattern $bDwAtE_signed_char :: Encoding
$mDwAtE_signed_char :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_signed_char =  Encoding 6
pattern DwAtE_unsigned :: Encoding
pattern $bDwAtE_unsigned :: Encoding
$mDwAtE_unsigned :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_unsigned =  Encoding 7
pattern DwAtE_unsigned_char :: Encoding
pattern $bDwAtE_unsigned_char :: Encoding
$mDwAtE_unsigned_char :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_unsigned_char =  Encoding 8
pattern DwAtE_imaginary_float :: Encoding
pattern $bDwAtE_imaginary_float :: Encoding
$mDwAtE_imaginary_float :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_imaginary_float =  Encoding 9
pattern DwAtE_packed_decimal :: Encoding
pattern $bDwAtE_packed_decimal :: Encoding
$mDwAtE_packed_decimal :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_packed_decimal =  Encoding 10
pattern DwAtE_numeric_string :: Encoding
pattern $bDwAtE_numeric_string :: Encoding
$mDwAtE_numeric_string :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_numeric_string =  Encoding 11
pattern DwAtE_edited :: Encoding
pattern $bDwAtE_edited :: Encoding
$mDwAtE_edited :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_edited =  Encoding 12
pattern DwAtE_signed_fixed :: Encoding
pattern $bDwAtE_signed_fixed :: Encoding
$mDwAtE_signed_fixed :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_signed_fixed =  Encoding 13
pattern DwAtE_unsigned_fixed :: Encoding
pattern $bDwAtE_unsigned_fixed :: Encoding
$mDwAtE_unsigned_fixed :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_unsigned_fixed =  Encoding 14
pattern DwAtE_decimal_float :: Encoding
pattern $bDwAtE_decimal_float :: Encoding
$mDwAtE_decimal_float :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_decimal_float =  Encoding 15
pattern DwAtE_UTF :: Encoding
pattern $bDwAtE_UTF :: Encoding
$mDwAtE_UTF :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_UTF =  Encoding 16
pattern DwAtE_UCS :: Encoding
pattern $bDwAtE_UCS :: Encoding
$mDwAtE_UCS :: forall r. Encoding -> (Void# -> r) -> (Void# -> r) -> r
DwAtE_UCS =  Encoding 17
pattern DwAtE_ASCII :: Encoding
pattern DwAtE_ASCII =  Encoding 18

{-# LINE 80 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype DwTag = DwTag Word16
  deriving (Data, Show)


pattern DwTag_imported_module :: DwTag
pattern DwTag_imported_module =  DwTag 58
pattern DwTag_imported_declaration :: DwTag
pattern DwTag_imported_declaration =  DwTag 8
pattern DwTag_typedef :: DwTag
pattern DwTag_typedef =  DwTag 22
pattern DwTag_pointer_type :: DwTag
pattern DwTag_pointer_type =  DwTag 15
pattern DwTag_ptr_to_member_type :: DwTag
pattern DwTag_ptr_to_member_type =  DwTag 31
pattern DwTag_reference_type :: DwTag
pattern DwTag_reference_type =  DwTag 16
pattern DwTag_rvalue_reference_type :: DwTag
pattern DwTag_rvalue_reference_type =  DwTag 66
pattern DwTag_const_type :: DwTag
pattern DwTag_const_type =  DwTag 38
pattern DwTag_volatile_type :: DwTag
pattern DwTag_volatile_type =  DwTag 53
pattern DwTag_restrict_type :: DwTag
pattern DwTag_restrict_type =  DwTag 55
pattern DwTag_atomic_type :: DwTag
pattern DwTag_atomic_type =  DwTag 71
pattern DwTag_member :: DwTag
pattern DwTag_member =  DwTag 13
pattern DwTag_inheritance :: DwTag
pattern DwTag_inheritance =  DwTag 28
pattern DwTag_friend :: DwTag
pattern DwTag_friend =  DwTag 42
pattern DwTag_base_type :: DwTag
pattern DwTag_base_type =  DwTag 36
pattern DwTag_unspecified_type :: DwTag
pattern DwTag_unspecified_type =  DwTag 59
pattern DwTag_template_value_parameter :: DwTag
pattern DwTag_template_value_parameter =  DwTag 48
pattern DwTag_GNU_template_template_param :: DwTag
pattern DwTag_GNU_template_template_param =  DwTag 16646
pattern DwTag_GNU_template_parameter_pack :: DwTag
pattern DwTag_GNU_template_parameter_pack =  DwTag 16647
pattern DwTag_array_type :: DwTag
pattern DwTag_array_type =  DwTag 1
pattern DwTag_enumeration_type :: DwTag
pattern DwTag_enumeration_type =  DwTag 4
pattern DwTag_structure_type :: DwTag
pattern DwTag_structure_type =  DwTag 19
pattern DwTag_class_type :: DwTag
pattern DwTag_class_type =  DwTag 2
pattern DwTag_union_type :: DwTag
pattern DwTag_union_type =  DwTag 23

{-# LINE 86 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype DwVirtuality = DwVirtuality Word8
  deriving (Data, Show)


pattern DwVirtuality_none :: DwVirtuality
pattern DwVirtuality_none =  DwVirtuality 0
pattern DwVirtuality_virtual :: DwVirtuality
pattern DwVirtuality_virtual =  DwVirtuality 1
pattern DwVirtuality_pure_virtual :: DwVirtuality
pattern DwVirtuality_pure_virtual =  DwVirtuality 2

{-# LINE 92 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

deriving instance Data CUInt

newtype LLVMBool = LLVMBool CUInt

-- | If an FFI function returns a value wrapped in 'OwnerTransfered',
-- this value needs to be freed after it has been processed. Usually
-- this is done automatically in the 'DecodeM' instance.
newtype OwnerTransfered a = OwnerTransfered a
  deriving (Eq, Storable)

newtype NothingAsMinusOne h = NothingAsMinusOne CInt
  deriving (Storable)

newtype NothingAsEmptyString c = NothingAsEmptyString c
  deriving (Storable)

newtype CPPOpcode = CPPOpcode CUInt
  deriving (Eq, Ord, Show, Typeable, Data, Generic)

newtype ICmpPredicate = ICmpPredicate CUInt
  deriving (Eq, Ord, Show, Typeable, Data, Generic)
iCmpPredEQ  :: ICmpPredicate
iCmpPredEQ  = ICmpPredicate 32
iCmpPredNE  :: ICmpPredicate
iCmpPredNE  = ICmpPredicate 33
iCmpPredUGT  :: ICmpPredicate
iCmpPredUGT  = ICmpPredicate 34
iCmpPredUGE  :: ICmpPredicate
iCmpPredUGE  = ICmpPredicate 35
iCmpPredULT  :: ICmpPredicate
iCmpPredULT  = ICmpPredicate 36
iCmpPredULE  :: ICmpPredicate
iCmpPredULE  = ICmpPredicate 37
iCmpPredSGT  :: ICmpPredicate
iCmpPredSGT  = ICmpPredicate 38
iCmpPredSGE  :: ICmpPredicate
iCmpPredSGE  = ICmpPredicate 39
iCmpPredSLT  :: ICmpPredicate
iCmpPredSLT  = ICmpPredicate 40
iCmpPredSLE  :: ICmpPredicate
iCmpPredSLE  = ICmpPredicate 41

{-# LINE 126 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype FCmpPredicate = FCmpPredicate CUInt
  deriving (Eq, Ord, Show, Typeable, Data, Generic)
fCmpPredFalse  :: FCmpPredicate
fCmpPredFalse  = FCmpPredicate 0
fCmpPredOEQ  :: FCmpPredicate
fCmpPredOEQ  = FCmpPredicate 1
fCmpPredOGT  :: FCmpPredicate
fCmpPredOGT  = FCmpPredicate 2
fCmpPredOGE  :: FCmpPredicate
fCmpPredOGE :: FCmpPredicate
fCmpPredOGE  = CUInt -> FCmpPredicate
FCmpPredicate 3
fCmpPredOLT  :: FCmpPredicate
fCmpPredOLT :: FCmpPredicate
fCmpPredOLT  = CUInt -> FCmpPredicate
FCmpPredicate 4
fCmpPredOLE  :: FCmpPredicate
fCmpPredOLE :: FCmpPredicate
fCmpPredOLE  = CUInt -> FCmpPredicate
FCmpPredicate 5
fCmpPredONE  :: FCmpPredicate
fCmpPredONE :: FCmpPredicate
fCmpPredONE  = CUInt -> FCmpPredicate
FCmpPredicate 6
fCmpPredORD  :: FCmpPredicate
fCmpPredORD :: FCmpPredicate
fCmpPredORD  = CUInt -> FCmpPredicate
FCmpPredicate 7
fCmpPredUNO  :: FCmpPredicate
fCmpPredUNO :: FCmpPredicate
fCmpPredUNO  = CUInt -> FCmpPredicate
FCmpPredicate 8
fCmpPredUEQ  :: FCmpPredicate
fCmpPredUEQ :: FCmpPredicate
fCmpPredUEQ  = CUInt -> FCmpPredicate
FCmpPredicate 9
fCmpPredUGT  :: FCmpPredicate
fCmpPredUGT :: FCmpPredicate
fCmpPredUGT  = CUInt -> FCmpPredicate
FCmpPredicate 10
fCmpPredUGE  :: FCmpPredicate
fCmpPredUGE :: FCmpPredicate
fCmpPredUGE  = CUInt -> FCmpPredicate
FCmpPredicate 11
fCmpPredULT  :: FCmpPredicate
fCmpPredULT :: FCmpPredicate
fCmpPredULT  = FCmpPredicate 12
fCmpPredULE  :: FCmpPredicate
fCmpPredULE :: FCmpPredicate
fCmpPredULE  = FCmpPredicate 13
fCmpPredUNE  :: FCmpPredicate
fCmpPredUNE :: FCmpPredicate
fCmpPredUNE  = FCmpPredicate 14
fcmpPredTrue  :: FCmpPredicate
fcmpPredTrue :: FCmpPredicate
fcmpPredTrue  = CUInt -> FCmpPredicate
FCmpPredicate 15

{-# LINE 147 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype MDKindID = MDKindID CUInt
  deriving (Storable)

newtype MDSubclassID = MDSubclassID CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

mdSubclassIdMDString :: MDSubclassID
mdSubclassIdMDString = MDSubclassID 0
mdSubclassIdConstantAsMetadata :: MDSubclassID
mdSubclassIdConstantAsMetadata = MDSubclassID 1
mdSubclassIdLocalAsMetadata :: MDSubclassID
mdSubclassIdLocalAsMetadata = MDSubclassID 2
mdSubclassIdDistinctMDOperandPlaceholder :: MDSubclassID
mdSubclassIdDistinctMDOperandPlaceholder = MDSubclassID 3
mdSubclassIdMDTuple :: MDSubclassID
mdSubclassIdMDTuple :: MDSubclassID
mdSubclassIdMDTuple = CUInt -> MDSubclassID
MDSubclassID 4
mdSubclassIdDILocation :: MDSubclassID
mdSubclassIdDILocation :: MDSubclassID
mdSubclassIdDILocation = MDSubclassID 5
mdSubclassIdDIExpression :: MDSubclassID
mdSubclassIdDIExpression :: MDSubclassID
mdSubclassIdDIExpression = MDSubclassID 6
mdSubclassIdDIGlobalVariableExpression :: MDSubclassID
mdSubclassIdDIGlobalVariableExpression :: MDSubclassID
mdSubclassIdDIGlobalVariableExpression = CUInt -> MDSubclassID
MDSubclassID 7
mdSubclassIdGenericDINode :: MDSubclassID
mdSubclassIdGenericDINode :: MDSubclassID
mdSubclassIdGenericDINode = MDSubclassID 8
mdSubclassIdDISubrange :: MDSubclassID
mdSubclassIdDISubrange :: MDSubclassID
mdSubclassIdDISubrange = CUInt -> MDSubclassID
MDSubclassID 9
mdSubclassIdDIEnumerator :: MDSubclassID
mdSubclassIdDIEnumerator :: MDSubclassID
mdSubclassIdDIEnumerator = CUInt -> MDSubclassID
MDSubclassID 10
mdSubclassIdDIBasicType :: MDSubclassID
mdSubclassIdDIBasicType = MDSubclassID 11
mdSubclassIdDIDerivedType :: MDSubclassID
mdSubclassIdDIDerivedType = MDSubclassID 12
mdSubclassIdDICompositeType :: MDSubclassID
mdSubclassIdDICompositeType = MDSubclassID 13
mdSubclassIdDISubroutineType :: MDSubclassID
mdSubclassIdDISubroutineType :: MDSubclassID
mdSubclassIdDISubroutineType = CUInt -> MDSubclassID
MDSubclassID 14
mdSubclassIdDIFile :: MDSubclassID
mdSubclassIdDIFile = MDSubclassID 15
mdSubclassIdDICompileUnit :: MDSubclassID
mdSubclassIdDICompileUnit = MDSubclassID 16
mdSubclassIdDISubprogram :: MDSubclassID
mdSubclassIdDISubprogram :: MDSubclassID
mdSubclassIdDISubprogram = CUInt -> MDSubclassID
MDSubclassID 17
mdSubclassIdDILexicalBlock :: MDSubclassID
mdSubclassIdDILexicalBlock :: MDSubclassID
mdSubclassIdDILexicalBlock = CUInt -> MDSubclassID
MDSubclassID 18
mdSubclassIdDILexicalBlockFile :: MDSubclassID
mdSubclassIdDILexicalBlockFile :: MDSubclassID
mdSubclassIdDILexicalBlockFile = CUInt -> MDSubclassID
MDSubclassID 19
mdSubclassIdDINamespace :: MDSubclassID
mdSubclassIdDINamespace :: MDSubclassID
mdSubclassIdDINamespace = CUInt -> MDSubclassID
MDSubclassID 20
mdSubclassIdDIModule :: MDSubclassID
mdSubclassIdDIModule :: MDSubclassID
mdSubclassIdDIModule = CUInt -> MDSubclassID
MDSubclassID 21
mdSubclassIdDITemplateTypeParameter :: MDSubclassID
mdSubclassIdDITemplateTypeParameter = MDSubclassID 22
mdSubclassIdDITemplateValueParameter :: MDSubclassID
mdSubclassIdDITemplateValueParameter = MDSubclassID 23
mdSubclassIdDIGlobalVariable :: MDSubclassID
mdSubclassIdDIGlobalVariable :: MDSubclassID
mdSubclassIdDIGlobalVariable = CUInt -> MDSubclassID
MDSubclassID 24
mdSubclassIdDILocalVariable :: MDSubclassID
mdSubclassIdDILocalVariable = MDSubclassID 25
mdSubclassIdDIObjCProperty :: MDSubclassID
mdSubclassIdDIObjCProperty = MDSubclassID 27
mdSubclassIdDIImportedEntity :: MDSubclassID
mdSubclassIdDIImportedEntity = MDSubclassID 28
mdSubclassIdDIMacro :: MDSubclassID
mdSubclassIdDIMacro = MDSubclassID 29
mdSubclassIdDIMacroFile :: MDSubclassID
mdSubclassIdDIMacroFile = MDSubclassID 30
mdSubclassIdP :: QuasiQuoter
mdSubclassIdP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "MDString" -> mdSubclassIdMDString
    "ConstantAsMetadata" -> mdSubclassIdConstantAsMetadata
    "LocalAsMetadata" -> mdSubclassIdLocalAsMetadata
    "DistinctMDOperandPlaceholder" -> mdSubclassIdDistinctMDOperandPlaceholder
    "MDTuple" -> mdSubclassIdMDTuple
    "DILocation" -> mdSubclassIdDILocation
    "DIExpression" -> mdSubclassIdDIExpression
    "DIGlobalVariableExpression" -> mdSubclassIdDIGlobalVariableExpression
    "GenericDINode" -> mdSubclassIdGenericDINode
    "DISubrange" -> mdSubclassIdDISubrange
    "DIEnumerator" -> mdSubclassIdDIEnumerator
    "DIBasicType" -> mdSubclassIdDIBasicType
    "DIDerivedType" -> mdSubclassIdDIDerivedType
    "DICompositeType" -> mdSubclassIdDICompositeType
    "DISubroutineType" -> mdSubclassIdDISubroutineType
    "DIFile" -> mdSubclassIdDIFile
    "DICompileUnit" -> mdSubclassIdDICompileUnit
    "DISubprogram" -> mdSubclassIdDISubprogram
    "DILexicalBlock" -> mdSubclassIdDILexicalBlock
    "DILexicalBlockFile" -> mdSubclassIdDILexicalBlockFile
    "DINamespace" -> mdSubclassIdDINamespace
    "DIModule" -> mdSubclassIdDIModule
    "DITemplateTypeParameter" -> mdSubclassIdDITemplateTypeParameter
    "DITemplateValueParameter" -> mdSubclassIdDITemplateValueParameter
    "DIGlobalVariable" -> mdSubclassIdDIGlobalVariable
    "DILocalVariable" -> mdSubclassIdDILocalVariable
    "DIObjCProperty" -> mdSubclassIdDIObjCProperty
    "DIImportedEntity" -> mdSubclassIdDIImportedEntity
    "DIMacro" -> mdSubclassIdDIMacro
    "DIMacroFile" -> mdSubclassIdDIMacroFile
    x -> error $ "bad quasiquoted FFI constant for mdSubclassId: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 155 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype FastMathFlags = FastMathFlags CUInt
  deriving (Eq, Ord, Show, Typeable, Data, Num, Bits, Generic)

fastMathFlagsAllowReassoc :: FastMathFlags
fastMathFlagsAllowReassoc = FastMathFlags 1
fastMathFlagsNoNaNs :: FastMathFlags
fastMathFlagsNoNaNs = FastMathFlags 2
fastMathFlagsNoInfs :: FastMathFlags
fastMathFlagsNoInfs = FastMathFlags 4
fastMathFlagsNoSignedZeros :: FastMathFlags
fastMathFlagsNoSignedZeros = FastMathFlags 8
fastMathFlagsAllowReciprocal :: FastMathFlags
fastMathFlagsAllowReciprocal = FastMathFlags 16
fastMathFlagsAllowContract :: FastMathFlags
fastMathFlagsAllowContract = FastMathFlags 32
fastMathFlagsApproxFunc :: FastMathFlags
fastMathFlagsApproxFunc = FastMathFlags 64
fastMathFlagsP :: QuasiQuoter
fastMathFlagsP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "AllowReassoc" -> fastMathFlagsAllowReassoc
    "NoNaNs" -> fastMathFlagsNoNaNs
    "NoInfs" -> fastMathFlagsNoInfs
    "NoSignedZeros" -> fastMathFlagsNoSignedZeros
    "AllowReciprocal" -> fastMathFlagsAllowReciprocal
    "AllowContract" -> fastMathFlagsAllowContract
    "ApproxFunc" -> fastMathFlagsApproxFunc
    x -> error $ "bad quasiquoted FFI constant for fastMathFlags: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 160 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype MemoryOrdering = MemoryOrdering CUInt
  deriving (Eq, Show, Typeable, Data, Generic)

memoryOrderingNotAtomic :: MemoryOrdering
memoryOrderingNotAtomic = MemoryOrdering 0
memoryOrderingUnordered :: MemoryOrdering
memoryOrderingUnordered = MemoryOrdering 1
memoryOrderingMonotonic :: MemoryOrdering
memoryOrderingMonotonic = MemoryOrdering 2
memoryOrderingAcquire :: MemoryOrdering
memoryOrderingAcquire = MemoryOrdering 4
memoryOrderingRelease :: MemoryOrdering
memoryOrderingRelease = MemoryOrdering 5
memoryOrderingAcquireRelease :: MemoryOrdering
memoryOrderingAcquireRelease = MemoryOrdering 6
memoryOrderingSequentiallyConsistent :: MemoryOrdering
memoryOrderingSequentiallyConsistent = MemoryOrdering 7
memoryOrderingP :: QuasiQuoter
memoryOrderingP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "NotAtomic" -> memoryOrderingNotAtomic
    "Unordered" -> memoryOrderingUnordered
    "Monotonic" -> memoryOrderingMonotonic
    "Acquire" -> memoryOrderingAcquire
    "Release" -> memoryOrderingRelease
    "AcquireRelease" -> memoryOrderingAcquireRelease
    "SequentiallyConsistent" -> memoryOrderingSequentiallyConsistent
    x -> error $ "bad quasiquoted FFI constant for memoryOrdering: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 165 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype UnnamedAddr = UnnamedAddr CUInt
  deriving (Eq, Show, Typeable, Data, Generic)

unnamedAddrNo :: UnnamedAddr
unnamedAddrNo = UnnamedAddr 0
unnamedAddrLocal :: UnnamedAddr
unnamedAddrLocal = UnnamedAddr 1
unnamedAddrGlobal :: UnnamedAddr
unnamedAddrGlobal = UnnamedAddr 2
unnamedAddrP :: QuasiQuoter
unnamedAddrP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "No" -> unnamedAddrNo
    "Local" -> unnamedAddrLocal
    "Global" -> unnamedAddrGlobal
    x -> error $ "bad quasiquoted FFI constant for unnamedAddr: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 170 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype SynchronizationScope = SynchronizationScope CUInt
  deriving (Eq, Show, Typeable, Data, Generic)

synchronizationScopeSingleThread :: SynchronizationScope
synchronizationScopeSingleThread = SynchronizationScope 0
synchronizationScopeSystem :: SynchronizationScope
synchronizationScopeSystem = SynchronizationScope 1
synchronizationScopeP :: QuasiQuoter
synchronizationScopeP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "SingleThread" -> synchronizationScopeSingleThread
    "System" -> synchronizationScopeSystem
    x -> error $ "bad quasiquoted FFI constant for synchronizationScope: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 175 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype TailCallKind = TailCallKind CUInt
  deriving (Eq, Show, Typeable, Data, Generic)

tailCallKindNone :: TailCallKind
tailCallKindNone = TailCallKind 0
tailCallKindTail :: TailCallKind
tailCallKindTail = TailCallKind 1
tailCallKindMustTail :: TailCallKind
tailCallKindMustTail = TailCallKind 2
tailCallKindNoTail :: TailCallKind
tailCallKindNoTail = TailCallKind 3
tailCallKindP :: QuasiQuoter
tailCallKindP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "None" -> tailCallKindNone
    "Tail" -> tailCallKindTail
    "MustTail" -> tailCallKindMustTail
    "NoTail" -> tailCallKindNoTail
    x -> error $ "bad quasiquoted FFI constant for tailCallKind: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 180 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype Linkage = Linkage CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

linkageExternal :: Linkage
linkageExternal = Linkage 0
linkageAvailableExternally :: Linkage
linkageAvailableExternally = Linkage 1
linkageLinkOnceAny :: Linkage
linkageLinkOnceAny = Linkage 2
linkageLinkOnceODR :: Linkage
linkageLinkOnceODR = Linkage 3
linkageWeakAny :: Linkage
linkageWeakAny = Linkage 5
linkageWeakODR :: Linkage
linkageWeakODR = Linkage 6
linkageAppending :: Linkage
linkageAppending = Linkage 7
linkageInternal :: Linkage
linkageInternal = Linkage 8
linkagePrivate :: Linkage
linkagePrivate = Linkage 9
linkageExternalWeak :: Linkage
linkageExternalWeak = Linkage 12
linkageCommon :: Linkage
linkageCommon = Linkage 14
linkageP :: QuasiQuoter
linkageP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "External" -> linkageExternal
    "AvailableExternally" -> linkageAvailableExternally
    "LinkOnceAny" -> linkageLinkOnceAny
    "LinkOnceODR" -> linkageLinkOnceODR
    "WeakAny" -> linkageWeakAny
    "WeakODR" -> linkageWeakODR
    "Appending" -> linkageAppending
    "Internal" -> linkageInternal
    "Private" -> linkagePrivate
    "ExternalWeak" -> linkageExternalWeak
    "Common" -> linkageCommon
    x -> error $ "bad quasiquoted FFI constant for linkage: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 185 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype Visibility = Visibility CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

visibilityDefault :: Visibility
visibilityDefault = Visibility 0
visibilityHidden :: Visibility
visibilityHidden = Visibility 1
visibilityProtected :: Visibility
visibilityProtected = Visibility 2
visibilityP :: QuasiQuoter
visibilityP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Default" -> visibilityDefault
    "Hidden" -> visibilityHidden
    "Protected" -> visibilityProtected
    x -> error $ "bad quasiquoted FFI constant for visibility: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 190 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype COMDATSelectionKind = COMDATSelectionKind CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

comdatSelectionKindAny :: COMDATSelectionKind
comdatSelectionKindAny = COMDATSelectionKind 0
comdatSelectionKindExactMatch :: COMDATSelectionKind
comdatSelectionKindExactMatch = COMDATSelectionKind 1
comdatSelectionKindLargest :: COMDATSelectionKind
comdatSelectionKindLargest = COMDATSelectionKind 2
comdatSelectionKindNoDuplicates :: COMDATSelectionKind
comdatSelectionKindNoDuplicates = COMDATSelectionKind 3
comdatSelectionKindSameSize :: COMDATSelectionKind
comdatSelectionKindSameSize = COMDATSelectionKind 4
comdatSelectionKindP :: QuasiQuoter
comdatSelectionKindP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Any" -> comdatSelectionKindAny
    "ExactMatch" -> comdatSelectionKindExactMatch
    "Largest" -> comdatSelectionKindLargest
    "NoDuplicates" -> comdatSelectionKindNoDuplicates
    "SameSize" -> comdatSelectionKindSameSize
    x -> error $ "bad quasiquoted FFI constant for comdatSelectionKind: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 195 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype DLLStorageClass = DLLStorageClass CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

dllStorageClassDefault :: DLLStorageClass
dllStorageClassDefault = DLLStorageClass 0
dllStorageClassDLLImport :: DLLStorageClass
dllStorageClassDLLImport = DLLStorageClass 1
dllStorageClassDLLExport :: DLLStorageClass
dllStorageClassDLLExport = DLLStorageClass 2
dllStorageClassP :: QuasiQuoter
dllStorageClassP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Default" -> dllStorageClassDefault
    "DLLImport" -> dllStorageClassDLLImport
    "DLLExport" -> dllStorageClassDLLExport
    x -> error $ "bad quasiquoted FFI constant for dllStorageClass: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 200 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype CallingConvention = CallingConvention CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

callingConventionC :: CallingConvention
callingConventionC = CallingConvention 0
callingConventionFast :: CallingConvention
callingConventionFast = CallingConvention 8
callingConventionCold :: CallingConvention
callingConventionCold = CallingConvention 9
callingConventionGHC :: CallingConvention
callingConventionGHC = CallingConvention 10
callingConventionHiPE :: CallingConvention
callingConventionHiPE = CallingConvention 11
callingConventionWebKit_JS :: CallingConvention
callingConventionWebKit_JS = CallingConvention 12
callingConventionAnyReg :: CallingConvention
callingConventionAnyReg = CallingConvention 13
callingConventionPreserveMost :: CallingConvention
callingConventionPreserveMost = CallingConvention 14
callingConventionPreserveAll :: CallingConvention
callingConventionPreserveAll = CallingConvention 15
callingConventionSwift :: CallingConvention
callingConventionSwift = CallingConvention 16
callingConventionCXX_FAST_TLS :: CallingConvention
callingConventionCXX_FAST_TLS = CallingConvention 17
callingConventionX86_StdCall :: CallingConvention
callingConventionX86_StdCall = CallingConvention 64
callingConventionX86_FastCall :: CallingConvention
callingConventionX86_FastCall = CallingConvention 65
callingConventionARM_APCS :: CallingConvention
callingConventionARM_APCS = CallingConvention 66
callingConventionARM_AAPCS :: CallingConvention
callingConventionARM_AAPCS = CallingConvention 67
callingConventionARM_AAPCS_VFP :: CallingConvention
callingConventionARM_AAPCS_VFP = CallingConvention 68
callingConventionMSP430_INTR :: CallingConvention
callingConventionMSP430_INTR = CallingConvention 69
callingConventionX86_ThisCall :: CallingConvention
callingConventionX86_ThisCall = CallingConvention 70
callingConventionPTX_Kernel :: CallingConvention
callingConventionPTX_Kernel = CallingConvention 71
callingConventionPTX_Device :: CallingConvention
callingConventionPTX_Device = CallingConvention 72
callingConventionSPIR_FUNC :: CallingConvention
callingConventionSPIR_FUNC = CallingConvention 75
callingConventionSPIR_KERNEL :: CallingConvention
callingConventionSPIR_KERNEL = CallingConvention 76
callingConventionIntel_OCL_BI :: CallingConvention
callingConventionIntel_OCL_BI = CallingConvention 77
callingConventionX86_64_SysV :: CallingConvention
callingConventionX86_64_SysV = CallingConvention 78
callingConventionWin64 :: CallingConvention
callingConventionWin64 = CallingConvention 79
callingConventionX86_VectorCall :: CallingConvention
callingConventionX86_VectorCall = CallingConvention 80
callingConventionHHVM :: CallingConvention
callingConventionHHVM = CallingConvention 81
callingConventionHHVM_C :: CallingConvention
callingConventionHHVM_C = CallingConvention 82
callingConventionX86_INTR :: CallingConvention
callingConventionX86_INTR = CallingConvention 83
callingConventionAVR_INTR :: CallingConvention
callingConventionAVR_INTR = CallingConvention 84
callingConventionAVR_SIGNAL :: CallingConvention
callingConventionAVR_SIGNAL = CallingConvention 85
callingConventionAVR_BUILTIN :: CallingConvention
callingConventionAVR_BUILTIN = CallingConvention 86
callingConventionAMDGPU_VS :: CallingConvention
callingConventionAMDGPU_VS = CallingConvention 87
callingConventionAMDGPU_GS :: CallingConvention
callingConventionAMDGPU_GS :: CallingConvention
callingConventionAMDGPU_GS = CUInt -> CallingConvention
CallingConvention 88
callingConventionAMDGPU_PS :: CallingConvention
callingConventionAMDGPU_PS :: CallingConvention
callingConventionAMDGPU_PS = CUInt -> CallingConvention
CallingConvention 89
callingConventionAMDGPU_CS :: CallingConvention
callingConventionAMDGPU_CS = CallingConvention 90
callingConventionAMDGPU_KERNEL :: CallingConvention
callingConventionAMDGPU_KERNEL = CallingConvention 91
callingConventionX86_RegCall :: CallingConvention
callingConventionX86_RegCall :: CallingConvention
callingConventionX86_RegCall = CUInt -> CallingConvention
CallingConvention 92
callingConventionAMDGPU_HS :: CallingConvention
callingConventionAMDGPU_HS :: CallingConvention
callingConventionAMDGPU_HS = CallingConvention 93
callingConventionMSP430_BUILTIN :: CallingConvention
callingConventionMSP430_BUILTIN :: CallingConvention
callingConventionMSP430_BUILTIN = CUInt -> CallingConvention
CallingConvention 94
callingConventionP :: QuasiQuoter
callingConventionP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "C" -> callingConventionC
    "Fast" -> callingConventionFast
    "Cold" -> callingConventionCold
    "GHC" -> callingConventionGHC
    "HiPE" -> callingConventionHiPE
    "WebKit_JS" -> callingConventionWebKit_JS
    "AnyReg" -> callingConventionAnyReg
    "PreserveMost" -> callingConventionPreserveMost
    "PreserveAll" -> callingConventionPreserveAll
    "Swift" -> callingConventionSwift
    "CXX_FAST_TLS" -> callingConventionCXX_FAST_TLS
    "X86_StdCall" -> callingConventionX86_StdCall
    "X86_FastCall" -> callingConventionX86_FastCall
    "ARM_APCS" -> callingConventionARM_APCS
    "ARM_AAPCS" -> callingConventionARM_AAPCS
    "ARM_AAPCS_VFP" -> callingConventionARM_AAPCS_VFP
    "MSP430_INTR" -> callingConventionMSP430_INTR
    "X86_ThisCall" -> callingConventionX86_ThisCall
    "PTX_Kernel" -> callingConventionPTX_Kernel
    "PTX_Device" -> callingConventionPTX_Device
    "SPIR_FUNC" -> callingConventionSPIR_FUNC
    "SPIR_KERNEL" -> callingConventionSPIR_KERNEL
    "Intel_OCL_BI" -> callingConventionIntel_OCL_BI
    "X86_64_SysV" -> callingConventionX86_64_SysV
    "Win64" -> callingConventionWin64
    "X86_VectorCall" -> callingConventionX86_VectorCall
    "HHVM" -> callingConventionHHVM
    "HHVM_C" -> callingConventionHHVM_C
    "X86_INTR" -> callingConventionX86_INTR
    "AVR_INTR" -> callingConventionAVR_INTR
    "AVR_SIGNAL" -> callingConventionAVR_SIGNAL
    "AVR_BUILTIN" -> callingConventionAVR_BUILTIN
    "AMDGPU_VS" -> callingConventionAMDGPU_VS
    "AMDGPU_GS" -> callingConventionAMDGPU_GS
    "AMDGPU_PS" -> callingConventionAMDGPU_PS
    "AMDGPU_CS" -> callingConventionAMDGPU_CS
    "AMDGPU_KERNEL" -> callingConventionAMDGPU_KERNEL
    "X86_RegCall" -> callingConventionX86_RegCall
    "AMDGPU_HS" -> callingConventionAMDGPU_HS
    "MSP430_BUILTIN" -> callingConventionMSP430_BUILTIN
    x -> error $ "bad quasiquoted FFI constant for callingConvention: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 205 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype ThreadLocalMode = ThreadLocalMode CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

threadLocalModeNotThreadLocal :: ThreadLocalMode
threadLocalModeNotThreadLocal = ThreadLocalMode 0
threadLocalModeGeneralDynamicTLSModel :: ThreadLocalMode
threadLocalModeGeneralDynamicTLSModel = ThreadLocalMode 1
threadLocalModeLocalDynamicTLSModel :: ThreadLocalMode
threadLocalModeLocalDynamicTLSModel = ThreadLocalMode 2
threadLocalModeInitialExecTLSModel :: ThreadLocalMode
threadLocalModeInitialExecTLSModel = ThreadLocalMode 3
threadLocalModeLocalExecTLSModel :: ThreadLocalMode
threadLocalModeLocalExecTLSModel = ThreadLocalMode 4
threadLocalModeP :: QuasiQuoter
threadLocalModeP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "NotThreadLocal" -> threadLocalModeNotThreadLocal
    "GeneralDynamicTLSModel" -> threadLocalModeGeneralDynamicTLSModel
    "LocalDynamicTLSModel" -> threadLocalModeLocalDynamicTLSModel
    "InitialExecTLSModel" -> threadLocalModeInitialExecTLSModel
    "LocalExecTLSModel" -> threadLocalModeLocalExecTLSModel
    x -> error $ "bad quasiquoted FFI constant for threadLocalMode: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 210 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype ValueSubclassId = ValueSubclassId CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

valueSubclassIdArgument :: ValueSubclassId
valueSubclassIdArgument = ValueSubclassId 0
valueSubclassIdBasicBlock :: ValueSubclassId
valueSubclassIdBasicBlock = ValueSubclassId 1
valueSubclassIdFunction :: ValueSubclassId
valueSubclassIdFunction = ValueSubclassId 2
valueSubclassIdGlobalAlias :: ValueSubclassId
valueSubclassIdGlobalAlias = ValueSubclassId 3
valueSubclassIdGlobalVariable :: ValueSubclassId
valueSubclassIdGlobalVariable = ValueSubclassId 4
valueSubclassIdUndefValue :: ValueSubclassId
valueSubclassIdUndefValue = ValueSubclassId 5
valueSubclassIdBlockAddress :: ValueSubclassId
valueSubclassIdBlockAddress = ValueSubclassId 6
valueSubclassIdConstantExpr :: ValueSubclassId
valueSubclassIdConstantExpr = ValueSubclassId 7
valueSubclassIdConstantAggregateZero :: ValueSubclassId
valueSubclassIdConstantAggregateZero = ValueSubclassId 8
valueSubclassIdConstantDataArray :: ValueSubclassId
valueSubclassIdConstantDataArray = ValueSubclassId 9
valueSubclassIdConstantDataVector :: ValueSubclassId
valueSubclassIdConstantDataVector = ValueSubclassId 10
valueSubclassIdConstantInt :: ValueSubclassId
valueSubclassIdConstantInt = ValueSubclassId 11
valueSubclassIdConstantFP :: ValueSubclassId
valueSubclassIdConstantFP = ValueSubclassId 12
valueSubclassIdConstantArray :: ValueSubclassId
valueSubclassIdConstantArray = ValueSubclassId 13
valueSubclassIdConstantStruct :: ValueSubclassId
valueSubclassIdConstantStruct = ValueSubclassId 14
valueSubclassIdConstantTokenNone :: ValueSubclassId
valueSubclassIdConstantTokenNone = ValueSubclassId 15
valueSubclassIdConstantVector :: ValueSubclassId
valueSubclassIdConstantVector = ValueSubclassId 16
valueSubclassIdConstantPointerNull :: ValueSubclassId
valueSubclassIdConstantPointerNull = ValueSubclassId 17
valueSubclassIdInlineAsm :: ValueSubclassId
valueSubclassIdInlineAsm = ValueSubclassId 18
valueSubclassIdInstruction :: ValueSubclassId
valueSubclassIdInstruction = ValueSubclassId 19
valueSubclassIdP :: QuasiQuoter
valueSubclassIdP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Argument" -> valueSubclassIdArgument
    "BasicBlock" -> valueSubclassIdBasicBlock
    "Function" -> valueSubclassIdFunction
    "GlobalAlias" -> valueSubclassIdGlobalAlias
    "GlobalVariable" -> valueSubclassIdGlobalVariable
    "UndefValue" -> valueSubclassIdUndefValue
    "BlockAddress" -> valueSubclassIdBlockAddress
    "ConstantExpr" -> valueSubclassIdConstantExpr
    "ConstantAggregateZero" -> valueSubclassIdConstantAggregateZero
    "ConstantDataArray" -> valueSubclassIdConstantDataArray
    "ConstantDataVector" -> valueSubclassIdConstantDataVector
    "ConstantInt" -> valueSubclassIdConstantInt
    "ConstantFP" -> valueSubclassIdConstantFP
    "ConstantArray" -> valueSubclassIdConstantArray
    "ConstantStruct" -> valueSubclassIdConstantStruct
    "ConstantTokenNone" -> valueSubclassIdConstantTokenNone
    "ConstantVector" -> valueSubclassIdConstantVector
    "ConstantPointerNull" -> valueSubclassIdConstantPointerNull
    "InlineAsm" -> valueSubclassIdInlineAsm
    "Instruction" -> valueSubclassIdInstruction
    x -> error $ "bad quasiquoted FFI constant for valueSubclassId: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 215 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype DiagnosticKind = DiagnosticKind CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

diagnosticKindError :: DiagnosticKind
diagnosticKindError = DiagnosticKind 0
diagnosticKindWarning :: DiagnosticKind
diagnosticKindWarning = DiagnosticKind 1
diagnosticKindNote :: DiagnosticKind
diagnosticKindNote = DiagnosticKind 2
diagnosticKindP :: QuasiQuoter
diagnosticKindP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Error" -> diagnosticKindError
    "Warning" -> diagnosticKindWarning
    "Note" -> diagnosticKindNote
    x -> error $ "bad quasiquoted FFI constant for diagnosticKind: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 220 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype AsmDialect = AsmDialect CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

asmDialectATT :: AsmDialect
asmDialectATT = AsmDialect 0
asmDialectIntel :: AsmDialect
asmDialectIntel = AsmDialect 1
asmDialectP :: QuasiQuoter
asmDialectP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "ATT" -> asmDialectATT
    "Intel" -> asmDialectIntel
    x -> error $ "bad quasiquoted FFI constant for asmDialect: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 225 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype RMWOperation = RMWOperation CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

rmwOperationXchg :: RMWOperation
rmwOperationXchg = RMWOperation 0
rmwOperationAdd :: RMWOperation
rmwOperationAdd = RMWOperation 1
rmwOperationSub :: RMWOperation
rmwOperationSub = RMWOperation 2
rmwOperationAnd :: RMWOperation
rmwOperationAnd = RMWOperation 3
rmwOperationNand :: RMWOperation
rmwOperationNand = RMWOperation 4
rmwOperationOr :: RMWOperation
rmwOperationOr = RMWOperation 5
rmwOperationXor :: RMWOperation
rmwOperationXor = RMWOperation 6
rmwOperationMax :: RMWOperation
rmwOperationMax = RMWOperation 7
rmwOperationMin :: RMWOperation
rmwOperationMin = RMWOperation 8
rmwOperationUMax :: RMWOperation
rmwOperationUMax = RMWOperation 9
rmwOperationUMin :: RMWOperation
rmwOperationUMin = RMWOperation 10
rmwOperationP :: QuasiQuoter
rmwOperationP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Xchg" -> rmwOperationXchg
    "Add" -> rmwOperationAdd
    "Sub" -> rmwOperationSub
    "And" -> rmwOperationAnd
    "Nand" -> rmwOperationNand
    "Or" -> rmwOperationOr
    "Xor" -> rmwOperationXor
    "Max" -> rmwOperationMax
    "Min" -> rmwOperationMin
    "UMax" -> rmwOperationUMax
    "UMin" -> rmwOperationUMin
    x -> error $ "bad quasiquoted FFI constant for rmwOperation: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 230 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype RelocModel = RelocModel CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

relocModelDefault :: RelocModel
relocModelDefault = RelocModel 0
relocModelStatic :: RelocModel
relocModelStatic = RelocModel 1
relocModelPIC :: RelocModel
relocModelPIC = RelocModel 2
relocModelDynamicNoPic :: RelocModel
relocModelDynamicNoPic = RelocModel 3
relocModelP :: QuasiQuoter
relocModelP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Default" -> relocModelDefault
    "Static" -> relocModelStatic
    "PIC" -> relocModelPIC
    "DynamicNoPic" -> relocModelDynamicNoPic
    x -> error $ "bad quasiquoted FFI constant for relocModel: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 235 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype CodeModel = CodeModel CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

codeModelDefault :: CodeModel
codeModelDefault = CodeModel 0
codeModelJITDefault :: CodeModel
codeModelJITDefault = CodeModel 1
codeModelSmall :: CodeModel
codeModelSmall = CodeModel 3
codeModelKernel :: CodeModel
codeModelKernel = CodeModel 4
codeModelMedium :: CodeModel
codeModelMedium = CodeModel 5
codeModelLarge :: CodeModel
codeModelLarge = CodeModel 6
codeModelP :: QuasiQuoter
codeModelP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Default" -> codeModelDefault
    "JITDefault" -> codeModelJITDefault
    "Small" -> codeModelSmall
    "Kernel" -> codeModelKernel
    "Medium" -> codeModelMedium
    "Large" -> codeModelLarge
    x -> error $ "bad quasiquoted FFI constant for codeModel: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 240 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype CodeGenOptLevel = CodeGenOptLevel CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

codeGenOptLevelNone :: CodeGenOptLevel
codeGenOptLevelNone = CodeGenOptLevel 0
codeGenOptLevelLess :: CodeGenOptLevel
codeGenOptLevelLess = CodeGenOptLevel 1
codeGenOptLevelDefault :: CodeGenOptLevel
codeGenOptLevelDefault = CodeGenOptLevel 2
codeGenOptLevelAggressive :: CodeGenOptLevel
codeGenOptLevelAggressive = CodeGenOptLevel 3
codeGenOptLevelP :: QuasiQuoter
codeGenOptLevelP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "None" -> codeGenOptLevelNone
    "Less" -> codeGenOptLevelLess
    "Default" -> codeGenOptLevelDefault
    "Aggressive" -> codeGenOptLevelAggressive
    x -> error $ "bad quasiquoted FFI constant for codeGenOptLevel: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 245 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype CodeGenFileType = CodeGenFileType CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

codeGenFileTypeAssembly :: CodeGenFileType
codeGenFileTypeAssembly = CodeGenFileType 0
codeGenFileTypeObject :: CodeGenFileType
codeGenFileTypeObject = CodeGenFileType 1
codeGenFileTypeP :: QuasiQuoter
codeGenFileTypeP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Assembly" -> codeGenFileTypeAssembly
    "Object" -> codeGenFileTypeObject
    x -> error $ "bad quasiquoted FFI constant for codeGenFileType: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 250 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype FloatABIType = FloatABIType CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

floatABIDefault :: FloatABIType
floatABIDefault = FloatABIType 0
floatABISoft :: FloatABIType
floatABISoft = FloatABIType 1
floatABIHard :: FloatABIType
floatABIHard = FloatABIType 2
floatABIP :: QuasiQuoter
floatABIP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Default" -> floatABIDefault
    "Soft" -> floatABISoft
    "Hard" -> floatABIHard
    x -> error $ "bad quasiquoted FFI constant for floatABI: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 255 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype FPOpFusionMode = FPOpFusionMode CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

fpOpFusionModeFast :: FPOpFusionMode
fpOpFusionModeFast = FPOpFusionMode 0
fpOpFusionModeStandard :: FPOpFusionMode
fpOpFusionModeStandard = FPOpFusionMode 1
fpOpFusionModeStrict :: FPOpFusionMode
fpOpFusionModeStrict = FPOpFusionMode 2
fpOpFusionModeP :: QuasiQuoter
fpOpFusionModeP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Fast" -> fpOpFusionModeFast
    "Standard" -> fpOpFusionModeStandard
    "Strict" -> fpOpFusionModeStrict
    x -> error $ "bad quasiquoted FFI constant for fpOpFusionMode: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 260 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype ThreadModel = ThreadModel CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

threadModelPOSIX :: ThreadModel
threadModelPOSIX = ThreadModel 0
threadModelSingle :: ThreadModel
threadModelSingle = ThreadModel 1
threadModelP :: QuasiQuoter
threadModelP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "POSIX" -> threadModelPOSIX
    "Single" -> threadModelSingle
    x -> error $ "bad quasiquoted FFI constant for threadModel: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 265 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype EABI = EABI CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

eabiVersionUnknown :: EABI
eabiVersionUnknown = EABI 0
eabiVersionDefault :: EABI
eabiVersionDefault = EABI 1
eabiVersionEABI4 :: EABI
eabiVersionEABI4 = EABI 2
eabiVersionEABI5 :: EABI
eabiVersionEABI5 = EABI 3
eabiVersionGNU :: EABI
eabiVersionGNU = EABI 4
eabiVersionP :: QuasiQuoter
eabiVersionP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Unknown" -> eabiVersionUnknown
    "Default" -> eabiVersionDefault
    "EABI4" -> eabiVersionEABI4
    "EABI5" -> eabiVersionEABI5
    "GNU" -> eabiVersionGNU
    x -> error $ "bad quasiquoted FFI constant for eabiVersion: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 270 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype DebuggerKind = DebuggerKind CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

debuggerKindDefault :: DebuggerKind
debuggerKindDefault = DebuggerKind 0
debuggerKindGDB :: DebuggerKind
debuggerKindGDB = DebuggerKind 1
debuggerKindLLDB :: DebuggerKind
debuggerKindLLDB = DebuggerKind 2
debuggerKindSCE :: DebuggerKind
debuggerKindSCE = DebuggerKind 3
debuggerKindP :: QuasiQuoter
debuggerKindP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Default" -> debuggerKindDefault
    "GDB" -> debuggerKindGDB
    "LLDB" -> debuggerKindLLDB
    "SCE" -> debuggerKindSCE
    x -> error $ "bad quasiquoted FFI constant for debuggerKind: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 275 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype FPDenormalMode = FPDenormalMode CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

fpDenormalModeIEEE :: FPDenormalMode
fpDenormalModeIEEE = FPDenormalMode 0
fpDenormalModePreserveSign :: FPDenormalMode
fpDenormalModePreserveSign = FPDenormalMode 1
fpDenormalModePositiveZero :: FPDenormalMode
fpDenormalModePositiveZero = FPDenormalMode 2
fpDenormalModeP :: QuasiQuoter
fpDenormalModeP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "IEEE" -> fpDenormalModeIEEE
    "PreserveSign" -> fpDenormalModePreserveSign
    "PositiveZero" -> fpDenormalModePositiveZero
    x -> error $ "bad quasiquoted FFI constant for fpDenormalMode: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 280 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype ExceptionHandling = ExceptionHandling CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

exceptionHandlingNone :: ExceptionHandling
exceptionHandlingNone = ExceptionHandling 0
exceptionHandlingDwarfCFI :: ExceptionHandling
exceptionHandlingDwarfCFI = ExceptionHandling 1
exceptionHandlingSjLj :: ExceptionHandling
exceptionHandlingSjLj = ExceptionHandling 2
exceptionHandlingARM :: ExceptionHandling
exceptionHandlingARM = ExceptionHandling 3
exceptionHandlingWinEH :: ExceptionHandling
exceptionHandlingWinEH = ExceptionHandling 4
exceptionHandlingP :: QuasiQuoter
exceptionHandlingP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "None" -> exceptionHandlingNone
    "DwarfCFI" -> exceptionHandlingDwarfCFI
    "SjLj" -> exceptionHandlingSjLj
    "ARM" -> exceptionHandlingARM
    "WinEH" -> exceptionHandlingWinEH
    x -> error $ "bad quasiquoted FFI constant for exceptionHandling: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 285 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype TargetOptionFlag = TargetOptionFlag CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

targetOptionFlagPrintMachineCode :: TargetOptionFlag
targetOptionFlagPrintMachineCode = TargetOptionFlag 0
targetOptionFlagUnsafeFPMath :: TargetOptionFlag
targetOptionFlagUnsafeFPMath = TargetOptionFlag 1
targetOptionFlagNoInfsFPMath :: TargetOptionFlag
targetOptionFlagNoInfsFPMath = TargetOptionFlag 2
targetOptionFlagNoNaNsFPMath :: TargetOptionFlag
targetOptionFlagNoNaNsFPMath = TargetOptionFlag 3
targetOptionFlagNoTrappingFPMath :: TargetOptionFlag
targetOptionFlagNoTrappingFPMath = TargetOptionFlag 4
targetOptionFlagNoSignedZerosFPMath :: TargetOptionFlag
targetOptionFlagNoSignedZerosFPMath = TargetOptionFlag 5
targetOptionFlagHonorSignDependentRoundingFPMathOption :: TargetOptionFlag
targetOptionFlagHonorSignDependentRoundingFPMathOption = TargetOptionFlag 6
targetOptionFlagNoZerosInBSS :: TargetOptionFlag
targetOptionFlagNoZerosInBSS = TargetOptionFlag 7
targetOptionFlagGuaranteedTailCallOpt :: TargetOptionFlag
targetOptionFlagGuaranteedTailCallOpt = TargetOptionFlag 8
targetOptionFlagStackSymbolOrdering :: TargetOptionFlag
targetOptionFlagStackSymbolOrdering = TargetOptionFlag 9
targetOptionFlagEnableFastISel :: TargetOptionFlag
targetOptionFlagEnableFastISel = TargetOptionFlag 10
targetOptionFlagUseInitArray :: TargetOptionFlag
targetOptionFlagUseInitArray = TargetOptionFlag 11
targetOptionFlagDisableIntegratedAS :: TargetOptionFlag
targetOptionFlagDisableIntegratedAS = TargetOptionFlag 12
targetOptionFlagRelaxELFRelocations :: TargetOptionFlag
targetOptionFlagRelaxELFRelocations = TargetOptionFlag 13
targetOptionFlagFunctionSections :: TargetOptionFlag
targetOptionFlagFunctionSections = TargetOptionFlag 14
targetOptionFlagDataSections :: TargetOptionFlag
targetOptionFlagDataSections = TargetOptionFlag 15
targetOptionFlagUniqueSectionNames :: TargetOptionFlag
targetOptionFlagUniqueSectionNames = TargetOptionFlag 16
targetOptionFlagTrapUnreachable :: TargetOptionFlag
targetOptionFlagTrapUnreachable = TargetOptionFlag 17
targetOptionFlagEmulatedTLS :: TargetOptionFlag
targetOptionFlagEmulatedTLS = TargetOptionFlag 18
targetOptionFlagEnableIPRA :: TargetOptionFlag
targetOptionFlagEnableIPRA = TargetOptionFlag 19
targetOptionFlagP :: QuasiQuoter
targetOptionFlagP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "PrintMachineCode" -> targetOptionFlagPrintMachineCode
    "UnsafeFPMath" -> targetOptionFlagUnsafeFPMath
    "NoInfsFPMath" -> targetOptionFlagNoInfsFPMath
    "NoNaNsFPMath" -> targetOptionFlagNoNaNsFPMath
    "NoTrappingFPMath" -> targetOptionFlagNoTrappingFPMath
    "NoSignedZerosFPMath" -> targetOptionFlagNoSignedZerosFPMath
    "HonorSignDependentRoundingFPMathOption" -> targetOptionFlagHonorSignDependentRoundingFPMathOption
    "NoZerosInBSS" -> targetOptionFlagNoZerosInBSS
    "GuaranteedTailCallOpt" -> targetOptionFlagGuaranteedTailCallOpt
    "StackSymbolOrdering" -> targetOptionFlagStackSymbolOrdering
    "EnableFastISel" -> targetOptionFlagEnableFastISel
    "UseInitArray" -> targetOptionFlagUseInitArray
    "DisableIntegratedAS" -> targetOptionFlagDisableIntegratedAS
    "RelaxELFRelocations" -> targetOptionFlagRelaxELFRelocations
    "FunctionSections" -> targetOptionFlagFunctionSections
    "DataSections" -> targetOptionFlagDataSections
    "UniqueSectionNames" -> targetOptionFlagUniqueSectionNames
    "TrapUnreachable" -> targetOptionFlagTrapUnreachable
    "EmulatedTLS" -> targetOptionFlagEmulatedTLS
    "EnableIPRA" -> targetOptionFlagEnableIPRA
    x -> error $ "bad quasiquoted FFI constant for targetOptionFlag: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 290 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype MCTargetOptionFlag = MCTargetOptionFlag CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

mcTargetOptionFlagMCRelaxAll :: MCTargetOptionFlag
mcTargetOptionFlagMCRelaxAll = MCTargetOptionFlag 0
mcTargetOptionFlagMCNoExecStack :: MCTargetOptionFlag
mcTargetOptionFlagMCNoExecStack = MCTargetOptionFlag 1
mcTargetOptionFlagMCFatalWarnings :: MCTargetOptionFlag
mcTargetOptionFlagMCFatalWarnings = MCTargetOptionFlag 2
mcTargetOptionFlagMCNoWarn :: MCTargetOptionFlag
mcTargetOptionFlagMCNoWarn = MCTargetOptionFlag 3
mcTargetOptionFlagMCNoDeprecatedWarn :: MCTargetOptionFlag
mcTargetOptionFlagMCNoDeprecatedWarn = MCTargetOptionFlag 4
mcTargetOptionFlagMCSaveTempLabels :: MCTargetOptionFlag
mcTargetOptionFlagMCSaveTempLabels = MCTargetOptionFlag 5
mcTargetOptionFlagMCUseDwarfDirectory :: MCTargetOptionFlag
mcTargetOptionFlagMCUseDwarfDirectory = MCTargetOptionFlag 6
mcTargetOptionFlagMCIncrementalLinkerCompatible :: MCTargetOptionFlag
mcTargetOptionFlagMCIncrementalLinkerCompatible = MCTargetOptionFlag 7
mcTargetOptionFlagMCPIECopyRelocations :: MCTargetOptionFlag
mcTargetOptionFlagMCPIECopyRelocations = MCTargetOptionFlag 8
mcTargetOptionFlagShowMCEncoding :: MCTargetOptionFlag
mcTargetOptionFlagShowMCEncoding = MCTargetOptionFlag 9
mcTargetOptionFlagShowMCInst :: MCTargetOptionFlag
mcTargetOptionFlagShowMCInst = MCTargetOptionFlag 10
mcTargetOptionFlagAsmVerbose :: MCTargetOptionFlag
mcTargetOptionFlagAsmVerbose = MCTargetOptionFlag 11
mcTargetOptionFlagPreserveAsmComments :: MCTargetOptionFlag
mcTargetOptionFlagPreserveAsmComments = MCTargetOptionFlag 12
mcTargetOptionFlagP :: QuasiQuoter
mcTargetOptionFlagP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "MCRelaxAll" -> mcTargetOptionFlagMCRelaxAll
    "MCNoExecStack" -> mcTargetOptionFlagMCNoExecStack
    "MCFatalWarnings" -> mcTargetOptionFlagMCFatalWarnings
    "MCNoWarn" -> mcTargetOptionFlagMCNoWarn
    "MCNoDeprecatedWarn" -> mcTargetOptionFlagMCNoDeprecatedWarn
    "MCSaveTempLabels" -> mcTargetOptionFlagMCSaveTempLabels
    "MCUseDwarfDirectory" -> mcTargetOptionFlagMCUseDwarfDirectory
    "MCIncrementalLinkerCompatible" -> mcTargetOptionFlagMCIncrementalLinkerCompatible
    "MCPIECopyRelocations" -> mcTargetOptionFlagMCPIECopyRelocations
    "ShowMCEncoding" -> mcTargetOptionFlagShowMCEncoding
    "ShowMCInst" -> mcTargetOptionFlagShowMCInst
    "AsmVerbose" -> mcTargetOptionFlagAsmVerbose
    "PreserveAsmComments" -> mcTargetOptionFlagPreserveAsmComments
    x -> error $ "bad quasiquoted FFI constant for mcTargetOptionFlag: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 295 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype DebugCompressionType = DebugCompressionType CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

debugCompressionTypeNone :: DebugCompressionType
debugCompressionTypeNone = DebugCompressionType 0
debugCompressionTypeGNU :: DebugCompressionType
debugCompressionTypeGNU = DebugCompressionType 1
debugCompressionTypeZ :: DebugCompressionType
debugCompressionTypeZ = DebugCompressionType 2
debugCompressionTypeP :: QuasiQuoter
debugCompressionTypeP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "None" -> debugCompressionTypeNone
    "GNU" -> debugCompressionTypeGNU
    "Z" -> debugCompressionTypeZ
    x -> error $ "bad quasiquoted FFI constant for debugCompressionType: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 300 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype TypeKind = TypeKind CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

typeKindVoid :: TypeKind
typeKindVoid = TypeKind 0
typeKindHalf :: TypeKind
typeKindHalf = TypeKind 1
typeKindFloat :: TypeKind
typeKindFloat = TypeKind 2
typeKindDouble :: TypeKind
typeKindDouble = TypeKind 3
typeKindX86_FP80 :: TypeKind
typeKindX86_FP80 = TypeKind 4
typeKindFP128 :: TypeKind
typeKindFP128 = TypeKind 5
typeKindPPC_FP128 :: TypeKind
typeKindPPC_FP128 = TypeKind 6
typeKindLabel :: TypeKind
typeKindLabel = TypeKind 7
typeKindInteger :: TypeKind
typeKindInteger = TypeKind 8
typeKindFunction :: TypeKind
typeKindFunction = TypeKind 9
typeKindStruct :: TypeKind
typeKindStruct = TypeKind 10
typeKindArray :: TypeKind
typeKindArray = TypeKind 11
typeKindPointer :: TypeKind
typeKindPointer = TypeKind 12
typeKindVector :: TypeKind
typeKindVector = TypeKind 13
typeKindMetadata :: TypeKind
typeKindMetadata = TypeKind 14
typeKindX86_MMX :: TypeKind
typeKindX86_MMX = TypeKind 15
typeKindToken :: TypeKind
typeKindToken = TypeKind 16
typeKindP :: QuasiQuoter
typeKindP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Void" -> typeKindVoid
    "Half" -> typeKindHalf
    "Float" -> typeKindFloat
    "Double" -> typeKindDouble
    "X86_FP80" -> typeKindX86_FP80
    "FP128" -> typeKindFP128
    "PPC_FP128" -> typeKindPPC_FP128
    "Label" -> typeKindLabel
    "Integer" -> typeKindInteger
    "Function" -> typeKindFunction
    "Struct" -> typeKindStruct
    "Array" -> typeKindArray
    "Pointer" -> typeKindPointer
    "Vector" -> typeKindVector
    "Metadata" -> typeKindMetadata
    "X86_MMX" -> typeKindX86_MMX
    "Token" -> typeKindToken
    x -> error $ "bad quasiquoted FFI constant for typeKind: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 305 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}











newtype ParameterAttributeKind = ParameterAttributeKind CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

parameterAttributeKindAlignment :: ParameterAttributeKind
parameterAttributeKindAlignment = ParameterAttributeKind 1
parameterAttributeKindByVal :: ParameterAttributeKind
parameterAttributeKindByVal = ParameterAttributeKind 6
parameterAttributeKindDereferenceable :: ParameterAttributeKind
parameterAttributeKindDereferenceable = ParameterAttributeKind 9
parameterAttributeKindDereferenceableOrNull :: ParameterAttributeKind
parameterAttributeKindDereferenceableOrNull = ParameterAttributeKind 10
parameterAttributeKindImmArg :: ParameterAttributeKind
parameterAttributeKindImmArg = ParameterAttributeKind 11
parameterAttributeKindInAlloca :: ParameterAttributeKind
parameterAttributeKindInAlloca = ParameterAttributeKind 12
parameterAttributeKindInReg :: ParameterAttributeKind
parameterAttributeKindInReg = ParameterAttributeKind 13
parameterAttributeKindNest :: ParameterAttributeKind
parameterAttributeKindNest = ParameterAttributeKind 20
parameterAttributeKindNoAlias :: ParameterAttributeKind
parameterAttributeKindNoAlias = ParameterAttributeKind 21
parameterAttributeKindNoCapture :: ParameterAttributeKind
parameterAttributeKindNoCapture = ParameterAttributeKind 23
parameterAttributeKindNonNull :: ParameterAttributeKind
parameterAttributeKindNonNull = ParameterAttributeKind 35
parameterAttributeKindReadNone :: ParameterAttributeKind
parameterAttributeKindReadNone = ParameterAttributeKind 39
parameterAttributeKindReadOnly :: ParameterAttributeKind
parameterAttributeKindReadOnly = ParameterAttributeKind 40
parameterAttributeKindReturned :: ParameterAttributeKind
parameterAttributeKindReturned = ParameterAttributeKind 41
parameterAttributeKindSExt :: ParameterAttributeKind
parameterAttributeKindSExt = ParameterAttributeKind 43
parameterAttributeKindStructRet :: ParameterAttributeKind
parameterAttributeKindStructRet = ParameterAttributeKind 58
parameterAttributeKindSwiftError :: ParameterAttributeKind
parameterAttributeKindSwiftError = ParameterAttributeKind 59
parameterAttributeKindSwiftSelf :: ParameterAttributeKind
parameterAttributeKindSwiftSelf = ParameterAttributeKind 60
parameterAttributeKindWriteOnly :: ParameterAttributeKind
parameterAttributeKindWriteOnly = ParameterAttributeKind 63
parameterAttributeKindZExt :: ParameterAttributeKind
parameterAttributeKindZExt = ParameterAttributeKind 64
parameterAttributeKindP :: QuasiQuoter
parameterAttributeKindP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "Alignment" -> parameterAttributeKindAlignment
    "ByVal" -> parameterAttributeKindByVal
    "Dereferenceable" -> parameterAttributeKindDereferenceable
    "DereferenceableOrNull" -> parameterAttributeKindDereferenceableOrNull
    "ImmArg" -> parameterAttributeKindImmArg
    "InAlloca" -> parameterAttributeKindInAlloca
    "InReg" -> parameterAttributeKindInReg
    "Nest" -> parameterAttributeKindNest
    "NoAlias" -> parameterAttributeKindNoAlias
    "NoCapture" -> parameterAttributeKindNoCapture
    "NonNull" -> parameterAttributeKindNonNull
    "ReadNone" -> parameterAttributeKindReadNone
    "ReadOnly" -> parameterAttributeKindReadOnly
    "Returned" -> parameterAttributeKindReturned
    "SExt" -> parameterAttributeKindSExt
    "StructRet" -> parameterAttributeKindStructRet
    "SwiftError" -> parameterAttributeKindSwiftError
    "SwiftSelf" -> parameterAttributeKindSwiftSelf
    "WriteOnly" -> parameterAttributeKindWriteOnly
    "ZExt" -> parameterAttributeKindZExt
    x -> error $ "bad quasiquoted FFI constant for parameterAttributeKind: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 320 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype FunctionAttributeKind = FunctionAttributeKind CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

functionAttributeKindAllocSize :: FunctionAttributeKind
functionAttributeKindAllocSize = FunctionAttributeKind 2
functionAttributeKindAlwaysInline :: FunctionAttributeKind
functionAttributeKindAlwaysInline = FunctionAttributeKind 3
functionAttributeKindArgMemOnly :: FunctionAttributeKind
functionAttributeKindArgMemOnly = FunctionAttributeKind 4
functionAttributeKindBuiltin :: FunctionAttributeKind
functionAttributeKindBuiltin = FunctionAttributeKind 5
functionAttributeKindCold :: FunctionAttributeKind
functionAttributeKindCold = FunctionAttributeKind 7
functionAttributeKindConvergent :: FunctionAttributeKind
functionAttributeKindConvergent = FunctionAttributeKind 8
functionAttributeKindInaccessibleMemOnly :: FunctionAttributeKind
functionAttributeKindInaccessibleMemOnly = FunctionAttributeKind 14
functionAttributeKindInaccessibleMemOrArgMemOnly :: FunctionAttributeKind
functionAttributeKindInaccessibleMemOrArgMemOnly = FunctionAttributeKind 15
functionAttributeKindInlineHint :: FunctionAttributeKind
functionAttributeKindInlineHint = FunctionAttributeKind 16
functionAttributeKindJumpTable :: FunctionAttributeKind
functionAttributeKindJumpTable = FunctionAttributeKind 17
functionAttributeKindMinSize :: FunctionAttributeKind
functionAttributeKindMinSize = FunctionAttributeKind 18
functionAttributeKindNaked :: FunctionAttributeKind
functionAttributeKindNaked = FunctionAttributeKind 19
functionAttributeKindNoBuiltin :: FunctionAttributeKind
functionAttributeKindNoBuiltin = FunctionAttributeKind 22
functionAttributeKindNoCfCheck :: FunctionAttributeKind
functionAttributeKindNoCfCheck = FunctionAttributeKind 24
functionAttributeKindNoDuplicate :: FunctionAttributeKind
functionAttributeKindNoDuplicate = FunctionAttributeKind 25
functionAttributeKindNoFree :: FunctionAttributeKind
functionAttributeKindNoFree = FunctionAttributeKind 26
functionAttributeKindNoImplicitFloat :: FunctionAttributeKind
functionAttributeKindNoImplicitFloat = FunctionAttributeKind 27
functionAttributeKindNoInline :: FunctionAttributeKind
functionAttributeKindNoInline = FunctionAttributeKind 28
functionAttributeKindNoRecurse :: FunctionAttributeKind
functionAttributeKindNoRecurse = FunctionAttributeKind 29
functionAttributeKindNoRedZone :: FunctionAttributeKind
functionAttributeKindNoRedZone = FunctionAttributeKind 30
functionAttributeKindNoReturn :: FunctionAttributeKind
functionAttributeKindNoReturn = FunctionAttributeKind 31
functionAttributeKindNoSync :: FunctionAttributeKind
functionAttributeKindNoSync = FunctionAttributeKind 32
functionAttributeKindNoUnwind :: FunctionAttributeKind
functionAttributeKindNoUnwind = FunctionAttributeKind 33
functionAttributeKindNonLazyBind :: FunctionAttributeKind
functionAttributeKindNonLazyBind = FunctionAttributeKind 34
functionAttributeKindOptForFuzzing :: FunctionAttributeKind
functionAttributeKindOptForFuzzing = FunctionAttributeKind 36
functionAttributeKindOptimizeForSize :: FunctionAttributeKind
functionAttributeKindOptimizeForSize = FunctionAttributeKind 37
functionAttributeKindOptimizeNone :: FunctionAttributeKind
functionAttributeKindOptimizeNone = FunctionAttributeKind 38
functionAttributeKindReadNone :: FunctionAttributeKind
functionAttributeKindReadNone = FunctionAttributeKind 39
functionAttributeKindReadOnly :: FunctionAttributeKind
functionAttributeKindReadOnly = FunctionAttributeKind 40
functionAttributeKindReturnsTwice :: FunctionAttributeKind
functionAttributeKindReturnsTwice = FunctionAttributeKind 42
functionAttributeKindSafeStack :: FunctionAttributeKind
functionAttributeKindSafeStack = FunctionAttributeKind 44
functionAttributeKindSanitizeAddress :: FunctionAttributeKind
functionAttributeKindSanitizeAddress = FunctionAttributeKind 45
functionAttributeKindSanitizeHWAddress :: FunctionAttributeKind
functionAttributeKindSanitizeHWAddress :: FunctionAttributeKind
functionAttributeKindSanitizeHWAddress = CUInt -> FunctionAttributeKind
FunctionAttributeKind 46
functionAttributeKindSanitizeMemTag :: FunctionAttributeKind
functionAttributeKindSanitizeMemTag :: FunctionAttributeKind
functionAttributeKindSanitizeMemTag = CUInt -> FunctionAttributeKind
FunctionAttributeKind 47
functionAttributeKindSanitizeMemory :: FunctionAttributeKind
functionAttributeKindSanitizeMemory :: FunctionAttributeKind
functionAttributeKindSanitizeMemory = CUInt -> FunctionAttributeKind
FunctionAttributeKind 48
functionAttributeKindSanitizeThread :: FunctionAttributeKind
functionAttributeKindSanitizeThread :: FunctionAttributeKind
functionAttributeKindSanitizeThread = CUInt -> FunctionAttributeKind
FunctionAttributeKind 49
functionAttributeKindShadowCallStack :: FunctionAttributeKind
functionAttributeKindShadowCallStack :: FunctionAttributeKind
functionAttributeKindShadowCallStack = CUInt -> FunctionAttributeKind
FunctionAttributeKind 50
functionAttributeKindSpeculatable :: FunctionAttributeKind
functionAttributeKindSpeculatable :: FunctionAttributeKind
functionAttributeKindSpeculatable = CUInt -> FunctionAttributeKind
FunctionAttributeKind 51
functionAttributeKindSpeculativeLoadHardening :: FunctionAttributeKind
functionAttributeKindSpeculativeLoadHardening :: FunctionAttributeKind
functionAttributeKindSpeculativeLoadHardening = CUInt -> FunctionAttributeKind
FunctionAttributeKind 52
functionAttributeKindStackAlignment :: FunctionAttributeKind
functionAttributeKindStackAlignment :: FunctionAttributeKind
functionAttributeKindStackAlignment = CUInt -> FunctionAttributeKind
FunctionAttributeKind 53
functionAttributeKindStackProtect :: FunctionAttributeKind
functionAttributeKindStackProtect :: FunctionAttributeKind
functionAttributeKindStackProtect = CUInt -> FunctionAttributeKind
FunctionAttributeKind 54
functionAttributeKindStackProtectReq :: FunctionAttributeKind
functionAttributeKindStackProtectReq :: FunctionAttributeKind
functionAttributeKindStackProtectReq = CUInt -> FunctionAttributeKind
FunctionAttributeKind 55
functionAttributeKindStackProtectStrong :: FunctionAttributeKind
functionAttributeKindStackProtectStrong :: FunctionAttributeKind
functionAttributeKindStackProtectStrong = CUInt -> FunctionAttributeKind
FunctionAttributeKind 56
functionAttributeKindStrictFP :: FunctionAttributeKind
functionAttributeKindStrictFP :: FunctionAttributeKind
functionAttributeKindStrictFP = CUInt -> FunctionAttributeKind
FunctionAttributeKind 57
functionAttributeKindUWTable :: FunctionAttributeKind
functionAttributeKindUWTable :: FunctionAttributeKind
functionAttributeKindUWTable = CUInt -> FunctionAttributeKind
FunctionAttributeKind 61
functionAttributeKindWillReturn :: FunctionAttributeKind
functionAttributeKindWillReturn :: FunctionAttributeKind
functionAttributeKindWillReturn = CUInt -> FunctionAttributeKind
FunctionAttributeKind 62
functionAttributeKindWriteOnly :: FunctionAttributeKind
functionAttributeKindWriteOnly :: FunctionAttributeKind
functionAttributeKindWriteOnly = CUInt -> FunctionAttributeKind
FunctionAttributeKind 63
functionAttributeKindP :: QuasiQuoter
functionAttributeKindP :: QuasiQuoter
functionAttributeKindP = QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter {
  quoteExp = undefined,
  quotePat :: String -> Q Pat
quotePat = \s :: String
s -> (forall b. Data b => b -> Maybe (Q Pat))
-> FunctionAttributeKind -> Q Pat
forall a.
Data a =>
(forall b. Data b => b -> Maybe (Q Pat)) -> a -> Q Pat
dataToPatQ (Maybe (Q Pat) -> b -> Maybe (Q Pat)
forall a b. a -> b -> a
const Maybe (Q Pat)
forall a. Maybe a
Nothing) (FunctionAttributeKind -> Q Pat) -> FunctionAttributeKind -> Q Pat
forall a b. (a -> b) -> a -> b
$ case String
s of
    "AllocSize" -> FunctionAttributeKind
functionAttributeKindAllocSize
    "AlwaysInline" -> FunctionAttributeKind
functionAttributeKindAlwaysInline
    "ArgMemOnly" -> FunctionAttributeKind
functionAttributeKindArgMemOnly
    "Builtin" -> FunctionAttributeKind
functionAttributeKindBuiltin
    "Cold" -> FunctionAttributeKind
functionAttributeKindCold
    "Convergent" -> FunctionAttributeKind
functionAttributeKindConvergent
    "InaccessibleMemOnly" -> FunctionAttributeKind
functionAttributeKindInaccessibleMemOnly
    "InaccessibleMemOrArgMemOnly" -> FunctionAttributeKind
functionAttributeKindInaccessibleMemOrArgMemOnly
    "InlineHint" -> FunctionAttributeKind
functionAttributeKindInlineHint
    "JumpTable" -> FunctionAttributeKind
functionAttributeKindJumpTable
    "MinSize" -> FunctionAttributeKind
functionAttributeKindMinSize
    "Naked" -> FunctionAttributeKind
functionAttributeKindNaked
    "NoBuiltin" -> FunctionAttributeKind
functionAttributeKindNoBuiltin
    "NoCfCheck" -> FunctionAttributeKind
functionAttributeKindNoCfCheck
    "NoDuplicate" -> FunctionAttributeKind
functionAttributeKindNoDuplicate
    "NoFree" -> FunctionAttributeKind
functionAttributeKindNoFree
    "NoImplicitFloat" -> FunctionAttributeKind
functionAttributeKindNoImplicitFloat
    "NoInline" -> FunctionAttributeKind
functionAttributeKindNoInline
    "NoRecurse" -> FunctionAttributeKind
functionAttributeKindNoRecurse
    "NoRedZone" -> FunctionAttributeKind
functionAttributeKindNoRedZone
    "NoReturn" -> FunctionAttributeKind
functionAttributeKindNoReturn
    "NoSync" -> FunctionAttributeKind
functionAttributeKindNoSync
    "NoUnwind" -> FunctionAttributeKind
functionAttributeKindNoUnwind
    "NonLazyBind" -> FunctionAttributeKind
functionAttributeKindNonLazyBind
    "OptForFuzzing" -> FunctionAttributeKind
functionAttributeKindOptForFuzzing
    "OptimizeForSize" -> FunctionAttributeKind
functionAttributeKindOptimizeForSize
    "OptimizeNone" -> FunctionAttributeKind
functionAttributeKindOptimizeNone
    "ReadNone" -> FunctionAttributeKind
functionAttributeKindReadNone
    "ReadOnly" -> FunctionAttributeKind
functionAttributeKindReadOnly
    "ReturnsTwice" -> FunctionAttributeKind
functionAttributeKindReturnsTwice
    "SafeStack" -> FunctionAttributeKind
functionAttributeKindSafeStack
    "SanitizeAddress" -> FunctionAttributeKind
functionAttributeKindSanitizeAddress
    "SanitizeHWAddress" -> FunctionAttributeKind
functionAttributeKindSanitizeHWAddress
    "SanitizeMemTag" -> FunctionAttributeKind
functionAttributeKindSanitizeMemTag
    "SanitizeMemory" -> FunctionAttributeKind
functionAttributeKindSanitizeMemory
    "SanitizeThread" -> FunctionAttributeKind
functionAttributeKindSanitizeThread
    "ShadowCallStack" -> FunctionAttributeKind
functionAttributeKindShadowCallStack
    "Speculatable" -> FunctionAttributeKind
functionAttributeKindSpeculatable
    "SpeculativeLoadHardening" -> FunctionAttributeKind
functionAttributeKindSpeculativeLoadHardening
    "StackAlignment" -> FunctionAttributeKind
functionAttributeKindStackAlignment
    "StackProtect" -> FunctionAttributeKind
functionAttributeKindStackProtect
    "StackProtectReq" -> FunctionAttributeKind
functionAttributeKindStackProtectReq
    "StackProtectStrong" -> FunctionAttributeKind
functionAttributeKindStackProtectStrong
    "StrictFP" -> FunctionAttributeKind
functionAttributeKindStrictFP
    "UWTable" -> FunctionAttributeKind
functionAttributeKindUWTable
    "WillReturn" -> FunctionAttributeKind
functionAttributeKindWillReturn
    "WriteOnly" -> FunctionAttributeKind
functionAttributeKindWriteOnly
    x :: String
x -> String -> FunctionAttributeKind
forall a. HasCallStack => String -> a
error (String -> FunctionAttributeKind)
-> String -> FunctionAttributeKind
forall a b. (a -> b) -> a -> b
$ "bad quasiquoted FFI constant for functionAttributeKind: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 325 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype FloatSemantics = FloatSemantics CUInt
  deriving (Eq, Read, Show, Typeable, Data, Generic)

floatSemanticsIEEEhalf :: FloatSemantics
floatSemanticsIEEEhalf = FloatSemantics 0
floatSemanticsIEEEsingle :: FloatSemantics
floatSemanticsIEEEsingle = FloatSemantics 1
floatSemanticsIEEEdouble :: FloatSemantics
floatSemanticsIEEEdouble = FloatSemantics 2
floatSemanticsIEEEquad :: FloatSemantics
floatSemanticsIEEEquad = FloatSemantics 3
floatSemanticsPPCDoubleDouble :: FloatSemantics
floatSemanticsPPCDoubleDouble = FloatSemantics 4
floatSemanticsx87DoubleExtended :: FloatSemantics
floatSemanticsx87DoubleExtended = FloatSemantics 5
floatSemanticsBogus :: FloatSemantics
floatSemanticsBogus = FloatSemantics 6
floatSemanticsP :: QuasiQuoter
floatSemanticsP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "IEEEhalf" -> floatSemanticsIEEEhalf
    "IEEEsingle" -> floatSemanticsIEEEsingle
    "IEEEdouble" -> floatSemanticsIEEEdouble
    "IEEEquad" -> floatSemanticsIEEEquad
    "PPCDoubleDouble" -> floatSemanticsPPCDoubleDouble
    "x87DoubleExtended" -> floatSemanticsx87DoubleExtended
    "Bogus" -> floatSemanticsBogus
    x -> error $ "bad quasiquoted FFI constant for floatSemantics: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 330 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype VerifierFailureAction = VerifierFailureAction CUInt
  deriving (Eq, Read, Show, Bits, Typeable, Data, Num, Generic)

verifierFailureActionAbortProcess :: VerifierFailureAction
verifierFailureActionAbortProcess = VerifierFailureAction 0
verifierFailureActionPrintMessage :: VerifierFailureAction
verifierFailureActionPrintMessage = VerifierFailureAction 1
verifierFailureActionReturnStatus :: VerifierFailureAction
verifierFailureActionReturnStatus = VerifierFailureAction 2
verifierFailureActionP :: QuasiQuoter
verifierFailureActionP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "AbortProcess" -> verifierFailureActionAbortProcess
    "PrintMessage" -> verifierFailureActionPrintMessage
    "ReturnStatus" -> verifierFailureActionReturnStatus
    x -> error $ "bad quasiquoted FFI constant for verifierFailureAction: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 335 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype LibFunc = LibFunc CUInt
  deriving (Eq, Read, Show, Bits, Typeable, Data, Num, Storable, Generic)

libFunc__under_IO_getc :: LibFunc
libFunc__under_IO_getc = LibFunc 0
libFunc__under_IO_putc :: LibFunc
libFunc__under_IO_putc = LibFunc 1
libFunc__ZdaPv :: LibFunc
libFunc__ZdaPv = LibFunc 2
libFunc__ZdaPvRKSt9nothrow_t :: LibFunc
libFunc__ZdaPvRKSt9nothrow_t = LibFunc 3
libFunc__ZdlPv :: LibFunc
libFunc__ZdlPv = LibFunc 4
libFunc__ZdlPvRKSt9nothrow_t :: LibFunc
libFunc__ZdlPvRKSt9nothrow_t = LibFunc 5
libFunc__Znaj :: LibFunc
libFunc__Znaj = LibFunc 6
libFunc__ZnajRKSt9nothrow_t :: LibFunc
libFunc__ZnajRKSt9nothrow_t = LibFunc 7
libFunc__Znam :: LibFunc
libFunc__Znam = LibFunc 8
libFunc__ZnamRKSt9nothrow_t :: LibFunc
libFunc__ZnamRKSt9nothrow_t = LibFunc 9
libFunc__Znwj :: LibFunc
libFunc__Znwj = LibFunc 10
libFunc__ZnwjRKSt9nothrow_t :: LibFunc
libFunc__ZnwjRKSt9nothrow_t = LibFunc 11
libFunc__Znwm :: LibFunc
libFunc__Znwm = LibFunc 12
libFunc__ZnwmRKSt9nothrow_t :: LibFunc
libFunc__ZnwmRKSt9nothrow_t = LibFunc 13
libFunc__cospi :: LibFunc
libFunc__cospi = LibFunc 14
libFunc__cospif :: LibFunc
libFunc__cospif = LibFunc 15
libFunc__cxa_atexit :: LibFunc
libFunc__cxa_atexit = LibFunc 16
libFunc__cxa_guard_abort :: LibFunc
libFunc__cxa_guard_abort = LibFunc 17
libFunc__cxa_guard_acquire :: LibFunc
libFunc__cxa_guard_acquire = LibFunc 18
libFunc__cxa_guard_release :: LibFunc
libFunc__cxa_guard_release = LibFunc 19
libFunc__dunder_isoc99_scanf :: LibFunc
libFunc__dunder_isoc99_scanf = LibFunc 20
libFunc__dunder_isoc99_sscanf :: LibFunc
libFunc__dunder_isoc99_sscanf = LibFunc 21
libFunc__memcpy_chk :: LibFunc
libFunc__memcpy_chk = LibFunc 22
libFunc__sincospi_stret :: LibFunc
libFunc__sincospi_stret = LibFunc 23
libFunc__sincospif_stret :: LibFunc
libFunc__sincospif_stret = LibFunc 24
libFunc__sinpi :: LibFunc
libFunc__sinpi = LibFunc 25
libFunc__sinpif :: LibFunc
libFunc__sinpif = LibFunc 26
libFunc__sqrt_finite :: LibFunc
libFunc__sqrt_finite = LibFunc 27
libFunc__sqrtf_finite :: LibFunc
libFunc__sqrtf_finite = LibFunc 28
libFunc__sqrtl_finite :: LibFunc
libFunc__sqrtl_finite = LibFunc 29
libFunc__dunder_strdup :: LibFunc
libFunc__dunder_strdup = LibFunc 30
libFunc__dunder_strndup :: LibFunc
libFunc__dunder_strndup = LibFunc 31
libFunc__dunder_strtok_r :: LibFunc
libFunc__dunder_strtok_r = LibFunc 32
libFunc__abs :: LibFunc
libFunc__abs = LibFunc 33
libFunc__access :: LibFunc
libFunc__access = LibFunc 34
libFunc__acos :: LibFunc
libFunc__acos = LibFunc 35
libFunc__acosf :: LibFunc
libFunc__acosf = LibFunc 36
libFunc__acosh :: LibFunc
libFunc__acosh = LibFunc 37
libFunc__acoshf :: LibFunc
libFunc__acoshf = LibFunc 38
libFunc__acoshl :: LibFunc
libFunc__acoshl = LibFunc 39
libFunc__acosl :: LibFunc
libFunc__acosl = LibFunc 40
libFunc__asin :: LibFunc
libFunc__asin = LibFunc 41
libFunc__asinf :: LibFunc
libFunc__asinf = LibFunc 42
libFunc__asinh :: LibFunc
libFunc__asinh = LibFunc 43
libFunc__asinhf :: LibFunc
libFunc__asinhf = LibFunc 44
libFunc__asinhl :: LibFunc
libFunc__asinhl = LibFunc 45
libFunc__asinl :: LibFunc
libFunc__asinl = LibFunc 46
libFunc__atan :: LibFunc
libFunc__atan = LibFunc 47
libFunc__atan2 :: LibFunc
libFunc__atan2 = LibFunc 48
libFunc__atan2f :: LibFunc
libFunc__atan2f = LibFunc 49
libFunc__atan2l :: LibFunc
libFunc__atan2l = LibFunc 50
libFunc__atanf :: LibFunc
libFunc__atanf = LibFunc 51
libFunc__atanh :: LibFunc
libFunc__atanh = LibFunc 52
libFunc__atanhf :: LibFunc
libFunc__atanhf = LibFunc 53
libFunc__atanhl :: LibFunc
libFunc__atanhl = LibFunc 54
libFunc__atanl :: LibFunc
libFunc__atanl = LibFunc 55
libFunc__atof :: LibFunc
libFunc__atof = LibFunc 56
libFunc__atoi :: LibFunc
libFunc__atoi = LibFunc 57
libFunc__atol :: LibFunc
libFunc__atol = LibFunc 58
libFunc__atoll :: LibFunc
libFunc__atoll = LibFunc 59
libFunc__bcmp :: LibFunc
libFunc__bcmp = LibFunc 60
libFunc__bcopy :: LibFunc
libFunc__bcopy = LibFunc 61
libFunc__bzero :: LibFunc
libFunc__bzero = LibFunc 62
libFunc__calloc :: LibFunc
libFunc__calloc = LibFunc 63
libFunc__cbrt :: LibFunc
libFunc__cbrt = LibFunc 64
libFunc__cbrtf :: LibFunc
libFunc__cbrtf = LibFunc 65
libFunc__cbrtl :: LibFunc
libFunc__cbrtl = LibFunc 66
libFunc__ceil :: LibFunc
libFunc__ceil = LibFunc 67
libFunc__ceilf :: LibFunc
libFunc__ceilf :: LibFunc
libFunc__ceilf = CUInt -> LibFunc
LibFunc 68
libFunc__ceill :: LibFunc
libFunc__ceill :: LibFunc
libFunc__ceill = CUInt -> LibFunc
LibFunc 69
libFunc__chmod :: LibFunc
libFunc__chmod :: LibFunc
libFunc__chmod = CUInt -> LibFunc
LibFunc 70
libFunc__chown :: LibFunc
libFunc__chown :: LibFunc
libFunc__chown = CUInt -> LibFunc
LibFunc 71
libFunc__clearerr :: LibFunc
libFunc__clearerr :: LibFunc
libFunc__clearerr = CUInt -> LibFunc
LibFunc 72
libFunc__closedir :: LibFunc
libFunc__closedir :: LibFunc
libFunc__closedir = CUInt -> LibFunc
LibFunc 73
libFunc__copysign :: LibFunc
libFunc__copysign :: LibFunc
libFunc__copysign = CUInt -> LibFunc
LibFunc 74
libFunc__copysignf :: LibFunc
libFunc__copysignf :: LibFunc
libFunc__copysignf = CUInt -> LibFunc
LibFunc 75
libFunc__copysignl :: LibFunc
libFunc__copysignl :: LibFunc
libFunc__copysignl = CUInt -> LibFunc
LibFunc 76
libFunc__cos :: LibFunc
libFunc__cos :: LibFunc
libFunc__cos = CUInt -> LibFunc
LibFunc 77
libFunc__cosf :: LibFunc
libFunc__cosf :: LibFunc
libFunc__cosf = CUInt -> LibFunc
LibFunc 78
libFunc__cosh :: LibFunc
libFunc__cosh :: LibFunc
libFunc__cosh = CUInt -> LibFunc
LibFunc 79
libFunc__coshf :: LibFunc
libFunc__coshf :: LibFunc
libFunc__coshf = CUInt -> LibFunc
LibFunc 80
libFunc__coshl :: LibFunc
libFunc__coshl :: LibFunc
libFunc__coshl = CUInt -> LibFunc
LibFunc 81
libFunc__cosl :: LibFunc
libFunc__cosl :: LibFunc
libFunc__cosl = CUInt -> LibFunc
LibFunc 82
libFunc__ctermid :: LibFunc
libFunc__ctermid :: LibFunc
libFunc__ctermid = CUInt -> LibFunc
LibFunc 83
libFunc__exp :: LibFunc
libFunc__exp :: LibFunc
libFunc__exp = CUInt -> LibFunc
LibFunc 84
libFunc__exp10 :: LibFunc
libFunc__exp10 :: LibFunc
libFunc__exp10 = CUInt -> LibFunc
LibFunc 85
libFunc__exp10f :: LibFunc
libFunc__exp10f :: LibFunc
libFunc__exp10f = CUInt -> LibFunc
LibFunc 86
libFunc__exp10l :: LibFunc
libFunc__exp10l :: LibFunc
libFunc__exp10l = CUInt -> LibFunc
LibFunc 87
libFunc__exp2 :: LibFunc
libFunc__exp2 :: LibFunc
libFunc__exp2 = CUInt -> LibFunc
LibFunc 88
libFunc__exp2f :: LibFunc
libFunc__exp2f :: LibFunc
libFunc__exp2f = CUInt -> LibFunc
LibFunc 89
libFunc__exp2l :: LibFunc
libFunc__exp2l :: LibFunc
libFunc__exp2l = CUInt -> LibFunc
LibFunc 90
libFunc__expf :: LibFunc
libFunc__expf :: LibFunc
libFunc__expf = CUInt -> LibFunc
LibFunc 91
libFunc__expl :: LibFunc
libFunc__expl :: LibFunc
libFunc__expl = CUInt -> LibFunc
LibFunc 92
libFunc__expm1 :: LibFunc
libFunc__expm1 :: LibFunc
libFunc__expm1 = CUInt -> LibFunc
LibFunc 93
libFunc__expm1f :: LibFunc
libFunc__expm1f :: LibFunc
libFunc__expm1f = CUInt -> LibFunc
LibFunc 94
libFunc__expm1l :: LibFunc
libFunc__expm1l :: LibFunc
libFunc__expm1l = CUInt -> LibFunc
LibFunc 95
libFunc__fabs :: LibFunc
libFunc__fabs :: LibFunc
libFunc__fabs = CUInt -> LibFunc
LibFunc 96
libFunc__fabsf :: LibFunc
libFunc__fabsf :: LibFunc
libFunc__fabsf = CUInt -> LibFunc
LibFunc 97
libFunc__fabsl :: LibFunc
libFunc__fabsl :: LibFunc
libFunc__fabsl = CUInt -> LibFunc
LibFunc 98
libFunc__fclose :: LibFunc
libFunc__fclose :: LibFunc
libFunc__fclose = CUInt -> LibFunc
LibFunc 99
libFunc__fdopen :: LibFunc
libFunc__fdopen :: LibFunc
libFunc__fdopen = CUInt -> LibFunc
LibFunc 100
libFunc__feof :: LibFunc
libFunc__feof :: LibFunc
libFunc__feof = CUInt -> LibFunc
LibFunc 101
libFunc__ferror :: LibFunc
libFunc__ferror :: LibFunc
libFunc__ferror = CUInt -> LibFunc
LibFunc 102
libFunc__fflush :: LibFunc
libFunc__fflush :: LibFunc
libFunc__fflush = CUInt -> LibFunc
LibFunc 103
libFunc__ffs :: LibFunc
libFunc__ffs :: LibFunc
libFunc__ffs = CUInt -> LibFunc
LibFunc 104
libFunc__ffsl :: LibFunc
libFunc__ffsl :: LibFunc
libFunc__ffsl = CUInt -> LibFunc
LibFunc 105
libFunc__ffsll :: LibFunc
libFunc__ffsll :: LibFunc
libFunc__ffsll = CUInt -> LibFunc
LibFunc 106
libFunc__fgetc :: LibFunc
libFunc__fgetc :: LibFunc
libFunc__fgetc = CUInt -> LibFunc
LibFunc 107
libFunc__fgetpos :: LibFunc
libFunc__fgetpos :: LibFunc
libFunc__fgetpos = CUInt -> LibFunc
LibFunc 108
libFunc__fgets :: LibFunc
libFunc__fgets :: LibFunc
libFunc__fgets = CUInt -> LibFunc
LibFunc 109
libFunc__fileno :: LibFunc
libFunc__fileno :: LibFunc
libFunc__fileno = CUInt -> LibFunc
LibFunc 110
libFunc__fiprintf :: LibFunc
libFunc__fiprintf :: LibFunc
libFunc__fiprintf = CUInt -> LibFunc
LibFunc 111
libFunc__flockfile :: LibFunc
libFunc__flockfile :: LibFunc
libFunc__flockfile = CUInt -> LibFunc
LibFunc 112
libFunc__floor :: LibFunc
libFunc__floor :: LibFunc
libFunc__floor = CUInt -> LibFunc
LibFunc 113
libFunc__floorf :: LibFunc
libFunc__floorf :: LibFunc
libFunc__floorf = CUInt -> LibFunc
LibFunc 114
libFunc__floorl :: LibFunc
libFunc__floorl :: LibFunc
libFunc__floorl = CUInt -> LibFunc
LibFunc 115
libFunc__fmax :: LibFunc
libFunc__fmax :: LibFunc
libFunc__fmax = CUInt -> LibFunc
LibFunc 116
libFunc__fmaxf :: LibFunc
libFunc__fmaxf :: LibFunc
libFunc__fmaxf = CUInt -> LibFunc
LibFunc 117
libFunc__fmaxl :: LibFunc
libFunc__fmaxl :: LibFunc
libFunc__fmaxl = CUInt -> LibFunc
LibFunc 118
libFunc__fmin :: LibFunc
libFunc__fmin :: LibFunc
libFunc__fmin = CUInt -> LibFunc
LibFunc 119
libFunc__fminf :: LibFunc
libFunc__fminf :: LibFunc
libFunc__fminf = CUInt -> LibFunc
LibFunc 120
libFunc__fminl :: LibFunc
libFunc__fminl :: LibFunc
libFunc__fminl = CUInt -> LibFunc
LibFunc 121
libFunc__fmod :: LibFunc
libFunc__fmod :: LibFunc
libFunc__fmod = CUInt -> LibFunc
LibFunc 122
libFunc__fmodf :: LibFunc
libFunc__fmodf :: LibFunc
libFunc__fmodf = CUInt -> LibFunc
LibFunc 123
libFunc__fmodl :: LibFunc
libFunc__fmodl :: LibFunc
libFunc__fmodl = CUInt -> LibFunc
LibFunc 124
libFunc__fopen :: LibFunc
libFunc__fopen :: LibFunc
libFunc__fopen = CUInt -> LibFunc
LibFunc 125
libFunc__fopen64 :: LibFunc
libFunc__fopen64 :: LibFunc
libFunc__fopen64 = CUInt -> LibFunc
LibFunc 126
libFunc__fprintf :: LibFunc
libFunc__fprintf :: LibFunc
libFunc__fprintf = CUInt -> LibFunc
LibFunc 127
libFunc__fputc :: LibFunc
libFunc__fputc :: LibFunc
libFunc__fputc = CUInt -> LibFunc
LibFunc 128
libFunc__fputs :: LibFunc
libFunc__fputs :: LibFunc
libFunc__fputs = CUInt -> LibFunc
LibFunc 129
libFunc__fread :: LibFunc
libFunc__fread :: LibFunc
libFunc__fread = CUInt -> LibFunc
LibFunc 130
libFunc__free :: LibFunc
libFunc__free :: LibFunc
libFunc__free = CUInt -> LibFunc
LibFunc 131
libFunc__frexp :: LibFunc
libFunc__frexp :: LibFunc
libFunc__frexp = CUInt -> LibFunc
LibFunc 132
libFunc__frexpf :: LibFunc
libFunc__frexpf :: LibFunc
libFunc__frexpf = CUInt -> LibFunc
LibFunc 133
libFunc__frexpl :: LibFunc
libFunc__frexpl :: LibFunc
libFunc__frexpl = CUInt -> LibFunc
LibFunc 134
libFunc__fscanf :: LibFunc
libFunc__fscanf :: LibFunc
libFunc__fscanf = CUInt -> LibFunc
LibFunc 135
libFunc__fseek :: LibFunc
libFunc__fseek :: LibFunc
libFunc__fseek = CUInt -> LibFunc
LibFunc 136
libFunc__fseeko :: LibFunc
libFunc__fseeko :: LibFunc
libFunc__fseeko = CUInt -> LibFunc
LibFunc 137
libFunc__fseeko64 :: LibFunc
libFunc__fseeko64 :: LibFunc
libFunc__fseeko64 = CUInt -> LibFunc
LibFunc 138
libFunc__fsetpos :: LibFunc
libFunc__fsetpos :: LibFunc
libFunc__fsetpos = CUInt -> LibFunc
LibFunc 139
libFunc__fstat :: LibFunc
libFunc__fstat :: LibFunc
libFunc__fstat = CUInt -> LibFunc
LibFunc 140
libFunc__fstat64 :: LibFunc
libFunc__fstat64 :: LibFunc
libFunc__fstat64 = CUInt -> LibFunc
LibFunc 141
libFunc__fstatvfs :: LibFunc
libFunc__fstatvfs :: LibFunc
libFunc__fstatvfs = CUInt -> LibFunc
LibFunc 142
libFunc__fstatvfs64 :: LibFunc
libFunc__fstatvfs64 :: LibFunc
libFunc__fstatvfs64 = CUInt -> LibFunc
LibFunc 143
libFunc__ftell :: LibFunc
libFunc__ftell :: LibFunc
libFunc__ftell = CUInt -> LibFunc
LibFunc 144
libFunc__ftello :: LibFunc
libFunc__ftello :: LibFunc
libFunc__ftello = CUInt -> LibFunc
LibFunc 145
libFunc__ftello64 :: LibFunc
libFunc__ftello64 :: LibFunc
libFunc__ftello64 = CUInt -> LibFunc
LibFunc 146
libFunc__ftrylockfile :: LibFunc
libFunc__ftrylockfile :: LibFunc
libFunc__ftrylockfile = CUInt -> LibFunc
LibFunc 147
libFunc__funlockfile :: LibFunc
libFunc__funlockfile :: LibFunc
libFunc__funlockfile = CUInt -> LibFunc
LibFunc 148
libFunc__fwrite :: LibFunc
libFunc__fwrite :: LibFunc
libFunc__fwrite = CUInt -> LibFunc
LibFunc 149
libFunc__getc :: LibFunc
libFunc__getc :: LibFunc
libFunc__getc = CUInt -> LibFunc
LibFunc 150
libFunc__getc_unlocked :: LibFunc
libFunc__getc_unlocked :: LibFunc
libFunc__getc_unlocked = CUInt -> LibFunc
LibFunc 151
libFunc__getchar :: LibFunc
libFunc__getchar :: LibFunc
libFunc__getchar = CUInt -> LibFunc
LibFunc 152
libFunc__getenv :: LibFunc
libFunc__getenv :: LibFunc
libFunc__getenv = CUInt -> LibFunc
LibFunc 153
libFunc__getitimer :: LibFunc
libFunc__getitimer :: LibFunc
libFunc__getitimer = CUInt -> LibFunc
LibFunc 154
libFunc__getlogin_r :: LibFunc
libFunc__getlogin_r :: LibFunc
libFunc__getlogin_r = CUInt -> LibFunc
LibFunc 155
libFunc__getpwnam :: LibFunc
libFunc__getpwnam :: LibFunc
libFunc__getpwnam = CUInt -> LibFunc
LibFunc 156
libFunc__gets :: LibFunc
libFunc__gets :: LibFunc
libFunc__gets = CUInt -> LibFunc
LibFunc 157
libFunc__gettimeofday :: LibFunc
libFunc__gettimeofday :: LibFunc
libFunc__gettimeofday = CUInt -> LibFunc
LibFunc 158
libFunc__htonl :: LibFunc
libFunc__htonl :: LibFunc
libFunc__htonl = CUInt -> LibFunc
LibFunc 159
libFunc__htons :: LibFunc
libFunc__htons :: LibFunc
libFunc__htons = CUInt -> LibFunc
LibFunc 160
libFunc__iprintf :: LibFunc
libFunc__iprintf :: LibFunc
libFunc__iprintf = CUInt -> LibFunc
LibFunc 161
libFunc__isascii :: LibFunc
libFunc__isascii :: LibFunc
libFunc__isascii = CUInt -> LibFunc
LibFunc 162
libFunc__isdigit :: LibFunc
libFunc__isdigit :: LibFunc
libFunc__isdigit = CUInt -> LibFunc
LibFunc 163
libFunc__labs :: LibFunc
libFunc__labs :: LibFunc
libFunc__labs = CUInt -> LibFunc
LibFunc 164
libFunc__lchown :: LibFunc
libFunc__lchown :: LibFunc
libFunc__lchown = CUInt -> LibFunc
LibFunc 165
libFunc__ldexp :: LibFunc
libFunc__ldexp :: LibFunc
libFunc__ldexp = CUInt -> LibFunc
LibFunc 166
libFunc__ldexpf :: LibFunc
libFunc__ldexpf :: LibFunc
libFunc__ldexpf = CUInt -> LibFunc
LibFunc 167
libFunc__ldexpl :: LibFunc
libFunc__ldexpl :: LibFunc
libFunc__ldexpl = CUInt -> LibFunc
LibFunc 168
libFunc__llabs :: LibFunc
libFunc__llabs :: LibFunc
libFunc__llabs = CUInt -> LibFunc
LibFunc 169
libFunc__log :: LibFunc
libFunc__log :: LibFunc
libFunc__log = CUInt -> LibFunc
LibFunc 170
libFunc__log10 :: LibFunc
libFunc__log10 :: LibFunc
libFunc__log10 = CUInt -> LibFunc
LibFunc 171
libFunc__log10f :: LibFunc
libFunc__log10f :: LibFunc
libFunc__log10f = CUInt -> LibFunc
LibFunc 172
libFunc__log10l :: LibFunc
libFunc__log10l :: LibFunc
libFunc__log10l = CUInt -> LibFunc
LibFunc 173
libFunc__log1p :: LibFunc
libFunc__log1p :: LibFunc
libFunc__log1p = CUInt -> LibFunc
LibFunc 174
libFunc__log1pf :: LibFunc
libFunc__log1pf :: LibFunc
libFunc__log1pf = CUInt -> LibFunc
LibFunc 175
libFunc__log1pl :: LibFunc
libFunc__log1pl :: LibFunc
libFunc__log1pl = CUInt -> LibFunc
LibFunc 176
libFunc__log2 :: LibFunc
libFunc__log2 :: LibFunc
libFunc__log2 = CUInt -> LibFunc
LibFunc 177
libFunc__log2f :: LibFunc
libFunc__log2f :: LibFunc
libFunc__log2f = CUInt -> LibFunc
LibFunc 178
libFunc__log2l :: LibFunc
libFunc__log2l :: LibFunc
libFunc__log2l = CUInt -> LibFunc
LibFunc 179
libFunc__logb :: LibFunc
libFunc__logb :: LibFunc
libFunc__logb = CUInt -> LibFunc
LibFunc 180
libFunc__logbf :: LibFunc
libFunc__logbf :: LibFunc
libFunc__logbf = CUInt -> LibFunc
LibFunc 181
libFunc__logbl :: LibFunc
libFunc__logbl :: LibFunc
libFunc__logbl = CUInt -> LibFunc
LibFunc 182
libFunc__logf :: LibFunc
libFunc__logf :: LibFunc
libFunc__logf = CUInt -> LibFunc
LibFunc 183
libFunc__logl :: LibFunc
libFunc__logl :: LibFunc
libFunc__logl = CUInt -> LibFunc
LibFunc 184
libFunc__lstat :: LibFunc
libFunc__lstat :: LibFunc
libFunc__lstat = CUInt -> LibFunc
LibFunc 185
libFunc__lstat64 :: LibFunc
libFunc__lstat64 :: LibFunc
libFunc__lstat64 = CUInt -> LibFunc
LibFunc 186
libFunc__malloc :: LibFunc
libFunc__malloc :: LibFunc
libFunc__malloc = CUInt -> LibFunc
LibFunc 187
libFunc__memalign :: LibFunc
libFunc__memalign :: LibFunc
libFunc__memalign = CUInt -> LibFunc
LibFunc 188
libFunc__memccpy :: LibFunc
libFunc__memccpy :: LibFunc
libFunc__memccpy = CUInt -> LibFunc
LibFunc 189
libFunc__memchr :: LibFunc
libFunc__memchr :: LibFunc
libFunc__memchr = CUInt -> LibFunc
LibFunc 190
libFunc__memcmp :: LibFunc
libFunc__memcmp :: LibFunc
libFunc__memcmp = CUInt -> LibFunc
LibFunc 191
libFunc__memcpy :: LibFunc
libFunc__memcpy :: LibFunc
libFunc__memcpy = CUInt -> LibFunc
LibFunc 192
libFunc__memmove :: LibFunc
libFunc__memmove :: LibFunc
libFunc__memmove = CUInt -> LibFunc
LibFunc 193
libFunc__memrchr :: LibFunc
libFunc__memrchr :: LibFunc
libFunc__memrchr = CUInt -> LibFunc
LibFunc 194
libFunc__memset :: LibFunc
libFunc__memset :: LibFunc
libFunc__memset = CUInt -> LibFunc
LibFunc 195
libFunc__memset_pattern16 :: LibFunc
libFunc__memset_pattern16 :: LibFunc
libFunc__memset_pattern16 = CUInt -> LibFunc
LibFunc 196
libFunc__mkdir :: LibFunc
libFunc__mkdir :: LibFunc
libFunc__mkdir = CUInt -> LibFunc
LibFunc 197
libFunc__mktime :: LibFunc
libFunc__mktime :: LibFunc
libFunc__mktime = CUInt -> LibFunc
LibFunc 198
libFunc__modf :: LibFunc
libFunc__modf :: LibFunc
libFunc__modf = CUInt -> LibFunc
LibFunc 199
libFunc__modff :: LibFunc
libFunc__modff :: LibFunc
libFunc__modff = CUInt -> LibFunc
LibFunc 200
libFunc__modfl :: LibFunc
libFunc__modfl :: LibFunc
libFunc__modfl = CUInt -> LibFunc
LibFunc 201
libFunc__nearbyint :: LibFunc
libFunc__nearbyint :: LibFunc
libFunc__nearbyint = CUInt -> LibFunc
LibFunc 202
libFunc__nearbyintf :: LibFunc
libFunc__nearbyintf :: LibFunc
libFunc__nearbyintf = CUInt -> LibFunc
LibFunc 203
libFunc__nearbyintl :: LibFunc
libFunc__nearbyintl :: LibFunc
libFunc__nearbyintl = CUInt -> LibFunc
LibFunc 204
libFunc__ntohl :: LibFunc
libFunc__ntohl :: LibFunc
libFunc__ntohl = CUInt -> LibFunc
LibFunc 205
libFunc__ntohs :: LibFunc
libFunc__ntohs :: LibFunc
libFunc__ntohs = CUInt -> LibFunc
LibFunc 206
libFunc__open :: LibFunc
libFunc__open :: LibFunc
libFunc__open = CUInt -> LibFunc
LibFunc 207
libFunc__open64 :: LibFunc
libFunc__open64 :: LibFunc
libFunc__open64 = CUInt -> LibFunc
LibFunc 208
libFunc__opendir :: LibFunc
libFunc__opendir :: LibFunc
libFunc__opendir = CUInt -> LibFunc
LibFunc 209
libFunc__pclose :: LibFunc
libFunc__pclose :: LibFunc
libFunc__pclose = CUInt -> LibFunc
LibFunc 210
libFunc__perror :: LibFunc
libFunc__perror :: LibFunc
libFunc__perror = CUInt -> LibFunc
LibFunc 211
libFunc__popen :: LibFunc
libFunc__popen :: LibFunc
libFunc__popen = CUInt -> LibFunc
LibFunc 212
libFunc__posix_memalign :: LibFunc
libFunc__posix_memalign :: LibFunc
libFunc__posix_memalign = CUInt -> LibFunc
LibFunc 213
libFunc__pow :: LibFunc
libFunc__pow :: LibFunc
libFunc__pow = CUInt -> LibFunc
LibFunc 214
libFunc__powf :: LibFunc
libFunc__powf :: LibFunc
libFunc__powf = CUInt -> LibFunc
LibFunc 215
libFunc__powl :: LibFunc
libFunc__powl :: LibFunc
libFunc__powl = CUInt -> LibFunc
LibFunc 216
libFunc__pread :: LibFunc
libFunc__pread :: LibFunc
libFunc__pread = CUInt -> LibFunc
LibFunc 217
libFunc__printf :: LibFunc
libFunc__printf :: LibFunc
libFunc__printf = CUInt -> LibFunc
LibFunc 218
libFunc__putc :: LibFunc
libFunc__putc :: LibFunc
libFunc__putc = CUInt -> LibFunc
LibFunc 219
libFunc__putchar :: LibFunc
libFunc__putchar :: LibFunc
libFunc__putchar = CUInt -> LibFunc
LibFunc 220
libFunc__puts :: LibFunc
libFunc__puts :: LibFunc
libFunc__puts = CUInt -> LibFunc
LibFunc 221
libFunc__pwrite :: LibFunc
libFunc__pwrite :: LibFunc
libFunc__pwrite = CUInt -> LibFunc
LibFunc 222
libFunc__qsort :: LibFunc
libFunc__qsort :: LibFunc
libFunc__qsort = CUInt -> LibFunc
LibFunc 223
libFunc__read :: LibFunc
libFunc__read :: LibFunc
libFunc__read = CUInt -> LibFunc
LibFunc 224
libFunc__readlink :: LibFunc
libFunc__readlink :: LibFunc
libFunc__readlink = CUInt -> LibFunc
LibFunc 225
libFunc__realloc :: LibFunc
libFunc__realloc :: LibFunc
libFunc__realloc = CUInt -> LibFunc
LibFunc 226
libFunc__reallocf :: LibFunc
libFunc__reallocf :: LibFunc
libFunc__reallocf = CUInt -> LibFunc
LibFunc 227
libFunc__realpath :: LibFunc
libFunc__realpath :: LibFunc
libFunc__realpath = CUInt -> LibFunc
LibFunc 228
libFunc__remove :: LibFunc
libFunc__remove :: LibFunc
libFunc__remove = CUInt -> LibFunc
LibFunc 229
libFunc__rename :: LibFunc
libFunc__rename :: LibFunc
libFunc__rename = CUInt -> LibFunc
LibFunc 230
libFunc__rewind :: LibFunc
libFunc__rewind :: LibFunc
libFunc__rewind = CUInt -> LibFunc
LibFunc 231
libFunc__rint :: LibFunc
libFunc__rint :: LibFunc
libFunc__rint = CUInt -> LibFunc
LibFunc 232
libFunc__rintf :: LibFunc
libFunc__rintf :: LibFunc
libFunc__rintf = CUInt -> LibFunc
LibFunc 233
libFunc__rintl :: LibFunc
libFunc__rintl :: LibFunc
libFunc__rintl = CUInt -> LibFunc
LibFunc 234
libFunc__rmdir :: LibFunc
libFunc__rmdir :: LibFunc
libFunc__rmdir = CUInt -> LibFunc
LibFunc 235
libFunc__round :: LibFunc
libFunc__round :: LibFunc
libFunc__round = CUInt -> LibFunc
LibFunc 236
libFunc__roundf :: LibFunc
libFunc__roundf :: LibFunc
libFunc__roundf = CUInt -> LibFunc
LibFunc 237
libFunc__roundl :: LibFunc
libFunc__roundl :: LibFunc
libFunc__roundl = CUInt -> LibFunc
LibFunc 238
libFunc__scanf :: LibFunc
libFunc__scanf :: LibFunc
libFunc__scanf = CUInt -> LibFunc
LibFunc 239
libFunc__setbuf :: LibFunc
libFunc__setbuf :: LibFunc
libFunc__setbuf = CUInt -> LibFunc
LibFunc 240
libFunc__setitimer :: LibFunc
libFunc__setitimer :: LibFunc
libFunc__setitimer = CUInt -> LibFunc
LibFunc 241
libFunc__setvbuf :: LibFunc
libFunc__setvbuf :: LibFunc
libFunc__setvbuf = CUInt -> LibFunc
LibFunc 242
libFunc__sin :: LibFunc
libFunc__sin :: LibFunc
libFunc__sin = CUInt -> LibFunc
LibFunc 243
libFunc__sinf :: LibFunc
libFunc__sinf :: LibFunc
libFunc__sinf = CUInt -> LibFunc
LibFunc 244
libFunc__sinh :: LibFunc
libFunc__sinh :: LibFunc
libFunc__sinh = CUInt -> LibFunc
LibFunc 245
libFunc__sinhf :: LibFunc
libFunc__sinhf :: LibFunc
libFunc__sinhf = CUInt -> LibFunc
LibFunc 246
libFunc__sinhl :: LibFunc
libFunc__sinhl :: LibFunc
libFunc__sinhl = CUInt -> LibFunc
LibFunc 247
libFunc__sinl :: LibFunc
libFunc__sinl :: LibFunc
libFunc__sinl = CUInt -> LibFunc
LibFunc 248
libFunc__siprintf :: LibFunc
libFunc__siprintf :: LibFunc
libFunc__siprintf = CUInt -> LibFunc
LibFunc 249
libFunc__snprintf :: LibFunc
libFunc__snprintf :: LibFunc
libFunc__snprintf = CUInt -> LibFunc
LibFunc 250
libFunc__sprintf :: LibFunc
libFunc__sprintf :: LibFunc
libFunc__sprintf = CUInt -> LibFunc
LibFunc 251
libFunc__sqrt :: LibFunc
libFunc__sqrt :: LibFunc
libFunc__sqrt = CUInt -> LibFunc
LibFunc 252
libFunc__sqrtf :: LibFunc
libFunc__sqrtf :: LibFunc
libFunc__sqrtf = CUInt -> LibFunc
LibFunc 253
libFunc__sqrtl :: LibFunc
libFunc__sqrtl :: LibFunc
libFunc__sqrtl = CUInt -> LibFunc
LibFunc 254
libFunc__sscanf :: LibFunc
libFunc__sscanf :: LibFunc
libFunc__sscanf = CUInt -> LibFunc
LibFunc 255
libFunc__stat :: LibFunc
libFunc__stat :: LibFunc
libFunc__stat = CUInt -> LibFunc
LibFunc 256
libFunc__stat64 :: LibFunc
libFunc__stat64 :: LibFunc
libFunc__stat64 = CUInt -> LibFunc
LibFunc 257
libFunc__statvfs :: LibFunc
libFunc__statvfs :: LibFunc
libFunc__statvfs = CUInt -> LibFunc
LibFunc 258
libFunc__statvfs64 :: LibFunc
libFunc__statvfs64 :: LibFunc
libFunc__statvfs64 = CUInt -> LibFunc
LibFunc 259
libFunc__stpcpy :: LibFunc
libFunc__stpcpy :: LibFunc
libFunc__stpcpy = CUInt -> LibFunc
LibFunc 260
libFunc__stpncpy :: LibFunc
libFunc__stpncpy :: LibFunc
libFunc__stpncpy = CUInt -> LibFunc
LibFunc 261
libFunc__strcasecmp :: LibFunc
libFunc__strcasecmp :: LibFunc
libFunc__strcasecmp = CUInt -> LibFunc
LibFunc 262
libFunc__strcat :: LibFunc
libFunc__strcat :: LibFunc
libFunc__strcat = CUInt -> LibFunc
LibFunc 263
libFunc__strchr :: LibFunc
libFunc__strchr :: LibFunc
libFunc__strchr = CUInt -> LibFunc
LibFunc 264
libFunc__strcmp :: LibFunc
libFunc__strcmp :: LibFunc
libFunc__strcmp = CUInt -> LibFunc
LibFunc 265
libFunc__strcoll :: LibFunc
libFunc__strcoll :: LibFunc
libFunc__strcoll = CUInt -> LibFunc
LibFunc 266
libFunc__strcpy :: LibFunc
libFunc__strcpy :: LibFunc
libFunc__strcpy = CUInt -> LibFunc
LibFunc 267
libFunc__strcspn :: LibFunc
libFunc__strcspn :: LibFunc
libFunc__strcspn = CUInt -> LibFunc
LibFunc 268
libFunc__strdup :: LibFunc
libFunc__strdup :: LibFunc
libFunc__strdup = CUInt -> LibFunc
LibFunc 269
libFunc__strlen :: LibFunc
libFunc__strlen :: LibFunc
libFunc__strlen = CUInt -> LibFunc
LibFunc 270
libFunc__strncasecmp :: LibFunc
libFunc__strncasecmp :: LibFunc
libFunc__strncasecmp = CUInt -> LibFunc
LibFunc 271
libFunc__strncat :: LibFunc
libFunc__strncat :: LibFunc
libFunc__strncat = CUInt -> LibFunc
LibFunc 272
libFunc__strncmp :: LibFunc
libFunc__strncmp :: LibFunc
libFunc__strncmp = CUInt -> LibFunc
LibFunc 273
libFunc__strncpy :: LibFunc
libFunc__strncpy :: LibFunc
libFunc__strncpy = CUInt -> LibFunc
LibFunc 274
libFunc__strndup :: LibFunc
libFunc__strndup :: LibFunc
libFunc__strndup = CUInt -> LibFunc
LibFunc 275
libFunc__strnlen :: LibFunc
libFunc__strnlen :: LibFunc
libFunc__strnlen = CUInt -> LibFunc
LibFunc 276
libFunc__strpbrk :: LibFunc
libFunc__strpbrk :: LibFunc
libFunc__strpbrk = CUInt -> LibFunc
LibFunc 277
libFunc__strrchr :: LibFunc
libFunc__strrchr :: LibFunc
libFunc__strrchr = CUInt -> LibFunc
LibFunc 278
libFunc__strspn :: LibFunc
libFunc__strspn :: LibFunc
libFunc__strspn = CUInt -> LibFunc
LibFunc 279
libFunc__strstr :: LibFunc
libFunc__strstr :: LibFunc
libFunc__strstr = CUInt -> LibFunc
LibFunc 280
libFunc__strtod :: LibFunc
libFunc__strtod :: LibFunc
libFunc__strtod = CUInt -> LibFunc
LibFunc 281
libFunc__strtof :: LibFunc
libFunc__strtof :: LibFunc
libFunc__strtof = CUInt -> LibFunc
LibFunc 282
libFunc__strtok :: LibFunc
libFunc__strtok :: LibFunc
libFunc__strtok = CUInt -> LibFunc
LibFunc 283
libFunc__strtok_r :: LibFunc
libFunc__strtok_r :: LibFunc
libFunc__strtok_r = CUInt -> LibFunc
LibFunc 284
libFunc__strtol :: LibFunc
libFunc__strtol :: LibFunc
libFunc__strtol = CUInt -> LibFunc
LibFunc 285
libFunc__strtold :: LibFunc
libFunc__strtold :: LibFunc
libFunc__strtold = CUInt -> LibFunc
LibFunc 286
libFunc__strtoll :: LibFunc
libFunc__strtoll :: LibFunc
libFunc__strtoll = CUInt -> LibFunc
LibFunc 287
libFunc__strtoul :: LibFunc
libFunc__strtoul :: LibFunc
libFunc__strtoul = CUInt -> LibFunc
LibFunc 288
libFunc__strtoull :: LibFunc
libFunc__strtoull :: LibFunc
libFunc__strtoull = CUInt -> LibFunc
LibFunc 289
libFunc__strxfrm :: LibFunc
libFunc__strxfrm :: LibFunc
libFunc__strxfrm = CUInt -> LibFunc
LibFunc 290
libFunc__system :: LibFunc
libFunc__system :: LibFunc
libFunc__system = CUInt -> LibFunc
LibFunc 291
libFunc__tan :: LibFunc
libFunc__tan :: LibFunc
libFunc__tan = CUInt -> LibFunc
LibFunc 292
libFunc__tanf :: LibFunc
libFunc__tanf :: LibFunc
libFunc__tanf = CUInt -> LibFunc
LibFunc 293
libFunc__tanh :: LibFunc
libFunc__tanh :: LibFunc
libFunc__tanh = CUInt -> LibFunc
LibFunc 294
libFunc__tanhf :: LibFunc
libFunc__tanhf :: LibFunc
libFunc__tanhf = CUInt -> LibFunc
LibFunc 295
libFunc__tanhl :: LibFunc
libFunc__tanhl :: LibFunc
libFunc__tanhl = CUInt -> LibFunc
LibFunc 296
libFunc__tanl :: LibFunc
libFunc__tanl :: LibFunc
libFunc__tanl = CUInt -> LibFunc
LibFunc 297
libFunc__times :: LibFunc
libFunc__times :: LibFunc
libFunc__times = CUInt -> LibFunc
LibFunc 298
libFunc__tmpfile :: LibFunc
libFunc__tmpfile :: LibFunc
libFunc__tmpfile = CUInt -> LibFunc
LibFunc 299
libFunc__tmpfile64 :: LibFunc
libFunc__tmpfile64 :: LibFunc
libFunc__tmpfile64 = CUInt -> LibFunc
LibFunc 300
libFunc__toascii :: LibFunc
libFunc__toascii :: LibFunc
libFunc__toascii = CUInt -> LibFunc
LibFunc 301
libFunc__trunc :: LibFunc
libFunc__trunc :: LibFunc
libFunc__trunc = CUInt -> LibFunc
LibFunc 302
libFunc__truncf :: LibFunc
libFunc__truncf :: LibFunc
libFunc__truncf = CUInt -> LibFunc
LibFunc 303
libFunc__truncl :: LibFunc
libFunc__truncl :: LibFunc
libFunc__truncl = CUInt -> LibFunc
LibFunc 304
libFunc__uname :: LibFunc
libFunc__uname :: LibFunc
libFunc__uname = CUInt -> LibFunc
LibFunc 305
libFunc__ungetc :: LibFunc
libFunc__ungetc :: LibFunc
libFunc__ungetc = CUInt -> LibFunc
LibFunc 306
libFunc__unlink :: LibFunc
libFunc__unlink :: LibFunc
libFunc__unlink = CUInt -> LibFunc
LibFunc 307
libFunc__unsetenv :: LibFunc
libFunc__unsetenv :: LibFunc
libFunc__unsetenv = CUInt -> LibFunc
LibFunc 308
libFunc__utime :: LibFunc
libFunc__utime :: LibFunc
libFunc__utime = CUInt -> LibFunc
LibFunc 309
libFunc__utimes :: LibFunc
libFunc__utimes :: LibFunc
libFunc__utimes = CUInt -> LibFunc
LibFunc 310
libFunc__valloc :: LibFunc
libFunc__valloc :: LibFunc
libFunc__valloc = CUInt -> LibFunc
LibFunc 311
libFunc__vfprintf :: LibFunc
libFunc__vfprintf :: LibFunc
libFunc__vfprintf = CUInt -> LibFunc
LibFunc 312
libFunc__vfscanf :: LibFunc
libFunc__vfscanf :: LibFunc
libFunc__vfscanf = CUInt -> LibFunc
LibFunc 313
libFunc__vprintf :: LibFunc
libFunc__vprintf :: LibFunc
libFunc__vprintf = CUInt -> LibFunc
LibFunc 314
libFunc__vscanf :: LibFunc
libFunc__vscanf :: LibFunc
libFunc__vscanf = CUInt -> LibFunc
LibFunc 315
libFunc__vsnprintf :: LibFunc
libFunc__vsnprintf :: LibFunc
libFunc__vsnprintf = CUInt -> LibFunc
LibFunc 316
libFunc__vsprintf :: LibFunc
libFunc__vsprintf :: LibFunc
libFunc__vsprintf = CUInt -> LibFunc
LibFunc 317
libFunc__vsscanf :: LibFunc
libFunc__vsscanf :: LibFunc
libFunc__vsscanf = CUInt -> LibFunc
LibFunc 318
libFunc__write :: LibFunc
libFunc__write :: LibFunc
libFunc__write = CUInt -> LibFunc
LibFunc 319
libFunc__P :: QuasiQuoter
libFunc__P :: QuasiQuoter
libFunc__P = QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter {
  quoteExp :: String -> Q Exp
quoteExp = String -> Q Exp
forall a. HasCallStack => a
undefined,
  quotePat :: String -> Q Pat
quotePat = \s :: String
s -> (forall b. Data b => b -> Maybe (Q Pat)) -> LibFunc -> Q Pat
forall a.
Data a =>
(forall b. Data b => b -> Maybe (Q Pat)) -> a -> Q Pat
dataToPatQ (Maybe (Q Pat) -> b -> Maybe (Q Pat)
forall a b. a -> b -> a
const Maybe (Q Pat)
forall a. Maybe a
Nothing) (LibFunc -> Q Pat) -> LibFunc -> Q Pat
forall a b. (a -> b) -> a -> b
$ case String
s of
    "under_IO_getc" -> LibFunc
libFunc__under_IO_getc
    "under_IO_putc" -> LibFunc
libFunc__under_IO_putc
    "ZdaPv" -> LibFunc
libFunc__ZdaPv
    "ZdaPvRKSt9nothrow_t" -> LibFunc
libFunc__ZdaPvRKSt9nothrow_t
    "ZdlPv" -> LibFunc
libFunc__ZdlPv
    "ZdlPvRKSt9nothrow_t" -> LibFunc
libFunc__ZdlPvRKSt9nothrow_t
    "Znaj" -> LibFunc
libFunc__Znaj
    "ZnajRKSt9nothrow_t" -> LibFunc
libFunc__ZnajRKSt9nothrow_t
    "Znam" -> LibFunc
libFunc__Znam
    "ZnamRKSt9nothrow_t" -> LibFunc
libFunc__ZnamRKSt9nothrow_t
    "Znwj" -> LibFunc
libFunc__Znwj
    "ZnwjRKSt9nothrow_t" -> LibFunc
libFunc__ZnwjRKSt9nothrow_t
    "Znwm" -> LibFunc
libFunc__Znwm
    "ZnwmRKSt9nothrow_t" -> LibFunc
libFunc__ZnwmRKSt9nothrow_t
    "cospi" -> LibFunc
libFunc__cospi
    "cospif" -> LibFunc
libFunc__cospif
    "cxa_atexit" -> LibFunc
libFunc__cxa_atexit
    "cxa_guard_abort" -> LibFunc
libFunc__cxa_guard_abort
    "cxa_guard_acquire" -> LibFunc
libFunc__cxa_guard_acquire
    "cxa_guard_release" -> LibFunc
libFunc__cxa_guard_release
    "dunder_isoc99_scanf" -> LibFunc
libFunc__dunder_isoc99_scanf
    "dunder_isoc99_sscanf" -> LibFunc
libFunc__dunder_isoc99_sscanf
    "memcpy_chk" -> LibFunc
libFunc__memcpy_chk
    "sincospi_stret" -> LibFunc
libFunc__sincospi_stret
    "sincospif_stret" -> LibFunc
libFunc__sincospif_stret
    "sinpi" -> LibFunc
libFunc__sinpi
    "sinpif" -> LibFunc
libFunc__sinpif
    "sqrt_finite" -> LibFunc
libFunc__sqrt_finite
    "sqrtf_finite" -> LibFunc
libFunc__sqrtf_finite
    "sqrtl_finite" -> LibFunc
libFunc__sqrtl_finite
    "dunder_strdup" -> LibFunc
libFunc__dunder_strdup
    "dunder_strndup" -> LibFunc
libFunc__dunder_strndup
    "dunder_strtok_r" -> LibFunc
libFunc__dunder_strtok_r
    "abs" -> LibFunc
libFunc__abs
    "access" -> LibFunc
libFunc__access
    "acos" -> LibFunc
libFunc__acos
    "acosf" -> LibFunc
libFunc__acosf
    "acosh" -> LibFunc
libFunc__acosh
    "acoshf" -> LibFunc
libFunc__acoshf
    "acoshl" -> LibFunc
libFunc__acoshl
    "acosl" -> LibFunc
libFunc__acosl
    "asin" -> LibFunc
libFunc__asin
    "asinf" -> LibFunc
libFunc__asinf
    "asinh" -> LibFunc
libFunc__asinh
    "asinhf" -> LibFunc
libFunc__asinhf
    "asinhl" -> LibFunc
libFunc__asinhl
    "asinl" -> LibFunc
libFunc__asinl
    "atan" -> LibFunc
libFunc__atan
    "atan2" -> LibFunc
libFunc__atan2
    "atan2f" -> LibFunc
libFunc__atan2f
    "atan2l" -> LibFunc
libFunc__atan2l
    "atanf" -> LibFunc
libFunc__atanf
    "atanh" -> LibFunc
libFunc__atanh
    "atanhf" -> LibFunc
libFunc__atanhf
    "atanhl" -> LibFunc
libFunc__atanhl
    "atanl" -> LibFunc
libFunc__atanl
    "atof" -> LibFunc
libFunc__atof
    "atoi" -> LibFunc
libFunc__atoi
    "atol" -> LibFunc
libFunc__atol
    "atoll" -> LibFunc
libFunc__atoll
    "bcmp" -> LibFunc
libFunc__bcmp
    "bcopy" -> LibFunc
libFunc__bcopy
    "bzero" -> LibFunc
libFunc__bzero
    "calloc" -> LibFunc
libFunc__calloc
    "cbrt" -> LibFunc
libFunc__cbrt
    "cbrtf" -> LibFunc
libFunc__cbrtf
    "cbrtl" -> LibFunc
libFunc__cbrtl
    "ceil" -> LibFunc
libFunc__ceil
    "ceilf" -> LibFunc
libFunc__ceilf
    "ceill" -> LibFunc
libFunc__ceill
    "chmod" -> LibFunc
libFunc__chmod
    "chown" -> LibFunc
libFunc__chown
    "clearerr" -> LibFunc
libFunc__clearerr
    "closedir" -> LibFunc
libFunc__closedir
    "copysign" -> LibFunc
libFunc__copysign
    "copysignf" -> LibFunc
libFunc__copysignf
    "copysignl" -> LibFunc
libFunc__copysignl
    "cos" -> LibFunc
libFunc__cos
    "cosf" -> LibFunc
libFunc__cosf
    "cosh" -> LibFunc
libFunc__cosh
    "coshf" -> LibFunc
libFunc__coshf
    "coshl" -> LibFunc
libFunc__coshl
    "cosl" -> LibFunc
libFunc__cosl
    "ctermid" -> LibFunc
libFunc__ctermid
    "exp" -> LibFunc
libFunc__exp
    "exp10" -> LibFunc
libFunc__exp10
    "exp10f" -> LibFunc
libFunc__exp10f
    "exp10l" -> LibFunc
libFunc__exp10l
    "exp2" -> LibFunc
libFunc__exp2
    "exp2f" -> LibFunc
libFunc__exp2f
    "exp2l" -> LibFunc
libFunc__exp2l
    "expf" -> LibFunc
libFunc__expf
    "expl" -> LibFunc
libFunc__expl
    "expm1" -> LibFunc
libFunc__expm1
    "expm1f" -> LibFunc
libFunc__expm1f
    "expm1l" -> LibFunc
libFunc__expm1l
    "fabs" -> LibFunc
libFunc__fabs
    "fabsf" -> LibFunc
libFunc__fabsf
    "fabsl" -> LibFunc
libFunc__fabsl
    "fclose" -> LibFunc
libFunc__fclose
    "fdopen" -> LibFunc
libFunc__fdopen
    "feof" -> LibFunc
libFunc__feof
    "ferror" -> LibFunc
libFunc__ferror
    "fflush" -> LibFunc
libFunc__fflush
    "ffs" -> LibFunc
libFunc__ffs
    "ffsl" -> LibFunc
libFunc__ffsl
    "ffsll" -> LibFunc
libFunc__ffsll
    "fgetc" -> LibFunc
libFunc__fgetc
    "fgetpos" -> LibFunc
libFunc__fgetpos
    "fgets" -> LibFunc
libFunc__fgets
    "fileno" -> LibFunc
libFunc__fileno
    "fiprintf" -> LibFunc
libFunc__fiprintf
    "flockfile" -> LibFunc
libFunc__flockfile
    "floor" -> LibFunc
libFunc__floor
    "floorf" -> LibFunc
libFunc__floorf
    "floorl" -> LibFunc
libFunc__floorl
    "fmax" -> LibFunc
libFunc__fmax
    "fmaxf" -> LibFunc
libFunc__fmaxf
    "fmaxl" -> LibFunc
libFunc__fmaxl
    "fmin" -> LibFunc
libFunc__fmin
    "fminf" -> LibFunc
libFunc__fminf
    "fminl" -> LibFunc
libFunc__fminl
    "fmod" -> LibFunc
libFunc__fmod
    "fmodf" -> LibFunc
libFunc__fmodf
    "fmodl" -> LibFunc
libFunc__fmodl
    "fopen" -> LibFunc
libFunc__fopen
    "fopen64" -> LibFunc
libFunc__fopen64
    "fprintf" -> LibFunc
libFunc__fprintf
    "fputc" -> LibFunc
libFunc__fputc
    "fputs" -> LibFunc
libFunc__fputs
    "fread" -> LibFunc
libFunc__fread
    "free" -> LibFunc
libFunc__free
    "frexp" -> LibFunc
libFunc__frexp
    "frexpf" -> LibFunc
libFunc__frexpf
    "frexpl" -> LibFunc
libFunc__frexpl
    "fscanf" -> LibFunc
libFunc__fscanf
    "fseek" -> LibFunc
libFunc__fseek
    "fseeko" -> LibFunc
libFunc__fseeko
    "fseeko64" -> LibFunc
libFunc__fseeko64
    "fsetpos" -> LibFunc
libFunc__fsetpos
    "fstat" -> LibFunc
libFunc__fstat
    "fstat64" -> LibFunc
libFunc__fstat64
    "fstatvfs" -> LibFunc
libFunc__fstatvfs
    "fstatvfs64" -> LibFunc
libFunc__fstatvfs64
    "ftell" -> LibFunc
libFunc__ftell
    "ftello" -> LibFunc
libFunc__ftello
    "ftello64" -> LibFunc
libFunc__ftello64
    "ftrylockfile" -> LibFunc
libFunc__ftrylockfile
    "funlockfile" -> LibFunc
libFunc__funlockfile
    "fwrite" -> LibFunc
libFunc__fwrite
    "getc" -> LibFunc
libFunc__getc
    "getc_unlocked" -> LibFunc
libFunc__getc_unlocked
    "getchar" -> LibFunc
libFunc__getchar
    "getenv" -> LibFunc
libFunc__getenv
    "getitimer" -> LibFunc
libFunc__getitimer
    "getlogin_r" -> LibFunc
libFunc__getlogin_r
    "getpwnam" -> LibFunc
libFunc__getpwnam
    "gets" -> LibFunc
libFunc__gets
    "gettimeofday" -> LibFunc
libFunc__gettimeofday
    "htonl" -> LibFunc
libFunc__htonl
    "htons" -> LibFunc
libFunc__htons
    "iprintf" -> LibFunc
libFunc__iprintf
    "isascii" -> LibFunc
libFunc__isascii
    "isdigit" -> LibFunc
libFunc__isdigit
    "labs" -> LibFunc
libFunc__labs
    "lchown" -> LibFunc
libFunc__lchown
    "ldexp" -> LibFunc
libFunc__ldexp
    "ldexpf" -> LibFunc
libFunc__ldexpf
    "ldexpl" -> LibFunc
libFunc__ldexpl
    "llabs" -> LibFunc
libFunc__llabs
    "log" -> LibFunc
libFunc__log
    "log10" -> LibFunc
libFunc__log10
    "log10f" -> LibFunc
libFunc__log10f
    "log10l" -> LibFunc
libFunc__log10l
    "log1p" -> LibFunc
libFunc__log1p
    "log1pf" -> LibFunc
libFunc__log1pf
    "log1pl" -> LibFunc
libFunc__log1pl
    "log2" -> LibFunc
libFunc__log2
    "log2f" -> LibFunc
libFunc__log2f
    "log2l" -> LibFunc
libFunc__log2l
    "logb" -> LibFunc
libFunc__logb
    "logbf" -> LibFunc
libFunc__logbf
    "logbl" -> LibFunc
libFunc__logbl
    "logf" -> LibFunc
libFunc__logf
    "logl" -> LibFunc
libFunc__logl
    "lstat" -> LibFunc
libFunc__lstat
    "lstat64" -> LibFunc
libFunc__lstat64
    "malloc" -> LibFunc
libFunc__malloc
    "memalign" -> LibFunc
libFunc__memalign
    "memccpy" -> LibFunc
libFunc__memccpy
    "memchr" -> LibFunc
libFunc__memchr
    "memcmp" -> LibFunc
libFunc__memcmp
    "memcpy" -> LibFunc
libFunc__memcpy
    "memmove" -> LibFunc
libFunc__memmove
    "memrchr" -> LibFunc
libFunc__memrchr
    "memset" -> LibFunc
libFunc__memset
    "memset_pattern16" -> LibFunc
libFunc__memset_pattern16
    "mkdir" -> LibFunc
libFunc__mkdir
    "mktime" -> LibFunc
libFunc__mktime
    "modf" -> LibFunc
libFunc__modf
    "modff" -> LibFunc
libFunc__modff
    "modfl" -> LibFunc
libFunc__modfl
    "nearbyint" -> LibFunc
libFunc__nearbyint
    "nearbyintf" -> LibFunc
libFunc__nearbyintf
    "nearbyintl" -> LibFunc
libFunc__nearbyintl
    "ntohl" -> LibFunc
libFunc__ntohl
    "ntohs" -> LibFunc
libFunc__ntohs
    "open" -> LibFunc
libFunc__open
    "open64" -> LibFunc
libFunc__open64
    "opendir" -> LibFunc
libFunc__opendir
    "pclose" -> LibFunc
libFunc__pclose
    "perror" -> LibFunc
libFunc__perror
    "popen" -> LibFunc
libFunc__popen
    "posix_memalign" -> LibFunc
libFunc__posix_memalign
    "pow" -> LibFunc
libFunc__pow
    "powf" -> LibFunc
libFunc__powf
    "powl" -> LibFunc
libFunc__powl
    "pread" -> LibFunc
libFunc__pread
    "printf" -> LibFunc
libFunc__printf
    "putc" -> LibFunc
libFunc__putc
    "putchar" -> LibFunc
libFunc__putchar
    "puts" -> LibFunc
libFunc__puts
    "pwrite" -> LibFunc
libFunc__pwrite
    "qsort" -> LibFunc
libFunc__qsort
    "read" -> LibFunc
libFunc__read
    "readlink" -> LibFunc
libFunc__readlink
    "realloc" -> LibFunc
libFunc__realloc
    "reallocf" -> LibFunc
libFunc__reallocf
    "realpath" -> LibFunc
libFunc__realpath
    "remove" -> LibFunc
libFunc__remove
    "rename" -> LibFunc
libFunc__rename
    "rewind" -> LibFunc
libFunc__rewind
    "rint" -> LibFunc
libFunc__rint
    "rintf" -> LibFunc
libFunc__rintf
    "rintl" -> LibFunc
libFunc__rintl
    "rmdir" -> LibFunc
libFunc__rmdir
    "round" -> LibFunc
libFunc__round
    "roundf" -> LibFunc
libFunc__roundf
    "roundl" -> LibFunc
libFunc__roundl
    "scanf" -> LibFunc
libFunc__scanf
    "setbuf" -> LibFunc
libFunc__setbuf
    "setitimer" -> LibFunc
libFunc__setitimer
    "setvbuf" -> LibFunc
libFunc__setvbuf
    "sin" -> LibFunc
libFunc__sin
    "sinf" -> LibFunc
libFunc__sinf
    "sinh" -> LibFunc
libFunc__sinh
    "sinhf" -> LibFunc
libFunc__sinhf
    "sinhl" -> LibFunc
libFunc__sinhl
    "sinl" -> LibFunc
libFunc__sinl
    "siprintf" -> LibFunc
libFunc__siprintf
    "snprintf" -> LibFunc
libFunc__snprintf
    "sprintf" -> LibFunc
libFunc__sprintf
    "sqrt" -> LibFunc
libFunc__sqrt
    "sqrtf" -> LibFunc
libFunc__sqrtf
    "sqrtl" -> LibFunc
libFunc__sqrtl
    "sscanf" -> LibFunc
libFunc__sscanf
    "stat" -> LibFunc
libFunc__stat
    "stat64" -> LibFunc
libFunc__stat64
    "statvfs" -> LibFunc
libFunc__statvfs
    "statvfs64" -> LibFunc
libFunc__statvfs64
    "stpcpy" -> LibFunc
libFunc__stpcpy
    "stpncpy" -> LibFunc
libFunc__stpncpy
    "strcasecmp" -> LibFunc
libFunc__strcasecmp
    "strcat" -> LibFunc
libFunc__strcat
    "strchr" -> LibFunc
libFunc__strchr
    "strcmp" -> LibFunc
libFunc__strcmp
    "strcoll" -> LibFunc
libFunc__strcoll
    "strcpy" -> LibFunc
libFunc__strcpy
    "strcspn" -> LibFunc
libFunc__strcspn
    "strdup" -> LibFunc
libFunc__strdup
    "strlen" -> LibFunc
libFunc__strlen
    "strncasecmp" -> LibFunc
libFunc__strncasecmp
    "strncat" -> LibFunc
libFunc__strncat
    "strncmp" -> LibFunc
libFunc__strncmp
    "strncpy" -> LibFunc
libFunc__strncpy
    "strndup" -> LibFunc
libFunc__strndup
    "strnlen" -> LibFunc
libFunc__strnlen
    "strpbrk" -> LibFunc
libFunc__strpbrk
    "strrchr" -> LibFunc
libFunc__strrchr
    "strspn" -> LibFunc
libFunc__strspn
    "strstr" -> LibFunc
libFunc__strstr
    "strtod" -> LibFunc
libFunc__strtod
    "strtof" -> LibFunc
libFunc__strtof
    "strtok" -> LibFunc
libFunc__strtok
    "strtok_r" -> LibFunc
libFunc__strtok_r
    "strtol" -> LibFunc
libFunc__strtol
    "strtold" -> LibFunc
libFunc__strtold
    "strtoll" -> LibFunc
libFunc__strtoll
    "strtoul" -> LibFunc
libFunc__strtoul
    "strtoull" -> LibFunc
libFunc__strtoull
    "strxfrm" -> LibFunc
libFunc__strxfrm
    "system" -> LibFunc
libFunc__system
    "tan" -> LibFunc
libFunc__tan
    "tanf" -> LibFunc
libFunc__tanf
    "tanh" -> LibFunc
libFunc__tanh
    "tanhf" -> LibFunc
libFunc__tanhf
    "tanhl" -> LibFunc
libFunc__tanhl
    "tanl" -> LibFunc
libFunc__tanl
    "times" -> LibFunc
libFunc__times
    "tmpfile" -> LibFunc
libFunc__tmpfile
    "tmpfile64" -> LibFunc
libFunc__tmpfile64
    "toascii" -> LibFunc
libFunc__toascii
    "trunc" -> LibFunc
libFunc__trunc
    "truncf" -> LibFunc
libFunc__truncf
    "truncl" -> LibFunc
libFunc__truncl
    "uname" -> LibFunc
libFunc__uname
    "ungetc" -> LibFunc
libFunc__ungetc
    "unlink" -> LibFunc
libFunc__unlink
    "unsetenv" -> LibFunc
libFunc__unsetenv
    "utime" -> LibFunc
libFunc__utime
    "utimes" -> LibFunc
libFunc__utimes
    "valloc" -> LibFunc
libFunc__valloc
    "vfprintf" -> LibFunc
libFunc__vfprintf
    "vfscanf" -> LibFunc
libFunc__vfscanf
    "vprintf" -> LibFunc
libFunc__vprintf
    "vscanf" -> LibFunc
libFunc__vscanf
    "vsnprintf" -> LibFunc
libFunc__vsnprintf
    "vsprintf" -> LibFunc
libFunc__vsprintf
    "vsscanf" -> LibFunc
libFunc__vsscanf
    "write" -> LibFunc
libFunc__write
    x :: String
x -> String -> LibFunc
forall a. HasCallStack => String -> a
error (String -> LibFunc) -> String -> LibFunc
forall a b. (a -> b) -> a -> b
$ "bad quasiquoted FFI constant for libFunc__: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
x,
  quoteType :: String -> Q Type
quoteType = String -> Q Type
forall a. HasCallStack => a
undefined,
  quoteDec :: String -> Q [Dec]
quoteDec = String -> Q [Dec]
forall a. HasCallStack => a
undefined
 }

{-# LINE 340 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype JITSymbolFlags = JITSymbolFlags CUInt
  deriving (Eq, Read, Show, Bits, Typeable, Data, Num, Storable, Generic)

jitSymbolFlagsNone :: JITSymbolFlags
jitSymbolFlagsNone = JITSymbolFlags 0
jitSymbolFlagsHasError :: JITSymbolFlags
jitSymbolFlagsHasError = JITSymbolFlags 1
jitSymbolFlagsWeak :: JITSymbolFlags
jitSymbolFlagsWeak = JITSymbolFlags 2
jitSymbolFlagsCommon :: JITSymbolFlags
jitSymbolFlagsCommon = JITSymbolFlags 4
jitSymbolFlagsAbsolute :: JITSymbolFlags
jitSymbolFlagsAbsolute = JITSymbolFlags 8
jitSymbolFlagsExported :: JITSymbolFlags
jitSymbolFlagsExported = JITSymbolFlags 16
jitSymbolFlagsP :: QuasiQuoter
jitSymbolFlagsP = QuasiQuoter {
  quoteExp = undefined,
  quotePat = \s -> dataToPatQ (const Nothing) $ case s of
    "None" -> jitSymbolFlagsNone
    "HasError" -> jitSymbolFlagsHasError
    "Weak" -> jitSymbolFlagsWeak
    "Common" -> jitSymbolFlagsCommon
    "Absolute" -> jitSymbolFlagsAbsolute
    "Exported" -> jitSymbolFlagsExported
    x -> error $ "bad quasiquoted FFI constant for jitSymbolFlags: " ++ x,
  quoteType = undefined,
  quoteDec = undefined
 }

{-# LINE 345 "src/LLVM/Internal/FFI/LLVMCTypes.hsc" #-}

newtype ChecksumKind = ChecksumKind CUInt
  deriving (Data, Show)

newtype Macinfo = Macinfo CUInt
  deriving (Data, Show)

pattern DW_Macinfo_Define :: Macinfo
pattern DW_Macinfo_Define = Macinfo 0x01
pattern DW_Macinfo_Undef :: Macinfo
pattern DW_Macinfo_Undef = Macinfo 0x02

newtype DebugEmissionKind = DebugEmissionKind CUInt
  deriving (Data, Show)

pattern NoDebug :: DebugEmissionKind
pattern NoDebug = DebugEmissionKind 0
pattern FullDebug :: DebugEmissionKind
pattern FullDebug = DebugEmissionKind 1
pattern LineTablesOnly :: DebugEmissionKind
pattern LineTablesOnly = DebugEmissionKind 2

newtype DebugNameTableKind = DebugNameTableKind CUInt
  deriving (Data, Show)

pattern NameTableKindDefault :: DebugNameTableKind
pattern NameTableKindDefault = DebugNameTableKind 0

pattern NameTableKindGNU :: DebugNameTableKind
pattern NameTableKindGNU = DebugNameTableKind 1

pattern NameTableKindNone :: DebugNameTableKind
pattern NameTableKindNone = DebugNameTableKind 2