{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.Control.Types (
CheckSatResult(..)
, Logic(..)
, SMTOption(..), isStartModeOption, isOnlyOnceOption
, SMTInfoFlag(..)
, SMTErrorBehavior(..)
, SMTReasonUnknown(..)
, SMTInfoResponse(..)
) where
import Control.DeepSeq (NFData(..))
import GHC.Generics (Generic)
data CheckSatResult = Sat
| DSat (Maybe String)
| Unsat
| Unk
deriving (CheckSatResult -> CheckSatResult -> Bool
(CheckSatResult -> CheckSatResult -> Bool)
-> (CheckSatResult -> CheckSatResult -> Bool) -> Eq CheckSatResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheckSatResult -> CheckSatResult -> Bool
== :: CheckSatResult -> CheckSatResult -> Bool
$c/= :: CheckSatResult -> CheckSatResult -> Bool
/= :: CheckSatResult -> CheckSatResult -> Bool
Eq, Int -> CheckSatResult -> ShowS
[CheckSatResult] -> ShowS
CheckSatResult -> String
(Int -> CheckSatResult -> ShowS)
-> (CheckSatResult -> String)
-> ([CheckSatResult] -> ShowS)
-> Show CheckSatResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CheckSatResult -> ShowS
showsPrec :: Int -> CheckSatResult -> ShowS
$cshow :: CheckSatResult -> String
show :: CheckSatResult -> String
$cshowList :: [CheckSatResult] -> ShowS
showList :: [CheckSatResult] -> ShowS
Show, CheckSatResult -> ()
(CheckSatResult -> ()) -> NFData CheckSatResult
forall a. (a -> ()) -> NFData a
$crnf :: CheckSatResult -> ()
rnf :: CheckSatResult -> ()
NFData, (forall x. CheckSatResult -> Rep CheckSatResult x)
-> (forall x. Rep CheckSatResult x -> CheckSatResult)
-> Generic CheckSatResult
forall x. Rep CheckSatResult x -> CheckSatResult
forall x. CheckSatResult -> Rep CheckSatResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CheckSatResult -> Rep CheckSatResult x
from :: forall x. CheckSatResult -> Rep CheckSatResult x
$cto :: forall x. Rep CheckSatResult x -> CheckSatResult
to :: forall x. Rep CheckSatResult x -> CheckSatResult
Generic)
data SMTInfoFlag = AllStatistics
| AssertionStackLevels
| Authors
| ErrorBehavior
| Name
| ReasonUnknown
| Version
| InfoKeyword String
data SMTErrorBehavior = ErrorImmediateExit
| ErrorContinuedExecution
deriving Int -> SMTErrorBehavior -> ShowS
[SMTErrorBehavior] -> ShowS
SMTErrorBehavior -> String
(Int -> SMTErrorBehavior -> ShowS)
-> (SMTErrorBehavior -> String)
-> ([SMTErrorBehavior] -> ShowS)
-> Show SMTErrorBehavior
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SMTErrorBehavior -> ShowS
showsPrec :: Int -> SMTErrorBehavior -> ShowS
$cshow :: SMTErrorBehavior -> String
show :: SMTErrorBehavior -> String
$cshowList :: [SMTErrorBehavior] -> ShowS
showList :: [SMTErrorBehavior] -> ShowS
Show
data SMTReasonUnknown = UnknownMemOut
| UnknownIncomplete
| UnknownTimeOut
| UnknownOther String
instance NFData SMTReasonUnknown where rnf :: SMTReasonUnknown -> ()
rnf SMTReasonUnknown
a = SMTReasonUnknown -> () -> ()
forall a b. a -> b -> b
seq SMTReasonUnknown
a ()
instance Show SMTReasonUnknown where
show :: SMTReasonUnknown -> String
show SMTReasonUnknown
UnknownMemOut = String
"memout"
show SMTReasonUnknown
UnknownIncomplete = String
"incomplete"
show SMTReasonUnknown
UnknownTimeOut = String
"timeout"
show (UnknownOther String
s) = String
s
data SMTInfoResponse = Resp_Unsupported
| Resp_AllStatistics [(String, String)]
| Resp_AssertionStackLevels Integer
| Resp_Authors [String]
| Resp_Error SMTErrorBehavior
| Resp_Name String
| Resp_ReasonUnknown SMTReasonUnknown
| Resp_Version String
| Resp_InfoKeyword String [String]
deriving Int -> SMTInfoResponse -> ShowS
[SMTInfoResponse] -> ShowS
SMTInfoResponse -> String
(Int -> SMTInfoResponse -> ShowS)
-> (SMTInfoResponse -> String)
-> ([SMTInfoResponse] -> ShowS)
-> Show SMTInfoResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SMTInfoResponse -> ShowS
showsPrec :: Int -> SMTInfoResponse -> ShowS
$cshow :: SMTInfoResponse -> String
show :: SMTInfoResponse -> String
$cshowList :: [SMTInfoResponse] -> ShowS
showList :: [SMTInfoResponse] -> ShowS
Show
instance Show SMTInfoFlag where
show :: SMTInfoFlag -> String
show SMTInfoFlag
AllStatistics = String
":all-statistics"
show SMTInfoFlag
AssertionStackLevels = String
":assertion-stack-levels"
show SMTInfoFlag
Authors = String
":authors"
show SMTInfoFlag
ErrorBehavior = String
":error-behavior"
show SMTInfoFlag
Name = String
":name"
show SMTInfoFlag
ReasonUnknown = String
":reason-unknown"
show SMTInfoFlag
Version = String
":version"
show (InfoKeyword String
s) = String
s
data SMTOption = DiagnosticOutputChannel FilePath
| ProduceAssertions Bool
| ProduceAssignments Bool
| ProduceProofs Bool
| ProduceInterpolants Bool
| ProduceUnsatAssumptions Bool
| ProduceUnsatCores Bool
| ProduceAbducts Bool
| RandomSeed Integer
| ReproducibleResourceLimit Integer
| SMTVerbosity Integer
| OptionKeyword String [String]
| SetLogic Logic
| SetInfo String [String]
| SetTimeOut Integer
deriving Int -> SMTOption -> ShowS
[SMTOption] -> ShowS
SMTOption -> String
(Int -> SMTOption -> ShowS)
-> (SMTOption -> String)
-> ([SMTOption] -> ShowS)
-> Show SMTOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SMTOption -> ShowS
showsPrec :: Int -> SMTOption -> ShowS
$cshow :: SMTOption -> String
show :: SMTOption -> String
$cshowList :: [SMTOption] -> ShowS
showList :: [SMTOption] -> ShowS
Show
isStartModeOption :: SMTOption -> Bool
isStartModeOption :: SMTOption -> Bool
isStartModeOption DiagnosticOutputChannel{} = Bool
False
isStartModeOption ProduceAssertions{} = Bool
True
isStartModeOption ProduceAssignments{} = Bool
True
isStartModeOption ProduceProofs{} = Bool
True
isStartModeOption ProduceInterpolants{} = Bool
True
isStartModeOption ProduceUnsatAssumptions{} = Bool
True
isStartModeOption ProduceUnsatCores{} = Bool
True
isStartModeOption ProduceAbducts{} = Bool
True
isStartModeOption RandomSeed{} = Bool
True
isStartModeOption ReproducibleResourceLimit{} = Bool
False
isStartModeOption SMTVerbosity{} = Bool
False
isStartModeOption OptionKeyword{} = Bool
True
isStartModeOption SetLogic{} = Bool
True
isStartModeOption SetInfo{} = Bool
False
isStartModeOption SetTimeOut{} = Bool
True
isOnlyOnceOption :: SMTOption -> Bool
isOnlyOnceOption :: SMTOption -> Bool
isOnlyOnceOption DiagnosticOutputChannel{} = Bool
True
isOnlyOnceOption ProduceAssertions{} = Bool
True
isOnlyOnceOption ProduceAssignments{} = Bool
True
isOnlyOnceOption ProduceProofs{} = Bool
True
isOnlyOnceOption ProduceInterpolants{} = Bool
True
isOnlyOnceOption ProduceUnsatAssumptions{} = Bool
True
isOnlyOnceOption ProduceAbducts{} = Bool
False
isOnlyOnceOption ProduceUnsatCores{} = Bool
True
isOnlyOnceOption RandomSeed{} = Bool
False
isOnlyOnceOption ReproducibleResourceLimit{} = Bool
False
isOnlyOnceOption SMTVerbosity{} = Bool
False
isOnlyOnceOption OptionKeyword{} = Bool
False
isOnlyOnceOption SetLogic{} = Bool
True
isOnlyOnceOption SetInfo{} = Bool
False
isOnlyOnceOption SetTimeOut{} = Bool
False
data Logic
= AUFLIA
| AUFLIRA
| AUFNIRA
| LRA
| QF_ABV
| QF_AUFBV
| QF_AUFLIA
| QF_AX
| QF_BV
| QF_IDL
| QF_LIA
| QF_LRA
| QF_NIA
| QF_NRA
| QF_RDL
| QF_UF
| QF_UFBV
| QF_UFIDL
| QF_UFLIA
| QF_UFLRA
| QF_UFNRA
| QF_UFNIRA
| UFLRA
| UFNIA
| QF_FPBV
| QF_FP
| QF_FD
| QF_S
| Logic_ALL
| Logic_NONE
| CustomLogic String
instance Show Logic where
show :: Logic -> String
show Logic
AUFLIA = String
"AUFLIA"
show Logic
AUFLIRA = String
"AUFLIRA"
show Logic
AUFNIRA = String
"AUFNIRA"
show Logic
LRA = String
"LRA"
show Logic
QF_ABV = String
"QF_ABV"
show Logic
QF_AUFBV = String
"QF_AUFBV"
show Logic
QF_AUFLIA = String
"QF_AUFLIA"
show Logic
QF_AX = String
"QF_AX"
show Logic
QF_BV = String
"QF_BV"
show Logic
QF_IDL = String
"QF_IDL"
show Logic
QF_LIA = String
"QF_LIA"
show Logic
QF_LRA = String
"QF_LRA"
show Logic
QF_NIA = String
"QF_NIA"
show Logic
QF_NRA = String
"QF_NRA"
show Logic
QF_RDL = String
"QF_RDL"
show Logic
QF_UF = String
"QF_UF"
show Logic
QF_UFBV = String
"QF_UFBV"
show Logic
QF_UFIDL = String
"QF_UFIDL"
show Logic
QF_UFLIA = String
"QF_UFLIA"
show Logic
QF_UFLRA = String
"QF_UFLRA"
show Logic
QF_UFNRA = String
"QF_UFNRA"
show Logic
QF_UFNIRA = String
"QF_UFNIRA"
show Logic
UFLRA = String
"UFLRA"
show Logic
UFNIA = String
"UFNIA"
show Logic
QF_FPBV = String
"QF_FPBV"
show Logic
QF_FP = String
"QF_FP"
show Logic
QF_FD = String
"QF_FD"
show Logic
QF_S = String
"QF_S"
show Logic
Logic_ALL = String
"ALL"
show Logic
Logic_NONE = String
"Logic_NONE"
show (CustomLogic String
l) = String
l