sbv: SMT Based Verification: Symbolic Haskell theorem prover using SMT solving.

[ bit-vectors, bsd3, formal-methods, library, math, smt, symbolic-computation, theorem-provers ] [ Propose Tags ]

Express properties about Haskell programs and automatically prove them using SMT (Satisfiability Modulo Theories) solvers.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.9, 0.9.1, 0.9.2, 0.9.3, 0.9.4, 0.9.5, 0.9.6, 0.9.7, 0.9.8, 0.9.9, 0.9.10, 0.9.11, 0.9.12, 0.9.13, 0.9.14, 0.9.15, 0.9.16, 0.9.17, 0.9.18, 0.9.19, 0.9.20, 0.9.21, 0.9.22, 0.9.23, 0.9.24, 1.0, 1.1, 1.2, 1.3, 1.4, 2.0, 2.1, 2.2, 2.3, 2.4, 2.5, 2.6, 2.7, 2.8, 2.9, 2.10, 3.0, 3.1, 3.2, 3.3, 3.4, 3.5, 4.0, 4.1, 4.2, 4.3, 4.4, 5.0, 5.1, 5.2, 5.3, 5.4, 5.5, 5.6, 5.7, 5.8, 5.9, 5.10, 5.11, 5.12, 5.13, 5.14, 5.15, 6.0, 6.1, 7.0, 7.1, 7.2, 7.3, 7.4, 7.5, 7.6, 7.7, 7.8, 7.9, 7.10, 7.11, 7.12, 7.13, 8.0, 8.1, 8.2, 8.3, 8.4, 8.5, 8.6, 8.7, 8.8, 8.9, 8.10, 8.11, 8.12, 8.13, 8.14, 8.15, 8.16, 8.17, 9.0, 9.1, 9.2, 10.0, 10.1, 10.2, 10.3, 10.4, 10.5, 10.6 (info)
Change log CHANGES.md
Dependencies array, async, base (>=4.16 && <5), containers, deepseq, directory, filepath, libBF (>=0.6.7), mtl, pretty, process, QuickCheck, random, syb, template-haskell, text, time, transformers, uniplate [details]
License BSD-3-Clause
Copyright Levent Erkok, 2010-2024
Author Levent Erkok
Maintainer Levent Erkok (erkokl@gmail.com)
Category Formal Methods, Theorem Provers, Bit vectors, Symbolic Computation, Math, SMT
Home page http://github.com/LeventErkok/sbv
Bug tracker http://github.com/LeventErkok/sbv/issues
Source repo head: git clone git://github.com/LeventErkok/sbv.git
Uploaded by LeventErkok at 2024-03-16T17:48:30Z
Distributions Arch:9.1, Debian:8.7, LTSHaskell:10.2, Stackage:10.5
Reverse Dependencies 12 direct, 11 indirect [details]
Downloads 74960 total (377 in the last 30 days)
Rating 2.75 (votes: 9) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for sbv-10.6

[back to package description]

SBV: SMT Based Verification in Haskell

Build Status

On Hackage: http://hackage.haskell.org/package/sbv

Express properties about Haskell programs and automatically prove them using SMT solvers.

$ ghci
ghci> :m Data.SBV
ghci> prove $ \x -> x `shiftL` 2 .== 4 * (x::SWord8)
Q.E.D.
ghci> prove $ \x -> x `shiftL` 2 .== 2 * (x::SWord8)
Falsifiable. Counter-example:
  s0 = 32 :: Word8

The function prove establishes theorem-hood, while sat finds a satisfying model if it exists. All satisfying models can be computed using allSat. SBV can also perform static assertion checks, such as absence of division-by-0, and other user given properties. Furthermore, SBV can perform optimization, minimizing/maximizing arithmetic goals for their optimal values.

SBV also allows for an incremental mode: Users are given a handle to the SMT solver as their programs execute, and they can issue SMTLib commands programmatically, query values, and direct the interaction using a high-level typed API. The incremental mode also allows for creation of constraints based on the current model, and access to internals of SMT solvers for advanced users. See the runSMT and query commands for details.

Overview

SBV library provides support for dealing with symbolic values in Haskell. It introduces the types:

  • SBool: Symbolic Booleans (bits).
  • SWord8, SWord16, SWord32, SWord64: Symbolic Words (unsigned).
  • SInt8, SInt16, SInt32, SInt64: Symbolic Ints (signed).
  • SWord N, SInt N, for N > 0: Arbitrary sized unsigned/signed bit-vectors, parameterized by the bitsize. (Using DataKinds extension.)
  • SInteger: Symbolic unbounded integers (signed).
  • SReal: Symbolic infinite precision algebraic reals (signed).
  • SRational: Symbolic rationals, ratio of two symbolic integers. (Rational.)
  • SFloat: IEEE-754 single precision floating point number. (Float.)
  • SDouble: IEEE-754 double precision floating point number. (Double.)
  • SFloatingPoint: IEEE-754 floating point number with user specified exponent and significand sizes. (FloatingPoint)
  • SChar: Symbolic characters, supporting unicode.
  • SString: Symbolic strings.
  • SList: Symbolic lists. (Which can be nested, i.e., lists of lists.)
  • STuple: Symbolic tuples (upto 8-tuples, can be nested)
  • SEither: Symbolic sums
  • SMaybe: Symbolic optional values
  • SSet: Symbolic sets
  • Arrays of symbolic values.
  • Symbolic enumerations, for arbitrary user-defined enumerated types.
  • Symbolic polynomials over GF(2^n ), polynomial arithmetic, and CRCs.
  • Uninterpreted constants and functions over symbolic values, with user defined axioms.
  • Uninterpreted sorts, and proofs over such sorts, potentially with axioms.
  • Ability to define SMTLib functions, generated directly from Haskell versions, including support for recursive and mutually recursive functions.
  • Reasoning with universal and existential quantifiers, including alternating quantifiers.

The user can construct ordinary Haskell programs using these types, which behave like ordinary Haskell values when used concretely. However, when used with symbolic arguments, functions built out of these types can also be:

  • proven correct via an external SMT solver (the prove function),
  • checked for satisfiability (the sat, and allSat functions),
  • checked for assertion violations (the safe function with sAssert calls),
  • checked for delta-satisfiability (the dsat and dprove functions),
  • used in synthesis (the satfunction with existentials),
  • checked for machine-arithmetic overflow/underflow conditions,
  • optimized with respect to cost functions (the optimize, maximize, and minimize functions),
  • quick-checked,
  • used for generating Haskell and C test vectors (the genTest function),
  • compiled down to C, rendered as straight-line programs or libraries (compileToC and compileToCLib functions).

Picking the SMT solver to use

The SBV library uses third-party SMT solvers via the standard SMT-Lib interface. The following solvers are supported:

  • ABC from University of Berkeley
  • Boolector from Johannes Kepler University
  • Bitwuzla from Stanford University
  • CVC4 and CVC5 from Stanford University and the University of Iowa
  • DReal from CMU
  • MathSAT from FBK and DISI-University of Trento
  • OpenSMT from Università della Svizzera italiana
  • Yices from SRI
  • Z3 from Microsoft

Most functions have two variants: For instance prove/proveWith. The former uses the default solver, which is currently Z3. The latter expects you to pass it a configuration that picks the solver. The valid values are abc, boolector, bitwuzla, cvc4, cvc5, dReal, mathSAT, openSMT, yices, and z3.

See versions for a listing of the versions of these tools SBV has been tested with. Please report if you see any discrepancies!

Other SMT solvers can be used with SBV as well, with a relatively easy hook-up mechanism. Please do get in touch if you plan to use SBV with any other solver.

Using multiple solvers, simultaneously

SBV also allows for running multiple solvers at the same time, either picking the result of the first to complete, or getting results from all. See proveWithAny/proveWithAll and satWithAny/satWithAll functions. The function sbvAvailableSolvers can be used to query the available solvers at run-time.

The SBV library is distributed with the BSD3 license. See COPYRIGHT for details. The LICENSE file contains the BSD3 verbiage.

Thanks

The following people made major contributions to SBV, by developing new features and contributing to the design in significant ways: Joel Burget, Brian Huffman, Brian Schroeder, and Jeffrey Young.

The following people reported bugs, provided comments/feedback, or contributed to the development of SBV in various ways: Ara Adkins, Kanishka Azimi, Markus Barenhoff, Reid Barton, Ben Blaxill, Ian Blumenfeld, Guillaume Bouchard, Martin Brain, Ian Calvert, Oliver Charles, Christian Conkle, Matthew Danish, Iavor Diatchki, Alex Dixon, Robert Dockins, Thomas DuBuisson, Trevor Elliott, Gergő Érdi, John Erickson, Richard Fergie, Adam Foltzer, Joshua Gancher, Remy Goldschmidt, Brad Hardy, Tom Hawkins, Greg Horn, Jan Hrcek, Georges-Axel Jaloyan, Anders Kaseorg, Tom Sydney Kerckhove, Lars Kuhtz, Piërre van de Laar, Pablo Lamela, Ken Friis Larsen, Andrew Lelechenko, Joe Leslie-Hurd, Nick Lewchenko, Brett Letner, Sirui Lu, Georgy Lukyanov, Martin Lundfall, John Matthews, Curran McConnell, Philipp Meyer, Joshua Moerman, Matt Parker, Jan Path, Matt Peddie, Lucas Peña, Matthew Pickering, Lee Pike, Gleb Popov, Rohit Ramesh, Geoffrey Ramseyer, Jaro Reinders, Stephan Renatus, Dan Rosén, Ryan Scott, Eric Seidel, Austin Seipp, Andrés Sicard-Ramírez, Don Stewart, Greg Sullivan, Josef Svenningsson, George Thomas, May Torrence, Daniel Wagner, Sean Weaver, Nis Wegmann, and Jared Ziegler.

Thanks!