{-# LANGUAGE ScopedTypeVariables #-}
module Data.SBV.Provers.Z3(z3) where
import Data.SBV.Core.Data
import Data.SBV.SMT.SMT
z3 :: SMTSolver
z3 = SMTSolver {
name = Z3
, executable = "z3"
, options = modConfig ["-nw", "-in", "-smt2"]
, engine = standardEngine "SBV_Z3" "SBV_Z3_OPTIONS"
, capabilities = SolverCapabilities {
supportsQuantifiers = True
, supportsUninterpretedSorts = True
, supportsUnboundedInts = True
, supportsReals = True
, supportsApproxReals = True
, supportsIEEE754 = True
, supportsOptimization = True
, supportsPseudoBooleans = True
, supportsCustomQueries = True
, supportsGlobalDecls = True
}
}
where modConfig :: [String] -> SMTConfig -> [String]
modConfig opts _cfg = opts