{-# LANGUAGE ScopedTypeVariables #-}
module Data.SBV.Provers.MathSAT(mathSAT) where
import Data.SBV.Core.Data
import Data.SBV.SMT.SMT
mathSAT :: SMTSolver
mathSAT = SMTSolver {
name = MathSAT
, executable = "mathsat"
, options = ["-input=smt2", "-theory.fp.minmax_zero_mode=4"]
, engine = standardEngine "SBV_MATHSAT" "SBV_MATHSAT_OPTIONS" modConfig addTimeOut standardModel
, capabilities = SolverCapabilities {
capSolverName = "MathSAT"
, mbDefaultLogic = const Nothing
, supportsDefineFun = True
, supportsProduceModels = True
, supportsQuantifiers = True
, supportsUninterpretedSorts = True
, supportsUnboundedInts = True
, supportsReals = True
, supportsFloats = True
, supportsDoubles = True
, supportsOptimization = False
, supportsPseudoBooleans = False
, supportsUnsatCores = True
}
}
where addTimeOut _ _ = error "MathSAT: Timeout values are not supported"
modConfig :: SMTConfig -> SMTConfig
modConfig cfg
| not (getUnsatCore cfg) = cfg
| True = cfg {solver = (solver cfg) {options = newOpts}}
where newOpts = options (solver cfg) ++ ["-unsat_core_generation=3"]