{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.Provers.MathSAT(mathSAT) where
import Data.SBV.Core.Data
import Data.SBV.SMT.SMT
import Data.SBV.Control.Types
mathSAT :: SMTSolver
mathSAT = SMTSolver {
name = MathSAT
, executable = "mathsat"
, preprocess = id
, options = modConfig ["-input=smt2", "-theory.fp.minmax_zero_mode=4"]
, engine = standardEngine "SBV_MATHSAT" "SBV_MATHSAT_OPTIONS"
, capabilities = SolverCapabilities {
supportsQuantifiers = True
, supportsUninterpretedSorts = True
, supportsUnboundedInts = True
, supportsReals = True
, supportsApproxReals = False
, supportsIEEE754 = True
, supportsSets = False
, supportsOptimization = False
, supportsPseudoBooleans = False
, supportsCustomQueries = True
, supportsGlobalDecls = True
, supportsDataTypes = True
, supportsFlattenedModels = Nothing
}
}
where
modConfig :: [String] -> SMTConfig -> [String]
modConfig opts cfg
| or [b | ProduceUnsatCores b <- solverSetOptions cfg]
= opts ++ ["-unsat_core_generation=3"]
| True
= opts