{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.Provers.CVC4(cvc4) where
import Data.Char (isSpace)
import Data.SBV.Core.Data
import Data.SBV.SMT.SMT
cvc4 :: SMTSolver
cvc4 = SMTSolver {
name = CVC4
, executable = "cvc4"
, preprocess = clean
, options = const ["--lang", "smt", "--incremental", "--interactive", "--no-interactive-prompt", "--model-witness-value"]
, engine = standardEngine "SBV_CVC4" "SBV_CVC4_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
clean = map simpleSpace . noComment
noComment "" = ""
noComment (';':cs) = noComment $ dropWhile (/= '\n') cs
noComment (c:cs) = c : noComment cs
simpleSpace c
| isSpace c = ' '
| True = c