{-# LINE 1 "src/Clingo/Raw/Enums.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "src/Clingo/Raw/Enums.hsc" #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -Wno-missing-pattern-synonym-signatures #-}
module Clingo.Raw.Enums
(
    ClingoError,
    pattern ErrorSuccess,
    pattern ErrorRuntime,
    pattern ErrorLogic,
    pattern ErrorBadAlloc,
    pattern ErrorUnknown,

    ClingoWarning,
    pattern WarnOpUndefined,
    pattern WarnRTError,
    pattern WarnAtomUndefined,
    pattern WarnFileIncluded,
    pattern WarnVariableUnbounded,
    pattern WarnGlobalVariable,
    pattern WarnOther,

    TruthValue,
    pattern TruthFree,
    pattern TruthFalse,
    pattern TruthTrue,

    SymbolType,
    pattern SymInfimum,
    pattern SymNumber,
    pattern SymString,
    pattern SymFunction,
    pattern SymSupremum,

    ModelType,
    pattern StableModel,
    pattern BraveConsequences,
    pattern CautiousConsequences,

    ShowFlag,
    pattern ShowCSP,
    pattern ShowShown,
    pattern ShowAtoms,
    pattern ShowTerms,
    pattern ShowExtra,
    pattern ShowAll,
    pattern ShowComplement,

    SolveResult,
    pattern ResultSatisfiable,
    pattern ResultUnsatisfiable,
    pattern ResultExhausted,
    pattern ResultInterrupted,

    SolveMode,
    pattern SolveModeAsync,
    pattern SolveModeYield,

    SolveEvent,
    pattern SolveEventModel,
    pattern SolveEventFinish,

    TheoryTermType,
    pattern TheoryTuple,
    pattern TheoryList,
    pattern TheorySet,
    pattern TheoryFunction,
    pattern TheoryNumber,
    pattern TheorySymbol,

    ClauseType,
    pattern ClauseLearnt,
    pattern ClauseStatic,
    pattern ClauseVolatile,
    pattern ClauseVolatileStatic,

    HeuristicType,
    pattern HeuristicLevel,
    pattern HeuristicSign,
    pattern HeuristicFactor,
    pattern HeuristicInit,
    pattern HeuristicTrue,
    pattern HeuristicFalse,

    ExternalType,
    pattern ExternalFree,
    pattern ExternalTrue,
    pattern ExternalFalse,
    pattern ExternalRelease,

    ConfigurationType,
    pattern ConfigValue,
    pattern ConfigArray,
    pattern ConfigMap,

    StatisticsType,
    pattern StatsEmpty,
    pattern StatsValue,
    pattern StatsArray,
    pattern StatsMap
)
where

import Data.Int
import Data.Word


{-# LINE 109 "src/Clingo/Raw/Enums.hsc" #-}

type ClingoError = (Int32)
{-# LINE 111 "src/Clingo/Raw/Enums.hsc" #-}

pattern ErrorSuccess = 0
{-# LINE 113 "src/Clingo/Raw/Enums.hsc" #-}
pattern ErrorRuntime = 1
{-# LINE 114 "src/Clingo/Raw/Enums.hsc" #-}
pattern ErrorLogic = 2
{-# LINE 115 "src/Clingo/Raw/Enums.hsc" #-}
pattern ErrorBadAlloc = 3
{-# LINE 116 "src/Clingo/Raw/Enums.hsc" #-}
pattern ErrorUnknown = 4
{-# LINE 117 "src/Clingo/Raw/Enums.hsc" #-}

type ClingoWarning = (Int32)
{-# LINE 119 "src/Clingo/Raw/Enums.hsc" #-}

pattern WarnOpUndefined = 0
{-# LINE 121 "src/Clingo/Raw/Enums.hsc" #-}
pattern WarnRTError = 1
{-# LINE 122 "src/Clingo/Raw/Enums.hsc" #-}
pattern WarnAtomUndefined = 2
{-# LINE 123 "src/Clingo/Raw/Enums.hsc" #-}
pattern WarnFileIncluded = 3
{-# LINE 124 "src/Clingo/Raw/Enums.hsc" #-}
pattern WarnVariableUnbounded = 4
{-# LINE 125 "src/Clingo/Raw/Enums.hsc" #-}
pattern WarnGlobalVariable = 5
{-# LINE 126 "src/Clingo/Raw/Enums.hsc" #-}
pattern WarnOther = 6
{-# LINE 127 "src/Clingo/Raw/Enums.hsc" #-}

type TruthValue = (Int32)
{-# LINE 129 "src/Clingo/Raw/Enums.hsc" #-}

pattern TruthFree = 0
{-# LINE 131 "src/Clingo/Raw/Enums.hsc" #-}
pattern TruthFalse = 2
{-# LINE 132 "src/Clingo/Raw/Enums.hsc" #-}
pattern TruthTrue = 1
{-# LINE 133 "src/Clingo/Raw/Enums.hsc" #-}

type SymbolType = (Int32)
{-# LINE 135 "src/Clingo/Raw/Enums.hsc" #-}

pattern SymInfimum = 0
{-# LINE 137 "src/Clingo/Raw/Enums.hsc" #-}
pattern SymNumber = 1
{-# LINE 138 "src/Clingo/Raw/Enums.hsc" #-}
pattern SymString = 4
{-# LINE 139 "src/Clingo/Raw/Enums.hsc" #-}
pattern SymFunction = 5
{-# LINE 140 "src/Clingo/Raw/Enums.hsc" #-}
pattern SymSupremum = 7
{-# LINE 141 "src/Clingo/Raw/Enums.hsc" #-}

type ModelType = (Int32)
{-# LINE 143 "src/Clingo/Raw/Enums.hsc" #-}

pattern StableModel = 0
{-# LINE 145 "src/Clingo/Raw/Enums.hsc" #-}
pattern BraveConsequences = 1
{-# LINE 146 "src/Clingo/Raw/Enums.hsc" #-}
pattern CautiousConsequences = 2
{-# LINE 147 "src/Clingo/Raw/Enums.hsc" #-}

type ShowFlag = (Word32)
{-# LINE 149 "src/Clingo/Raw/Enums.hsc" #-}

pattern ShowCSP = 1
{-# LINE 151 "src/Clingo/Raw/Enums.hsc" #-}
pattern ShowShown = 2
{-# LINE 152 "src/Clingo/Raw/Enums.hsc" #-}
pattern ShowAtoms = 4
{-# LINE 153 "src/Clingo/Raw/Enums.hsc" #-}
pattern ShowTerms = 8
{-# LINE 154 "src/Clingo/Raw/Enums.hsc" #-}
pattern ShowExtra = 16
{-# LINE 155 "src/Clingo/Raw/Enums.hsc" #-}
pattern ShowAll = 31
{-# LINE 156 "src/Clingo/Raw/Enums.hsc" #-}
pattern ShowComplement = 32
{-# LINE 157 "src/Clingo/Raw/Enums.hsc" #-}

type SolveResult = (Word32)
{-# LINE 159 "src/Clingo/Raw/Enums.hsc" #-}

pattern ResultSatisfiable = 1
{-# LINE 161 "src/Clingo/Raw/Enums.hsc" #-}
pattern ResultUnsatisfiable = 2
{-# LINE 162 "src/Clingo/Raw/Enums.hsc" #-}
pattern ResultExhausted = 4
{-# LINE 163 "src/Clingo/Raw/Enums.hsc" #-}
pattern ResultInterrupted = 8
{-# LINE 164 "src/Clingo/Raw/Enums.hsc" #-}

type SolveMode = (Word32)
{-# LINE 166 "src/Clingo/Raw/Enums.hsc" #-}

pattern SolveModeAsync = 1
{-# LINE 168 "src/Clingo/Raw/Enums.hsc" #-}
pattern SolveModeYield = 2
{-# LINE 169 "src/Clingo/Raw/Enums.hsc" #-}

type SolveEvent = (Word32)
{-# LINE 171 "src/Clingo/Raw/Enums.hsc" #-}
pattern SolveEventModel = 0
{-# LINE 172 "src/Clingo/Raw/Enums.hsc" #-}
pattern SolveEventFinish = 1
{-# LINE 173 "src/Clingo/Raw/Enums.hsc" #-}

type TheoryTermType = (Int32)
{-# LINE 175 "src/Clingo/Raw/Enums.hsc" #-}

pattern TheoryTuple = 0
{-# LINE 177 "src/Clingo/Raw/Enums.hsc" #-}
pattern TheoryList = 1
{-# LINE 178 "src/Clingo/Raw/Enums.hsc" #-}
pattern TheorySet = 2
{-# LINE 179 "src/Clingo/Raw/Enums.hsc" #-}
pattern TheoryFunction = 3
{-# LINE 180 "src/Clingo/Raw/Enums.hsc" #-}
pattern TheoryNumber = 4
{-# LINE 181 "src/Clingo/Raw/Enums.hsc" #-}
pattern TheorySymbol = 5
{-# LINE 182 "src/Clingo/Raw/Enums.hsc" #-}

type ClauseType = (Int32)
{-# LINE 184 "src/Clingo/Raw/Enums.hsc" #-}

pattern ClauseLearnt = 0
{-# LINE 186 "src/Clingo/Raw/Enums.hsc" #-}
pattern ClauseStatic = 1
{-# LINE 187 "src/Clingo/Raw/Enums.hsc" #-}
pattern ClauseVolatile = 2
{-# LINE 188 "src/Clingo/Raw/Enums.hsc" #-}
pattern ClauseVolatileStatic = 3
{-# LINE 189 "src/Clingo/Raw/Enums.hsc" #-}

type HeuristicType = (Int32)
{-# LINE 191 "src/Clingo/Raw/Enums.hsc" #-}

pattern HeuristicLevel = 0
{-# LINE 193 "src/Clingo/Raw/Enums.hsc" #-}
pattern HeuristicSign = 1
{-# LINE 194 "src/Clingo/Raw/Enums.hsc" #-}
pattern HeuristicFactor = 2
{-# LINE 195 "src/Clingo/Raw/Enums.hsc" #-}
pattern HeuristicInit = 3
{-# LINE 196 "src/Clingo/Raw/Enums.hsc" #-}
pattern HeuristicTrue = 4
{-# LINE 197 "src/Clingo/Raw/Enums.hsc" #-}
pattern HeuristicFalse = 5
{-# LINE 198 "src/Clingo/Raw/Enums.hsc" #-}

type ExternalType = (Int32)
{-# LINE 200 "src/Clingo/Raw/Enums.hsc" #-}

pattern ExternalFree = 0
{-# LINE 202 "src/Clingo/Raw/Enums.hsc" #-}
pattern ExternalTrue = 1
{-# LINE 203 "src/Clingo/Raw/Enums.hsc" #-}
pattern ExternalFalse = 2
{-# LINE 204 "src/Clingo/Raw/Enums.hsc" #-}
pattern ExternalRelease = 3
{-# LINE 205 "src/Clingo/Raw/Enums.hsc" #-}

type ConfigurationType = (Word32)
{-# LINE 207 "src/Clingo/Raw/Enums.hsc" #-}

pattern ConfigValue = 1
{-# LINE 209 "src/Clingo/Raw/Enums.hsc" #-}
pattern ConfigArray = 2
{-# LINE 210 "src/Clingo/Raw/Enums.hsc" #-}
pattern ConfigMap = 4
{-# LINE 211 "src/Clingo/Raw/Enums.hsc" #-}

type StatisticsType = (Int32)
{-# LINE 213 "src/Clingo/Raw/Enums.hsc" #-}

pattern StatsEmpty = 0
{-# LINE 215 "src/Clingo/Raw/Enums.hsc" #-}
pattern StatsValue = 1
{-# LINE 216 "src/Clingo/Raw/Enums.hsc" #-}
pattern StatsArray = 2
{-# LINE 217 "src/Clingo/Raw/Enums.hsc" #-}
pattern StatsMap = 3
{-# LINE 218 "src/Clingo/Raw/Enums.hsc" #-}