{-# 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 DwOp_LLVM_fragment =   4096
pattern DwOp_stack_value :: Word64
pattern DwOp_stack_value =   159
pattern DwOp_swap :: Word64
pattern DwOp_swap =   22
pattern DwOp_constu :: Word64
pattern DwOp_constu =   16
pattern DwOp_lit0 :: Word64
pattern DwOp_lit0 =   48
pattern DwOp_plus_uconst :: Word64
pattern DwOp_plus_uconst =   35
pattern DwOp_plus :: Word64
pattern DwOp_plus =   34
pattern DwOp_minus :: Word64
pattern DwOp_minus =   28
pattern DwOp_mul :: Word64
pattern DwOp_mul =   30
pattern DwOp_div :: Word64
pattern DwOp_div =   27
pattern DwOp_mod :: Word64
pattern DwOp_mod =   29
pattern DwOp_not :: Word64
pattern DwOp_not =   32
pattern DwOp_or :: Word64
pattern DwOp_or =   33
pattern DwOp_xor :: Word64
pattern DwOp_xor =   39
pattern DwOp_and :: Word64
pattern DwOp_and =   26
pattern DwOp_shr :: Word64
pattern DwOp_shr =   37
pattern DwOp_shra :: Word64
pattern DwOp_shra =   38
pattern DwOp_shl :: Word64
pattern 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 DwAtE_signed_char =  Encoding 6
pattern DwAtE_unsigned :: Encoding
pattern DwAtE_unsigned =  Encoding 7
pattern DwAtE_unsigned_char :: Encoding
pattern DwAtE_unsigned_char =  Encoding 8
pattern DwAtE_imaginary_float :: Encoding
pattern DwAtE_imaginary_float =  Encoding 9
pattern DwAtE_packed_decimal :: Encoding
pattern DwAtE_packed_decimal =  Encoding 10
pattern DwAtE_numeric_string :: Encoding
pattern DwAtE_numeric_string =  Encoding 11
pattern DwAtE_edited :: Encoding
pattern DwAtE_edited =  Encoding 12
pattern DwAtE_signed_fixed :: Encoding
pattern DwAtE_signed_fixed =  Encoding 13
pattern DwAtE_unsigned_fixed :: Encoding
pattern DwAtE_unsigned_fixed =  Encoding 14
pattern DwAtE_decimal_float :: Encoding
pattern DwAtE_decimal_float =  Encoding 15
pattern DwAtE_UTF :: Encoding
pattern DwAtE_UTF =  Encoding 16
pattern DwAtE_UCS :: Encoding
pattern 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 3
fCmpPredOLT  :: FCmpPredicate
fCmpPredOLT  = FCmpPredicate 4
fCmpPredOLE  :: FCmpPredicate
fCmpPredOLE  = FCmpPredicate 5
fCmpPredONE  :: FCmpPredicate
fCmpPredONE  = FCmpPredicate 6
fCmpPredORD  :: FCmpPredicate
fCmpPredORD  = FCmpPredicate 7
fCmpPredUNO  :: FCmpPredicate
fCmpPredUNO  = FCmpPredicate 8
fCmpPredUEQ  :: FCmpPredicate
fCmpPredUEQ  = FCmpPredicate 9
fCmpPredUGT  :: FCmpPredicate
fCmpPredUGT  = FCmpPredicate 10
fCmpPredUGE  :: FCmpPredicate
fCmpPredUGE  = FCmpPredicate 11
fCmpPredULT  :: FCmpPredicate
fCmpPredULT  = FCmpPredicate 12
fCmpPredULE  :: FCmpPredicate
fCmpPredULE  = FCmpPredicate 13
fCmpPredUNE  :: FCmpPredicate
fCmpPredUNE  = FCmpPredicate 14
fcmpPredTrue  :: FCmpPredicate
fcmpPredTrue  = 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 4
mdSubclassIdDILocation :: MDSubclassID
mdSubclassIdDILocation = MDSubclassID 5
mdSubclassIdDIExpression :: MDSubclassID
mdSubclassIdDIExpression = MDSubclassID 6
mdSubclassIdDIGlobalVariableExpression :: MDSubclassID
mdSubclassIdDIGlobalVariableExpression = MDSubclassID 7
mdSubclassIdGenericDINode :: MDSubclassID
mdSubclassIdGenericDINode = MDSubclassID 8
mdSubclassIdDISubrange :: MDSubclassID
mdSubclassIdDISubrange = MDSubclassID 9
mdSubclassIdDIEnumerator :: MDSubclassID
mdSubclassIdDIEnumerator = MDSubclassID 10
mdSubclassIdDIBasicType :: MDSubclassID
mdSubclassIdDIBasicType = MDSubclassID 11
mdSubclassIdDIDerivedType :: MDSubclassID
mdSubclassIdDIDerivedType = MDSubclassID 12
mdSubclassIdDICompositeType :: MDSubclassID
mdSubclassIdDICompositeType = MDSubclassID 13
mdSubclassIdDISubroutineType :: MDSubclassID
mdSubclassIdDISubroutineType = MDSubclassID 14
mdSubclassIdDIFile :: MDSubclassID
mdSubclassIdDIFile = MDSubclassID 15
mdSubclassIdDICompileUnit :: MDSubclassID
mdSubclassIdDICompileUnit = MDSubclassID 16
mdSubclassIdDISubprogram :: MDSubclassID
mdSubclassIdDISubprogram = MDSubclassID 17
mdSubclassIdDILexicalBlock :: MDSubclassID
mdSubclassIdDILexicalBlock = MDSubclassID 18
mdSubclassIdDILexicalBlockFile :: MDSubclassID
mdSubclassIdDILexicalBlockFile = MDSubclassID 19
mdSubclassIdDINamespace :: MDSubclassID
mdSubclassIdDINamespace = MDSubclassID 20
mdSubclassIdDIModule :: MDSubclassID
mdSubclassIdDIModule = MDSubclassID 21
mdSubclassIdDITemplateTypeParameter :: MDSubclassID
mdSubclassIdDITemplateTypeParameter = MDSubclassID 22
mdSubclassIdDITemplateValueParameter :: MDSubclassID
mdSubclassIdDITemplateValueParameter = MDSubclassID 23
mdSubclassIdDIGlobalVariable :: MDSubclassID
mdSubclassIdDIGlobalVariable = 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 88
callingConventionAMDGPU_PS :: CallingConvention
callingConventionAMDGPU_PS = CallingConvention 89
callingConventionAMDGPU_CS :: CallingConvention
callingConventionAMDGPU_CS = CallingConvention 90
callingConventionAMDGPU_KERNEL :: CallingConvention
callingConventionAMDGPU_KERNEL = CallingConvention 91
callingConventionX86_RegCall :: CallingConvention
callingConventionX86_RegCall = CallingConvention 92
callingConventionAMDGPU_HS :: CallingConvention
callingConventionAMDGPU_HS = CallingConvention 93
callingConventionMSP430_BUILTIN :: CallingConvention
callingConventionMSP430_BUILTIN = 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)

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