{-# LANGUAGE ScopedTypeVariables #-}
module Data.SBV.Provers.CVC4(cvc4) where
import Data.SBV.Core.Data
import Data.SBV.SMT.SMT
cvc4 :: SMTSolver
cvc4 = SMTSolver {
name = CVC4
, executable = "cvc4"
, options = ["--lang", "smt"]
, engine = standardEngine "SBV_CVC4" "SBV_CVC4_OPTIONS" id addTimeOut standardModel
, capabilities = SolverCapabilities {
capSolverName = "CVC4"
, mbDefaultLogic = const (Just "ALL_SUPPORTED")
, supportsDefineFun = True
, supportsProduceModels = True
, supportsQuantifiers = True
, supportsUninterpretedSorts = True
, supportsUnboundedInts = True
, supportsReals = True
, supportsFloats = False
, supportsDoubles = False
, supportsOptimization = False
, supportsPseudoBooleans = False
, supportsUnsatCores = True
}
}
where addTimeOut o i | i < 0 = error $ "CVC4: Timeout value must be non-negative, received: " ++ show i
| True = o ++ ["--tlimit=" ++ show i ++ "000"]