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

Copyright(c) Brian Schroeder
Levent Erkok
LicenseBSD3
Maintainererkokl@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.SBV.Trans

Contents

Description

More generalized alternative to Data.SBV for advanced client use

Synopsis

Symbolic types

Booleans

type SBool = SBV Bool Source #

A symbolic boolean/bit

Boolean values and functions

sTrue :: SBool Source #

Symbolic True

sNot :: SBool -> SBool Source #

Symbolic boolean negation

(.&&) :: SBool -> SBool -> SBool infixr 3 Source #

Symbolic conjunction

(.||) :: SBool -> SBool -> SBool infixr 2 Source #

Symbolic disjunction

(.<+>) :: SBool -> SBool -> SBool infixl 6 Source #

Symbolic logical xor

(.~&) :: SBool -> SBool -> SBool infixr 3 Source #

Symbolic nand

(.~|) :: SBool -> SBool -> SBool infixr 2 Source #

Symbolic nor

(.=>) :: SBool -> SBool -> SBool infixr 1 Source #

Symbolic implication

(.<=>) :: SBool -> SBool -> SBool infixr 1 Source #

Symbolic boolean equivalence

fromBool :: Bool -> SBool Source #

Conversion from Bool to SBool

oneIf :: (Ord a, Num a, SymVal a) => SBool -> SBV a Source #

Returns 1 if the boolean is sTrue, otherwise 0.

Logical functions

sAnd :: [SBool] -> SBool Source #

Generalization of and

sOr :: [SBool] -> SBool Source #

Generalization of or

sAny :: (a -> SBool) -> [a] -> SBool Source #

Generalization of any

sAll :: (a -> SBool) -> [a] -> SBool Source #

Generalization of all

Bit-vectors

Unsigned bit-vectors

type SWord8 = SBV Word8 Source #

8-bit unsigned symbolic value

type SWord16 = SBV Word16 Source #

16-bit unsigned symbolic value

type SWord32 = SBV Word32 Source #

32-bit unsigned symbolic value

type SWord64 = SBV Word64 Source #

64-bit unsigned symbolic value

Signed bit-vectors

type SInt8 = SBV Int8 Source #

8-bit signed symbolic value, 2's complement representation

type SInt16 = SBV Int16 Source #

16-bit signed symbolic value, 2's complement representation

type SInt32 = SBV Int32 Source #

32-bit signed symbolic value, 2's complement representation

type SInt64 = SBV Int64 Source #

64-bit signed symbolic value, 2's complement representation

Unbounded integers

type SInteger = SBV Integer Source #

Infinite precision signed symbolic value

Floating point numbers

type SFloat = SBV Float Source #

IEEE-754 single-precision floating point numbers

type SDouble = SBV Double Source #

IEEE-754 double-precision floating point numbers

Algebraic reals

type SReal = SBV AlgReal Source #

Infinite precision symbolic algebraic real value

data AlgReal Source #

Algebraic reals. Note that the representation is left abstract. We represent rational results explicitly, while the roots-of-polynomials are represented implicitly by their defining equation

Instances
Eq AlgReal Source # 
Instance details

Defined in Data.SBV.Core.AlgReals

Methods

(==) :: AlgReal -> AlgReal -> Bool #

(/=) :: AlgReal -> AlgReal -> Bool #

Fractional AlgReal Source #

NB: Following the other types we have, we require `a/0` to be `0` for all a.

Instance details

Defined in Data.SBV.Core.AlgReals

Num AlgReal Source # 
Instance details

Defined in Data.SBV.Core.AlgReals

Ord AlgReal Source # 
Instance details

Defined in Data.SBV.Core.AlgReals

Real AlgReal Source # 
Instance details

Defined in Data.SBV.Core.AlgReals

Show AlgReal Source # 
Instance details

Defined in Data.SBV.Core.AlgReals

Arbitrary AlgReal Source # 
Instance details

Defined in Data.SBV.Core.AlgReals

Random AlgReal Source # 
Instance details

Defined in Data.SBV.Core.AlgReals

Methods

randomR :: RandomGen g => (AlgReal, AlgReal) -> g -> (AlgReal, g) #

random :: RandomGen g => g -> (AlgReal, g) #

randomRs :: RandomGen g => (AlgReal, AlgReal) -> g -> [AlgReal] #

randoms :: RandomGen g => g -> [AlgReal] #

randomRIO :: (AlgReal, AlgReal) -> IO AlgReal #

randomIO :: IO AlgReal #

HasKind AlgReal Source # 
Instance details

Defined in Data.SBV.Core.Kind

SymVal AlgReal Source # 
Instance details

Defined in Data.SBV.Core.Model

SatModel AlgReal Source #

AlgReal as extracted from a model

Instance details

Defined in Data.SBV.SMT.SMT

Methods

parseCVs :: [CV] -> Maybe (AlgReal, [CV]) Source #

cvtModel :: (AlgReal -> Maybe b) -> Maybe (AlgReal, [CV]) -> Maybe (b, [CV]) Source #

SMTValue AlgReal Source # 
Instance details

Defined in Data.SBV.Control.Utils

Methods

sexprToVal :: SExpr -> Maybe AlgReal Source #

Metric AlgReal Source # 
Instance details

Defined in Data.SBV.Core.Model

Associated Types

type MetricSpace AlgReal :: Type Source #

IEEEFloatConvertible AlgReal Source # 
Instance details

Defined in Data.SBV.Core.Floating

type MetricSpace AlgReal Source # 
Instance details

Defined in Data.SBV.Core.Model

sRealToSInteger :: SReal -> SInteger Source #

Convert an SReal to an SInteger. That is, it computes the largest integer n that satisfies sIntegerToSReal n <= r essentially giving us the floor.

For instance, 1.3 will be 1, but -1.3 will be -2.

Characters, Strings and Regular Expressions

type SChar = SBV Char Source #

A symbolic character. Note that, as far as SBV's symbolic strings are concerned, a character is currently an 8-bit unsigned value, corresponding to the ISO-8859-1 (Latin-1) character set: http://en.wikipedia.org/wiki/ISO/IEC_8859-1. A Haskell Char, on the other hand, is based on unicode. Therefore, there isn't a 1-1 correspondence between a Haskell character and an SBV character for the time being. This limitation is due to the SMT-solvers only supporting this particular subset. However, there is a pending proposal to add support for unicode, and SBV will track these changes to have full unicode support as solvers become available. For details, see: http://smtlib.cs.uiowa.edu/theories-UnicodeStrings.shtml

type SString = SBV String Source #

A symbolic string. Note that a symbolic string is not a list of symbolic characters, that is, it is not the case that SString = [SChar], unlike what one might expect following Haskell strings. An SString is a symbolic value of its own, of possibly arbitrary but finite length, and internally processed as one unit as opposed to a fixed-length list of characters.

Symbolic lists

type SList a = SBV [a] Source #

A symbolic list of items. Note that a symbolic list is not a list of symbolic items, that is, it is not the case that SList a = [a], unlike what one might expect following haskell lists/sequences. An SList is a symbolic value of its own, of possibly arbitrary but finite length, and internally processed as one unit as opposed to a fixed-length list of items. Note that lists can be nested, i.e., we do allow lists of lists of ... items.

Arrays of symbolic values

class SymArray array where Source #

Flat arrays of symbolic values An array a b is an array indexed by the type SBV a, with elements of type SBV b.

If a default value is supplied, then all the array elements will be initialized to this value. Otherwise, they will be left unspecified, i.e., a read from an unwritten location will produce an uninterpreted constant.

While it's certainly possible for user to create instances of SymArray, the SArray and SFunArray instances already provided should cover most use cases in practice. Note that there are a few differences between these two models in terms of use models:

  • SArray produces SMTLib arrays, and requires a solver that understands the array theory. SFunArray is internally handled, and thus can be used with any solver. (Note that all solvers except abc support arrays, so this isn't a big decision factor.)
  • For both arrays, if a default value is supplied, then reading from uninitialized cell will return that value. If the default is not given, then reading from uninitialized cells is still OK for both arrays, and will produce an uninterpreted constant in both cases.
  • Only SArray supports checking equality of arrays. (That is, checking if an entire array is equivalent to another.) SFunArrays cannot be checked for equality. In general, checking wholesale equality of arrays is a difficult decision problem and should be avoided if possible.
  • Only SFunArray supports compilation to C. Programs using SArray will not be accepted by the C-code generator.
  • You cannot use quickcheck on programs that contain these arrays. (Neither SArray nor SFunArray.)
  • With SArray, SBV transfers all array-processing to the SMT-solver. So, it can generate programs more quickly, but they might end up being too hard for the solver to handle. With SFunArray, SBV only generates code for individual elements and the array itself never shows up in the resulting SMTLib program. This puts more onus on the SBV side and might have some performance impacts, but it might generate problems that are easier for the SMT solvers to handle.

As a rule of thumb, try SArray first. These should generate compact code. However, if the backend solver has hard time solving the generated problems, switch to SFunArray. If you still have issues, please report so we can see what the problem might be!

Methods

newArray_ :: (MonadSymbolic m, HasKind a, HasKind b) => Maybe (SBV b) -> m (array a b) Source #

Generalization of newArray_

newArray :: (MonadSymbolic m, HasKind a, HasKind b) => String -> Maybe (SBV b) -> m (array a b) Source #

Generalization of newArray

readArray :: array a b -> SBV a -> SBV b Source #

Read the array element at a

writeArray :: SymVal b => array a b -> SBV a -> SBV b -> array a b Source #

Update the element at a to be b

mergeArrays :: SymVal b => SBV Bool -> array a b -> array a b -> array a b Source #

Merge two given arrays on the symbolic condition Intuitively: mergeArrays cond a b = if cond then a else b. Merging pushes the if-then-else choice down on to elements

Instances
SymArray SFunArray Source # 
Instance details

Defined in Data.SBV.Core.Data

Methods

newArray_ :: (MonadSymbolic m, HasKind a, HasKind b) => Maybe (SBV b) -> m (SFunArray a b) Source #

newArray :: (MonadSymbolic m, HasKind a, HasKind b) => String -> Maybe (SBV b) -> m (SFunArray a b) Source #

readArray :: SFunArray a b -> SBV a -> SBV b Source #

writeArray :: SymVal b => SFunArray a b -> SBV a -> SBV b -> SFunArray a b Source #

mergeArrays :: SymVal b => SBV Bool -> SFunArray a b -> SFunArray a b -> SFunArray a b Source #

newArrayInState :: (HasKind a, HasKind b) => Maybe String -> Maybe (SBV b) -> State -> IO (SFunArray a b) Source #

SymArray SArray Source # 
Instance details

Defined in Data.SBV.Core.Data

Methods

newArray_ :: (MonadSymbolic m, HasKind a, HasKind b) => Maybe (SBV b) -> m (SArray a b) Source #

newArray :: (MonadSymbolic m, HasKind a, HasKind b) => String -> Maybe (SBV b) -> m (SArray a b) Source #

readArray :: SArray a b -> SBV a -> SBV b Source #

writeArray :: SymVal b => SArray a b -> SBV a -> SBV b -> SArray a b Source #

mergeArrays :: SymVal b => SBV Bool -> SArray a b -> SArray a b -> SArray a b Source #

newArrayInState :: (HasKind a, HasKind b) => Maybe String -> Maybe (SBV b) -> State -> IO (SArray a b) Source #

data SArray a b Source #

Arrays implemented in terms of SMT-arrays: http://smtlib.cs.uiowa.edu/theories-ArraysEx.shtml

  • Maps directly to SMT-lib arrays
  • Reading from an unintialized value is OK. If the default value is given in newArray, it will be the result. Otherwise, the read yields an uninterpreted constant.
  • Can check for equality of these arrays
  • Cannot be used in code-generation (i.e., compilation to C)
  • Cannot quick-check theorems using SArray values
  • Typically slower as it heavily relies on SMT-solving for the array theory
Instances
SymArray SArray Source # 
Instance details

Defined in Data.SBV.Core.Data

Methods

newArray_ :: (MonadSymbolic m, HasKind a, HasKind b) => Maybe (SBV b) -> m (SArray a b) Source #

newArray :: (MonadSymbolic m, HasKind a, HasKind b) => String -> Maybe (SBV b) -> m (SArray a b) Source #

readArray :: SArray a b -> SBV a -> SBV b Source #

writeArray :: SymVal b => SArray a b -> SBV a -> SBV b -> SArray a b Source #

mergeArrays :: SymVal b => SBV Bool -> SArray a b -> SArray a b -> SArray a b Source #

newArrayInState :: (HasKind a, HasKind b) => Maybe String -> Maybe (SBV b) -> State -> IO (SArray a b) Source #

(HasKind a, HasKind b, MProvable m p) => MProvable m (SArray a b -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: (SArray a b -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> (SArray a b -> p) -> SymbolicT m SBool Source #

forSome_ :: (SArray a b -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> (SArray a b -> p) -> SymbolicT m SBool Source #

prove :: (SArray a b -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> (SArray a b -> p) -> m ThmResult Source #

sat :: (SArray a b -> p) -> m SatResult Source #

satWith :: SMTConfig -> (SArray a b -> p) -> m SatResult Source #

allSat :: (SArray a b -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> (SArray a b -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> (SArray a b -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> (SArray a b -> p) -> m OptimizeResult Source #

isVacuous :: (SArray a b -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> (SArray a b -> p) -> m Bool Source #

isTheorem :: (SArray a b -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> (SArray a b -> p) -> m Bool Source #

isSatisfiable :: (SArray a b -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> (SArray a b -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> (SArray a b -> p) -> SMTResult -> m SMTResult Source #

(HasKind a, HasKind b) => Show (SArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Data

Methods

showsPrec :: Int -> SArray a b -> ShowS #

show :: SArray a b -> String #

showList :: [SArray a b] -> ShowS #

SymVal b => Mergeable (SArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> SArray a b -> SArray a b -> SArray a b Source #

select :: (Ord b0, SymVal b0, Num b0) => [SArray a b] -> SArray a b -> SBV b0 -> SArray a b Source #

EqSymbolic (SArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: SArray a b -> SArray a b -> SBool Source #

(./=) :: SArray a b -> SArray a b -> SBool Source #

(.===) :: SArray a b -> SArray a b -> SBool Source #

(./==) :: SArray a b -> SArray a b -> SBool Source #

distinct :: [SArray a b] -> SBool Source #

allEqual :: [SArray a b] -> SBool Source #

sElem :: SArray a b -> [SArray a b] -> SBool Source #

data SFunArray a b Source #

Arrays implemented internally, without translating to SMT-Lib functions:

  • Internally handled by the library and not mapped to SMT-Lib, hence can be used with solvers that don't support arrays. (Such as abc.)
  • Reading from an unintialized value is OK. If the default value is given in newArray, it will be the result. Otherwise, the read yields an uninterpreted constant.
  • Cannot check for equality of arrays.
  • Can be used in code-generation (i.e., compilation to C).
  • Can not quick-check theorems using SFunArray values
  • Typically faster as it gets compiled away during translation.
Instances
SymArray SFunArray Source # 
Instance details

Defined in Data.SBV.Core.Data

Methods

newArray_ :: (MonadSymbolic m, HasKind a, HasKind b) => Maybe (SBV b) -> m (SFunArray a b) Source #

newArray :: (MonadSymbolic m, HasKind a, HasKind b) => String -> Maybe (SBV b) -> m (SFunArray a b) Source #

readArray :: SFunArray a b -> SBV a -> SBV b Source #

writeArray :: SymVal b => SFunArray a b -> SBV a -> SBV b -> SFunArray a b Source #

mergeArrays :: SymVal b => SBV Bool -> SFunArray a b -> SFunArray a b -> SFunArray a b Source #

newArrayInState :: (HasKind a, HasKind b) => Maybe String -> Maybe (SBV b) -> State -> IO (SFunArray a b) Source #

(HasKind a, HasKind b, MProvable m p) => MProvable m (SFunArray a b -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

(HasKind a, HasKind b) => Show (SFunArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Data

Methods

showsPrec :: Int -> SFunArray a b -> ShowS #

show :: SFunArray a b -> String #

showList :: [SFunArray a b] -> ShowS #

SymVal b => Mergeable (SFunArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> SFunArray a b -> SFunArray a b -> SFunArray a b Source #

select :: (Ord b0, SymVal b0, Num b0) => [SFunArray a b] -> SFunArray a b -> SBV b0 -> SFunArray a b Source #

Creating symbolic values

Single value

sBool :: MonadSymbolic m => String -> m SBool Source #

Generalization of sBool

sWord8 :: MonadSymbolic m => String -> m SWord8 Source #

Generalization of sWord8

sWord16 :: MonadSymbolic m => String -> m SWord16 Source #

Generalization of sWord16

sWord32 :: MonadSymbolic m => String -> m SWord32 Source #

Generalization of sWord32

sWord64 :: MonadSymbolic m => String -> m SWord64 Source #

Generalization of sWord64

sInt8 :: MonadSymbolic m => String -> m SInt8 Source #

Generalization of sInt8

sInt16 :: MonadSymbolic m => String -> m SInt16 Source #

Generalization of sInt16

sInt32 :: MonadSymbolic m => String -> m SInt32 Source #

Generalization of sInt32

sInt64 :: MonadSymbolic m => String -> m SInt64 Source #

Generalization of sInt64

sInteger :: MonadSymbolic m => String -> m SInteger Source #

Generalization of sInteger

sReal :: MonadSymbolic m => String -> m SReal Source #

Generalization of sReal

sFloat :: MonadSymbolic m => String -> m SFloat Source #

Generalization of sFloat

sDouble :: MonadSymbolic m => String -> m SDouble Source #

Generalization of sDouble

sChar :: MonadSymbolic m => String -> m SChar Source #

Generalization of sChar

sString :: MonadSymbolic m => String -> m SString Source #

Generalization of sString

sList :: (SymVal a, MonadSymbolic m) => String -> m (SList a) Source #

Generalization of sList

List of values

sBools :: MonadSymbolic m => [String] -> m [SBool] Source #

Generalization of sBools

sWord8s :: MonadSymbolic m => [String] -> m [SWord8] Source #

Generalization of sWord8s

sWord16s :: MonadSymbolic m => [String] -> m [SWord16] Source #

Generalization of sWord16s

sWord32s :: MonadSymbolic m => [String] -> m [SWord32] Source #

Generalization of sWord32s

sWord64s :: MonadSymbolic m => [String] -> m [SWord64] Source #

Generalization of sWord64s

sInt8s :: MonadSymbolic m => [String] -> m [SInt8] Source #

Generalization of sInt8s

sInt16s :: MonadSymbolic m => [String] -> m [SInt16] Source #

Generalization of sInt16s

sInt32s :: MonadSymbolic m => [String] -> m [SInt32] Source #

Generalization of sInt32s

sInt64s :: MonadSymbolic m => [String] -> m [SInt64] Source #

Generalization of sInt64s

sIntegers :: MonadSymbolic m => [String] -> m [SInteger] Source #

Generalization of sIntegers

sReals :: MonadSymbolic m => [String] -> m [SReal] Source #

Generalization of sReals

sFloats :: MonadSymbolic m => [String] -> m [SFloat] Source #

Generalization of sFloats

sDoubles :: MonadSymbolic m => [String] -> m [SDouble] Source #

Generalization of sDoubles

sChars :: MonadSymbolic m => [String] -> m [SChar] Source #

Generalization of sChars

sStrings :: MonadSymbolic m => [String] -> m [SString] Source #

Generalization of sStrings

sLists :: (SymVal a, MonadSymbolic m) => [String] -> m [SList a] Source #

Generalization of sLists

Symbolic Equality and Comparisons

class EqSymbolic a where Source #

Symbolic Equality. Note that we can't use Haskell's Eq class since Haskell insists on returning Bool Comparing symbolic values will necessarily return a symbolic value.

Minimal complete definition

(.==)

Methods

(.==) :: a -> a -> SBool infix 4 Source #

Symbolic equality.

(./=) :: a -> a -> SBool infix 4 Source #

Symbolic inequality.

(.===) :: a -> a -> SBool infix 4 Source #

Strong equality. On floats ('SFloat'/'SDouble'), strong equality is object equality; that is NaN == NaN holds, but +0 == -0 doesn't. On other types, (.===) is simply (.==). Note that (.==) is the right notion of equality for floats per IEEE754 specs, since by definition +0 == -0 and NaN equals no other value including itself. But occasionally we want to be stronger and state NaN equals NaN and +0 and -0 are different from each other. In a context where your type is concrete, simply use fpIsEqualObject. But in a polymorphic context, use the strong equality instead.

NB. If you do not care about or work with floats, simply use (.==) and (./=).

(./==) :: a -> a -> SBool infix 4 Source #

Negation of strong equality. Equaivalent to negation of (.===) on all types.

distinct :: [a] -> SBool Source #

Returns (symbolic) sTrue if all the elements of the given list are different.

allEqual :: [a] -> SBool Source #

Returns (symbolic) sTrue if all the elements of the given list are the same.

sElem :: a -> [a] -> SBool Source #

Symbolic membership test.

Instances
EqSymbolic Bool Source # 
Instance details

Defined in Data.SBV.Core.Model

EqSymbolic a => EqSymbolic [a] Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: [a] -> [a] -> SBool Source #

(./=) :: [a] -> [a] -> SBool Source #

(.===) :: [a] -> [a] -> SBool Source #

(./==) :: [a] -> [a] -> SBool Source #

distinct :: [[a]] -> SBool Source #

allEqual :: [[a]] -> SBool Source #

sElem :: [a] -> [[a]] -> SBool Source #

EqSymbolic a => EqSymbolic (Maybe a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: Maybe a -> Maybe a -> SBool Source #

(./=) :: Maybe a -> Maybe a -> SBool Source #

(.===) :: Maybe a -> Maybe a -> SBool Source #

(./==) :: Maybe a -> Maybe a -> SBool Source #

distinct :: [Maybe a] -> SBool Source #

allEqual :: [Maybe a] -> SBool Source #

sElem :: Maybe a -> [Maybe a] -> SBool Source #

EqSymbolic (SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: SBV a -> SBV a -> SBool Source #

(./=) :: SBV a -> SBV a -> SBool Source #

(.===) :: SBV a -> SBV a -> SBool Source #

(./==) :: SBV a -> SBV a -> SBool Source #

distinct :: [SBV a] -> SBool Source #

allEqual :: [SBV a] -> SBool Source #

sElem :: SBV a -> [SBV a] -> SBool Source #

EqSymbolic a => EqSymbolic (S a) Source #

Symbolic equality for S.

Instance details

Defined in Documentation.SBV.Examples.ProofTools.BMC

Methods

(.==) :: S a -> S a -> SBool Source #

(./=) :: S a -> S a -> SBool Source #

(.===) :: S a -> S a -> SBool Source #

(./==) :: S a -> S a -> SBool Source #

distinct :: [S a] -> SBool Source #

allEqual :: [S a] -> SBool Source #

sElem :: S a -> [S a] -> SBool Source #

(EqSymbolic a, EqSymbolic b) => EqSymbolic (Either a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: Either a b -> Either a b -> SBool Source #

(./=) :: Either a b -> Either a b -> SBool Source #

(.===) :: Either a b -> Either a b -> SBool Source #

(./==) :: Either a b -> Either a b -> SBool Source #

distinct :: [Either a b] -> SBool Source #

allEqual :: [Either a b] -> SBool Source #

sElem :: Either a b -> [Either a b] -> SBool Source #

(EqSymbolic a, EqSymbolic b) => EqSymbolic (a, b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: (a, b) -> (a, b) -> SBool Source #

(./=) :: (a, b) -> (a, b) -> SBool Source #

(.===) :: (a, b) -> (a, b) -> SBool Source #

(./==) :: (a, b) -> (a, b) -> SBool Source #

distinct :: [(a, b)] -> SBool Source #

allEqual :: [(a, b)] -> SBool Source #

sElem :: (a, b) -> [(a, b)] -> SBool Source #

EqSymbolic (SArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: SArray a b -> SArray a b -> SBool Source #

(./=) :: SArray a b -> SArray a b -> SBool Source #

(.===) :: SArray a b -> SArray a b -> SBool Source #

(./==) :: SArray a b -> SArray a b -> SBool Source #

distinct :: [SArray a b] -> SBool Source #

allEqual :: [SArray a b] -> SBool Source #

sElem :: SArray a b -> [SArray a b] -> SBool Source #

(EqSymbolic a, EqSymbolic b, EqSymbolic c) => EqSymbolic (a, b, c) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: (a, b, c) -> (a, b, c) -> SBool Source #

(./=) :: (a, b, c) -> (a, b, c) -> SBool Source #

(.===) :: (a, b, c) -> (a, b, c) -> SBool Source #

(./==) :: (a, b, c) -> (a, b, c) -> SBool Source #

distinct :: [(a, b, c)] -> SBool Source #

allEqual :: [(a, b, c)] -> SBool Source #

sElem :: (a, b, c) -> [(a, b, c)] -> SBool Source #

(EqSymbolic a, EqSymbolic b, EqSymbolic c, EqSymbolic d) => EqSymbolic (a, b, c, d) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

(./=) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

(.===) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

(./==) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

distinct :: [(a, b, c, d)] -> SBool Source #

allEqual :: [(a, b, c, d)] -> SBool Source #

sElem :: (a, b, c, d) -> [(a, b, c, d)] -> SBool Source #

(EqSymbolic a, EqSymbolic b, EqSymbolic c, EqSymbolic d, EqSymbolic e) => EqSymbolic (a, b, c, d, e) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

(./=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

(.===) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

(./==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

distinct :: [(a, b, c, d, e)] -> SBool Source #

allEqual :: [(a, b, c, d, e)] -> SBool Source #

sElem :: (a, b, c, d, e) -> [(a, b, c, d, e)] -> SBool Source #

(EqSymbolic a, EqSymbolic b, EqSymbolic c, EqSymbolic d, EqSymbolic e, EqSymbolic f) => EqSymbolic (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

(./=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

(.===) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

(./==) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

distinct :: [(a, b, c, d, e, f)] -> SBool Source #

allEqual :: [(a, b, c, d, e, f)] -> SBool Source #

sElem :: (a, b, c, d, e, f) -> [(a, b, c, d, e, f)] -> SBool Source #

(EqSymbolic a, EqSymbolic b, EqSymbolic c, EqSymbolic d, EqSymbolic e, EqSymbolic f, EqSymbolic g) => EqSymbolic (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.==) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

(./=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

(.===) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

(./==) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

distinct :: [(a, b, c, d, e, f, g)] -> SBool Source #

allEqual :: [(a, b, c, d, e, f, g)] -> SBool Source #

sElem :: (a, b, c, d, e, f, g) -> [(a, b, c, d, e, f, g)] -> SBool Source #

class (Mergeable a, EqSymbolic a) => OrdSymbolic a where Source #

Symbolic Comparisons. Similar to Eq, we cannot implement Haskell's Ord class since there is no way to return an Ordering value from a symbolic comparison. Furthermore, OrdSymbolic requires Mergeable to implement if-then-else, for the benefit of implementing symbolic versions of max and min functions.

Minimal complete definition

(.<)

Methods

(.<) :: a -> a -> SBool infix 4 Source #

Symbolic less than.

(.<=) :: a -> a -> SBool infix 4 Source #

Symbolic less than or equal to.

(.>) :: a -> a -> SBool infix 4 Source #

Symbolic greater than.

(.>=) :: a -> a -> SBool infix 4 Source #

Symbolic greater than or equal to.

smin :: a -> a -> a Source #

Symbolic minimum.

smax :: a -> a -> a Source #

Symbolic maximum.

inRange :: a -> (a, a) -> SBool Source #

Is the value withing the allowed inclusive range?

Instances
OrdSymbolic a => OrdSymbolic [a] Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: [a] -> [a] -> SBool Source #

(.<=) :: [a] -> [a] -> SBool Source #

(.>) :: [a] -> [a] -> SBool Source #

(.>=) :: [a] -> [a] -> SBool Source #

smin :: [a] -> [a] -> [a] Source #

smax :: [a] -> [a] -> [a] Source #

inRange :: [a] -> ([a], [a]) -> SBool Source #

OrdSymbolic a => OrdSymbolic (Maybe a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: Maybe a -> Maybe a -> SBool Source #

(.<=) :: Maybe a -> Maybe a -> SBool Source #

(.>) :: Maybe a -> Maybe a -> SBool Source #

(.>=) :: Maybe a -> Maybe a -> SBool Source #

smin :: Maybe a -> Maybe a -> Maybe a Source #

smax :: Maybe a -> Maybe a -> Maybe a Source #

inRange :: Maybe a -> (Maybe a, Maybe a) -> SBool Source #

(Ord a, SymVal a) => OrdSymbolic (SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: SBV a -> SBV a -> SBool Source #

(.<=) :: SBV a -> SBV a -> SBool Source #

(.>) :: SBV a -> SBV a -> SBool Source #

(.>=) :: SBV a -> SBV a -> SBool Source #

smin :: SBV a -> SBV a -> SBV a Source #

smax :: SBV a -> SBV a -> SBV a Source #

inRange :: SBV a -> (SBV a, SBV a) -> SBool Source #

(OrdSymbolic a, OrdSymbolic b) => OrdSymbolic (Either a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: Either a b -> Either a b -> SBool Source #

(.<=) :: Either a b -> Either a b -> SBool Source #

(.>) :: Either a b -> Either a b -> SBool Source #

(.>=) :: Either a b -> Either a b -> SBool Source #

smin :: Either a b -> Either a b -> Either a b Source #

smax :: Either a b -> Either a b -> Either a b Source #

inRange :: Either a b -> (Either a b, Either a b) -> SBool Source #

(OrdSymbolic a, OrdSymbolic b) => OrdSymbolic (a, b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: (a, b) -> (a, b) -> SBool Source #

(.<=) :: (a, b) -> (a, b) -> SBool Source #

(.>) :: (a, b) -> (a, b) -> SBool Source #

(.>=) :: (a, b) -> (a, b) -> SBool Source #

smin :: (a, b) -> (a, b) -> (a, b) Source #

smax :: (a, b) -> (a, b) -> (a, b) Source #

inRange :: (a, b) -> ((a, b), (a, b)) -> SBool Source #

(OrdSymbolic a, OrdSymbolic b, OrdSymbolic c) => OrdSymbolic (a, b, c) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: (a, b, c) -> (a, b, c) -> SBool Source #

(.<=) :: (a, b, c) -> (a, b, c) -> SBool Source #

(.>) :: (a, b, c) -> (a, b, c) -> SBool Source #

(.>=) :: (a, b, c) -> (a, b, c) -> SBool Source #

smin :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

smax :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

inRange :: (a, b, c) -> ((a, b, c), (a, b, c)) -> SBool Source #

(OrdSymbolic a, OrdSymbolic b, OrdSymbolic c, OrdSymbolic d) => OrdSymbolic (a, b, c, d) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

(.<=) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

(.>) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

(.>=) :: (a, b, c, d) -> (a, b, c, d) -> SBool Source #

smin :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

smax :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

inRange :: (a, b, c, d) -> ((a, b, c, d), (a, b, c, d)) -> SBool Source #

(OrdSymbolic a, OrdSymbolic b, OrdSymbolic c, OrdSymbolic d, OrdSymbolic e) => OrdSymbolic (a, b, c, d, e) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

(.<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

(.>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

(.>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> SBool Source #

smin :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

smax :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

inRange :: (a, b, c, d, e) -> ((a, b, c, d, e), (a, b, c, d, e)) -> SBool Source #

(OrdSymbolic a, OrdSymbolic b, OrdSymbolic c, OrdSymbolic d, OrdSymbolic e, OrdSymbolic f) => OrdSymbolic (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

(.<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

(.>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

(.>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> SBool Source #

smin :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

smax :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

inRange :: (a, b, c, d, e, f) -> ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> SBool Source #

(OrdSymbolic a, OrdSymbolic b, OrdSymbolic c, OrdSymbolic d, OrdSymbolic e, OrdSymbolic f, OrdSymbolic g) => OrdSymbolic (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(.<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

(.<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

(.>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

(.>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> SBool Source #

smin :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

smax :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

inRange :: (a, b, c, d, e, f, g) -> ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> SBool Source #

class Equality a where Source #

Equality as a proof method. Allows for very concise construction of equivalence proofs, which is very typical in bit-precise proofs.

Methods

(===) :: a -> a -> IO ThmResult infix 4 Source #

Instances
(SymVal a, SymVal b, EqSymbolic z) => Equality ((SBV a, SBV b) -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: ((SBV a, SBV b) -> z) -> ((SBV a, SBV b) -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, EqSymbolic z) => Equality ((SBV a, SBV b, SBV c) -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: ((SBV a, SBV b, SBV c) -> z) -> ((SBV a, SBV b, SBV c) -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, EqSymbolic z) => Equality ((SBV a, SBV b, SBV c, SBV d) -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: ((SBV a, SBV b, SBV c, SBV d) -> z) -> ((SBV a, SBV b, SBV c, SBV d) -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, EqSymbolic z) => Equality ((SBV a, SBV b, SBV c, SBV d, SBV e) -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> z) -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, EqSymbolic z) => Equality ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> z) -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, SymVal g, EqSymbolic z) => Equality ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> z) -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, SymVal g, EqSymbolic z) => Equality (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> SBV f -> SBV g -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> SBV f -> SBV g -> z) -> (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> SBV f -> SBV g -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, EqSymbolic z) => Equality (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> SBV f -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> SBV f -> z) -> (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> SBV f -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, EqSymbolic z) => Equality (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> z) -> (SBV a -> SBV b -> SBV c -> SBV d -> SBV e -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, EqSymbolic z) => Equality (SBV a -> SBV b -> SBV c -> SBV d -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: (SBV a -> SBV b -> SBV c -> SBV d -> z) -> (SBV a -> SBV b -> SBV c -> SBV d -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, SymVal c, EqSymbolic z) => Equality (SBV a -> SBV b -> SBV c -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: (SBV a -> SBV b -> SBV c -> z) -> (SBV a -> SBV b -> SBV c -> z) -> IO ThmResult Source #

(SymVal a, SymVal b, EqSymbolic z) => Equality (SBV a -> SBV b -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: (SBV a -> SBV b -> z) -> (SBV a -> SBV b -> z) -> IO ThmResult Source #

(SymVal a, EqSymbolic z) => Equality (SBV a -> z) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

(===) :: (SBV a -> z) -> (SBV a -> z) -> IO ThmResult Source #

Conditionals: Mergeable values

class Mergeable a where Source #

Symbolic conditionals are modeled by the Mergeable class, describing how to merge the results of an if-then-else call with a symbolic test. SBV provides all basic types as instances of this class, so users only need to declare instances for custom data-types of their programs as needed.

A Mergeable instance may be automatically derived for a custom data-type with a single constructor where the type of each field is an instance of Mergeable, such as a record of symbolic values. Users only need to add Generic and Mergeable to the deriving clause for the data-type. See Status for an example and an illustration of what the instance would look like if written by hand.

The function select is a total-indexing function out of a list of choices with a default value, simulating array/list indexing. It's an n-way generalization of the ite function.

Minimal complete definition: None, if the type is instance of Generic. Otherwise symbolicMerge. Note that most types subject to merging are likely to be trivial instances of Generic.

Minimal complete definition

Nothing

Methods

symbolicMerge :: Bool -> SBool -> a -> a -> a Source #

Merge two values based on the condition. The first argument states whether we force the then-and-else branches before the merging, at the word level. This is an efficiency concern; one that we'd rather not make but unfortunately necessary for getting symbolic simulation working efficiently.

select :: (Ord b, SymVal b, Num b) => [a] -> a -> SBV b -> a Source #

Total indexing operation. select xs default index is intuitively the same as xs !! index, except it evaluates to default if index underflows/overflows.

symbolicMerge :: (Generic a, GMergeable (Rep a)) => Bool -> SBool -> a -> a -> a Source #

Merge two values based on the condition. The first argument states whether we force the then-and-else branches before the merging, at the word level. This is an efficiency concern; one that we'd rather not make but unfortunately necessary for getting symbolic simulation working efficiently.

Instances
Mergeable () Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> () -> () -> () Source #

select :: (Ord b, SymVal b, Num b) => [()] -> () -> SBV b -> () Source #

Mergeable Mostek Source # 
Instance details

Defined in Documentation.SBV.Examples.BitPrecise.Legato

Methods

symbolicMerge :: Bool -> SBool -> Mostek -> Mostek -> Mostek Source #

select :: (Ord b, SymVal b, Num b) => [Mostek] -> Mostek -> SBV b -> Mostek Source #

Mergeable Status Source # 
Instance details

Defined in Documentation.SBV.Examples.Puzzles.U2Bridge

Methods

symbolicMerge :: Bool -> SBool -> Status -> Status -> Status Source #

select :: (Ord b, SymVal b, Num b) => [Status] -> Status -> SBV b -> Status Source #

Mergeable a => Mergeable [a] Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> [a] -> [a] -> [a] Source #

select :: (Ord b, SymVal b, Num b) => [[a]] -> [a] -> SBV b -> [a] Source #

Mergeable a => Mergeable (Maybe a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> Maybe a -> Maybe a -> Maybe a Source #

select :: (Ord b, SymVal b, Num b) => [Maybe a] -> Maybe a -> SBV b -> Maybe a Source #

Mergeable a => Mergeable (ZipList a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> ZipList a -> ZipList a -> ZipList a Source #

select :: (Ord b, SymVal b, Num b) => [ZipList a] -> ZipList a -> SBV b -> ZipList a Source #

SymVal a => Mergeable (SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> SBV a -> SBV a -> SBV a Source #

select :: (Ord b, SymVal b, Num b) => [SBV a] -> SBV a -> SBV b -> SBV a Source #

Mergeable a => Mergeable (S a) Source # 
Instance details

Defined in Documentation.SBV.Examples.ProofTools.Fibonacci

Methods

symbolicMerge :: Bool -> SBool -> S a -> S a -> S a Source #

select :: (Ord b, SymVal b, Num b) => [S a] -> S a -> SBV b -> S a Source #

Mergeable a => Mergeable (S a) Source # 
Instance details

Defined in Documentation.SBV.Examples.ProofTools.Sum

Methods

symbolicMerge :: Bool -> SBool -> S a -> S a -> S a Source #

select :: (Ord b, SymVal b, Num b) => [S a] -> S a -> SBV b -> S a Source #

Mergeable a => Mergeable (Move a) Source #

Mergeable instance for Move simply pushes the merging the data after run of each branch starting from the same state.

Instance details

Defined in Documentation.SBV.Examples.Puzzles.U2Bridge

Methods

symbolicMerge :: Bool -> SBool -> Move a -> Move a -> Move a Source #

select :: (Ord b, SymVal b, Num b) => [Move a] -> Move a -> SBV b -> Move a Source #

SymVal a => Mergeable (AppS a) Source # 
Instance details

Defined in Documentation.SBV.Examples.WeakestPreconditions.Append

Methods

symbolicMerge :: Bool -> SBool -> AppS a -> AppS a -> AppS a Source #

select :: (Ord b, SymVal b, Num b) => [AppS a] -> AppS a -> SBV b -> AppS a Source #

Mergeable a => Mergeable (FibS a) Source # 
Instance details

Defined in Documentation.SBV.Examples.WeakestPreconditions.Fib

Methods

symbolicMerge :: Bool -> SBool -> FibS a -> FibS a -> FibS a Source #

select :: (Ord b, SymVal b, Num b) => [FibS a] -> FibS a -> SBV b -> FibS a Source #

Mergeable a => Mergeable (GCDS a) Source # 
Instance details

Defined in Documentation.SBV.Examples.WeakestPreconditions.GCD

Methods

symbolicMerge :: Bool -> SBool -> GCDS a -> GCDS a -> GCDS a Source #

select :: (Ord b, SymVal b, Num b) => [GCDS a] -> GCDS a -> SBV b -> GCDS a Source #

Mergeable a => Mergeable (DivS a) Source # 
Instance details

Defined in Documentation.SBV.Examples.WeakestPreconditions.IntDiv

Methods

symbolicMerge :: Bool -> SBool -> DivS a -> DivS a -> DivS a Source #

select :: (Ord b, SymVal b, Num b) => [DivS a] -> DivS a -> SBV b -> DivS a Source #

Mergeable a => Mergeable (SqrtS a) Source # 
Instance details

Defined in Documentation.SBV.Examples.WeakestPreconditions.IntSqrt

Methods

symbolicMerge :: Bool -> SBool -> SqrtS a -> SqrtS a -> SqrtS a Source #

select :: (Ord b, SymVal b, Num b) => [SqrtS a] -> SqrtS a -> SBV b -> SqrtS a Source #

SymVal a => Mergeable (LenS a) Source # 
Instance details

Defined in Documentation.SBV.Examples.WeakestPreconditions.Length

Methods

symbolicMerge :: Bool -> SBool -> LenS a -> LenS a -> LenS a Source #

select :: (Ord b, SymVal b, Num b) => [LenS a] -> LenS a -> SBV b -> LenS a Source #

Mergeable a => Mergeable (SumS a) Source # 
Instance details

Defined in Documentation.SBV.Examples.WeakestPreconditions.Sum

Methods

symbolicMerge :: Bool -> SBool -> SumS a -> SumS a -> SumS a Source #

select :: (Ord b, SymVal b, Num b) => [SumS a] -> SumS a -> SBV b -> SumS a Source #

Mergeable b => Mergeable (a -> b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> (a -> b) -> (a -> b) -> a -> b Source #

select :: (Ord b0, SymVal b0, Num b0) => [a -> b] -> (a -> b) -> SBV b0 -> a -> b Source #

(Mergeable a, Mergeable b) => Mergeable (Either a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> Either a b -> Either a b -> Either a b Source #

select :: (Ord b0, SymVal b0, Num b0) => [Either a b] -> Either a b -> SBV b0 -> Either a b Source #

(Mergeable a, Mergeable b) => Mergeable (a, b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> (a, b) -> (a, b) -> (a, b) Source #

select :: (Ord b0, SymVal b0, Num b0) => [(a, b)] -> (a, b) -> SBV b0 -> (a, b) Source #

(Ix a, Mergeable b) => Mergeable (Array a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> Array a b -> Array a b -> Array a b Source #

select :: (Ord b0, SymVal b0, Num b0) => [Array a b] -> Array a b -> SBV b0 -> Array a b Source #

SymVal b => Mergeable (SFunArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> SFunArray a b -> SFunArray a b -> SFunArray a b Source #

select :: (Ord b0, SymVal b0, Num b0) => [SFunArray a b] -> SFunArray a b -> SBV b0 -> SFunArray a b Source #

SymVal b => Mergeable (SArray a b) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> SArray a b -> SArray a b -> SArray a b Source #

select :: (Ord b0, SymVal b0, Num b0) => [SArray a b] -> SArray a b -> SBV b0 -> SArray a b Source #

SymVal e => Mergeable (STree i e) Source # 
Instance details

Defined in Data.SBV.Tools.STree

Methods

symbolicMerge :: Bool -> SBool -> STree i e -> STree i e -> STree i e Source #

select :: (Ord b, SymVal b, Num b) => [STree i e] -> STree i e -> SBV b -> STree i e Source #

(Mergeable a, Mergeable b, Mergeable c) => Mergeable (a, b, c) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> (a, b, c) -> (a, b, c) -> (a, b, c) Source #

select :: (Ord b0, SymVal b0, Num b0) => [(a, b, c)] -> (a, b, c) -> SBV b0 -> (a, b, c) Source #

(Mergeable a, Mergeable b, Mergeable c, Mergeable d) => Mergeable (a, b, c, d) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

select :: (Ord b0, SymVal b0, Num b0) => [(a, b, c, d)] -> (a, b, c, d) -> SBV b0 -> (a, b, c, d) Source #

(Mergeable a, Mergeable b, Mergeable c, Mergeable d, Mergeable e) => Mergeable (a, b, c, d, e) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

select :: (Ord b0, SymVal b0, Num b0) => [(a, b, c, d, e)] -> (a, b, c, d, e) -> SBV b0 -> (a, b, c, d, e) Source #

(Mergeable a, Mergeable b, Mergeable c, Mergeable d, Mergeable e, Mergeable f) => Mergeable (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

select :: (Ord b0, SymVal b0, Num b0) => [(a, b, c, d, e, f)] -> (a, b, c, d, e, f) -> SBV b0 -> (a, b, c, d, e, f) Source #

(Mergeable a, Mergeable b, Mergeable c, Mergeable d, Mergeable e, Mergeable f, Mergeable g) => Mergeable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

symbolicMerge :: Bool -> SBool -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

select :: (Ord b0, SymVal b0, Num b0) => [(a, b, c, d, e, f, g)] -> (a, b, c, d, e, f, g) -> SBV b0 -> (a, b, c, d, e, f, g) Source #

ite :: Mergeable a => SBool -> a -> a -> a Source #

If-then-else. This is by definition symbolicMerge with both branches forced. This is typically the desired behavior, but also see iteLazy should you need more laziness.

iteLazy :: Mergeable a => SBool -> a -> a -> a Source #

A Lazy version of ite, which does not force its arguments. This might cause issues for symbolic simulation with large thunks around, so use with care.

Symbolic integral numbers

class (SymVal a, Num a, Bits a, Integral a) => SIntegral a Source #

Symbolic Numbers. This is a simple class that simply incorporates all number like base types together, simplifying writing polymorphic type-signatures that work for all symbolic numbers, such as SWord8, SInt8 etc. For instance, we can write a generic list-minimum function as follows:

   mm :: SIntegral a => [SBV a] -> SBV a
   mm = foldr1 (a b -> ite (a .<= b) a b)

It is similar to the standard Integral class, except ranging over symbolic instances.

Instances
SIntegral Int8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Int16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Int32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Int64 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Integer Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Word8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Word16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Word32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Word64 Source # 
Instance details

Defined in Data.SBV.Core.Model

SIntegral Word4 Source #

SIntegral instance, using default methods

Instance details

Defined in Documentation.SBV.Examples.Misc.Word4

Division and Modulus

class SDivisible a where Source #

The SDivisible class captures the essence of division. Unfortunately we cannot use Haskell's Integral class since the Real and Enum superclasses are not implementable for symbolic bit-vectors. However, quotRem and divMod both make perfect sense, and the SDivisible class captures this operation. One issue is how division by 0 behaves. The verification technology requires total functions, and there are several design choices here. We follow Isabelle/HOL approach of assigning the value 0 for division by 0. Therefore, we impose the following pair of laws:

     x sQuotRem 0 = (0, x)
     x sDivMod  0 = (0, x)

Note that our instances implement this law even when x is 0 itself.

NB. quot truncates toward zero, while div truncates toward negative infinity.

Minimal complete definition

sQuotRem, sDivMod

Methods

sQuotRem :: a -> a -> (a, a) Source #

sDivMod :: a -> a -> (a, a) Source #

sQuot :: a -> a -> a Source #

sRem :: a -> a -> a Source #

sDiv :: a -> a -> a Source #

sMod :: a -> a -> a Source #

Instances
SDivisible Int8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Int16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Int32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Int64 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Integer Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Word8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Word16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Word32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible Word64 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible CV Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

sQuotRem :: CV -> CV -> (CV, CV) Source #

sDivMod :: CV -> CV -> (CV, CV) Source #

sQuot :: CV -> CV -> CV Source #

sRem :: CV -> CV -> CV Source #

sDiv :: CV -> CV -> CV Source #

sMod :: CV -> CV -> CV Source #

SDivisible SInteger Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SInt64 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SInt32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SInt16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SInt8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SWord64 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SWord32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SWord16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SWord8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SDivisible SWord4 Source #

SDvisible instance, using default methods

Instance details

Defined in Documentation.SBV.Examples.Misc.Word4

SDivisible Word4 Source #

SDvisible instance, using 0-extension

Instance details

Defined in Documentation.SBV.Examples.Misc.Word4

Bit-vector operations

Conversions

sFromIntegral :: forall a b. (Integral a, HasKind a, Num a, SymVal a, HasKind b, Num b, SymVal b) => SBV a -> SBV b Source #

Conversion between integral-symbolic values, akin to Haskell's fromIntegral

Shifts and rotates

sShiftLeft :: (SIntegral a, SIntegral b) => SBV a -> SBV b -> SBV a Source #

Generalization of shiftL, when the shift-amount is symbolic. Since Haskell's shiftL only takes an Int as the shift amount, it cannot be used when we have a symbolic amount to shift with.

sShiftRight :: (SIntegral a, SIntegral b) => SBV a -> SBV b -> SBV a Source #

Generalization of shiftR, when the shift-amount is symbolic. Since Haskell's shiftR only takes an Int as the shift amount, it cannot be used when we have a symbolic amount to shift with.

NB. If the shiftee is signed, then this is an arithmetic shift; otherwise it's logical, following the usual Haskell convention. See sSignedShiftArithRight for a variant that explicitly uses the msb as the sign bit, even for unsigned underlying types.

sRotateLeft :: (SIntegral a, SIntegral b) => SBV a -> SBV b -> SBV a Source #

Generalization of rotateL, when the shift-amount is symbolic. Since Haskell's rotateL only takes an Int as the shift amount, it cannot be used when we have a symbolic amount to shift with. The first argument should be a bounded quantity.

sBarrelRotateLeft :: (SFiniteBits a, SFiniteBits b) => SBV a -> SBV b -> SBV a Source #

An implementation of rotate-left, using a barrel shifter like design. Only works when both arguments are finite bitvectors, and furthermore when the second argument is unsigned. The first condition is enforced by the type, but the second is dynamically checked. We provide this implementation as an alternative to sRotateLeft since SMTLib logic does not support variable argument rotates (as opposed to shifts), and thus this implementation can produce better code for verification compared to sRotateLeft.

>>> prove $ \x y -> (x `sBarrelRotateLeft`  y) `sBarrelRotateRight` (y :: SWord32) .== (x :: SWord64)
Q.E.D.

sRotateRight :: (SIntegral a, SIntegral b) => SBV a -> SBV b -> SBV a Source #

Generalization of rotateR, when the shift-amount is symbolic. Since Haskell's rotateR only takes an Int as the shift amount, it cannot be used when we have a symbolic amount to shift with. The first argument should be a bounded quantity.

sBarrelRotateRight :: (SFiniteBits a, SFiniteBits b) => SBV a -> SBV b -> SBV a Source #

An implementation of rotate-right, using a barrel shifter like design. See comments for sBarrelRotateLeft for details.

>>> prove $ \x y -> (x `sBarrelRotateRight` y) `sBarrelRotateLeft`  (y :: SWord32) .== (x :: SWord64)
Q.E.D.

sSignedShiftArithRight :: (SFiniteBits a, SIntegral b) => SBV a -> SBV b -> SBV a Source #

Arithmetic shift-right with a symbolic unsigned shift amount. This is equivalent to sShiftRight when the argument is signed. However, if the argument is unsigned, then it explicitly treats its msb as a sign-bit, and uses it as the bit that gets shifted in. Useful when using the underlying unsigned bit representation to implement custom signed operations. Note that there is no direct Haskell analogue of this function.

Finite bit-vector operations

class (Ord a, SymVal a, Num a, Bits a) => SFiniteBits a where Source #

Finite bit-length symbolic values. Essentially the same as SIntegral, but further leaves out Integer. Loosely based on Haskell's FiniteBits class, but with more methods defined and structured differently to fit into the symbolic world view. Minimal complete definition: sFiniteBitSize.

Minimal complete definition

sFiniteBitSize

Methods

sFiniteBitSize :: SBV a -> Int Source #

Bit size.

lsb :: SBV a -> SBool Source #

Least significant bit of a word, always stored at index 0.

msb :: SBV a -> SBool Source #

Most significant bit of a word, always stored at the last position.

blastBE :: SBV a -> [SBool] Source #

Big-endian blasting of a word into its bits.

blastLE :: SBV a -> [SBool] Source #

Little-endian blasting of a word into its bits.

fromBitsBE :: [SBool] -> SBV a Source #

Reconstruct from given bits, given in little-endian.

fromBitsLE :: [SBool] -> SBV a Source #

Reconstruct from given bits, given in little-endian.

sTestBit :: SBV a -> Int -> SBool Source #

Replacement for testBit, returning SBool instead of Bool.

sExtractBits :: SBV a -> [Int] -> [SBool] Source #

Variant of sTestBit, where we want to extract multiple bit positions.

sPopCount :: SBV a -> SWord8 Source #

Variant of popCount, returning a symbolic value.

setBitTo :: SBV a -> Int -> SBool -> SBV a Source #

A combo of setBit and clearBit, when the bit to be set is symbolic.

fullAdder :: SBV a -> SBV a -> (SBool, SBV a) Source #

Full adder, returns carry-out from the addition. Only for unsigned quantities.

fullMultiplier :: SBV a -> SBV a -> (SBV a, SBV a) Source #

Full multipler, returns both high and low-order bits. Only for unsigned quantities.

sCountLeadingZeros :: SBV a -> SWord8 Source #

Count leading zeros in a word, big-endian interpretation.

sCountTrailingZeros :: SBV a -> SWord8 Source #

Count trailing zeros in a word, big-endian interpretation.

Instances
SFiniteBits Int8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SFiniteBits Int16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SFiniteBits Int32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SFiniteBits Int64 Source # 
Instance details

Defined in Data.SBV.Core.Model

SFiniteBits Word8 Source # 
Instance details

Defined in Data.SBV.Core.Model

SFiniteBits Word16 Source # 
Instance details

Defined in Data.SBV.Core.Model

SFiniteBits Word32 Source # 
Instance details

Defined in Data.SBV.Core.Model

SFiniteBits Word64 Source # 
Instance details

Defined in Data.SBV.Core.Model

Splitting, joining, and extending

class Splittable a b | b -> a where Source #

Splitting an a into two b's and joining back. Intuitively, a is a larger bit-size word than b, typically double. The extend operation captures embedding of a b value into an a without changing its semantic value.

Methods

split :: a -> (b, b) Source #

(#) :: b -> b -> a infixr 5 Source #

extend :: b -> a Source #

Instances
Splittable Word8 Word4 Source #

Joiningsplitting tofrom Word8

Instance details

Defined in Documentation.SBV.Examples.Misc.Word4

Splittable Word16 Word8 Source # 
Instance details

Defined in Data.SBV.Core.Splittable

Splittable Word32 Word16 Source # 
Instance details

Defined in Data.SBV.Core.Splittable

Splittable Word64 Word32 Source # 
Instance details

Defined in Data.SBV.Core.Splittable

Splittable SWord64 SWord32 Source # 
Instance details

Defined in Data.SBV.Core.Splittable

Splittable SWord32 SWord16 Source # 
Instance details

Defined in Data.SBV.Core.Splittable

Splittable SWord16 SWord8 Source # 
Instance details

Defined in Data.SBV.Core.Splittable

Exponentiation

(.^) :: (Mergeable b, Num b, SIntegral e) => b -> SBV e -> b Source #

Symbolic exponentiation using bit blasting and repeated squaring.

N.B. The exponent must be unsigned/bounded if symbolic. Signed exponents will be rejected.

IEEE-floating point numbers

class (SymVal a, RealFloat a) => IEEEFloating a where Source #

A class of floating-point (IEEE754) operations, some of which behave differently based on rounding modes. Note that unless the rounding mode is concretely RoundNearestTiesToEven, we will not concretely evaluate these, but rather pass down to the SMT solver.

Minimal complete definition

Nothing

Methods

fpAbs :: SBV a -> SBV a Source #

Compute the floating point absolute value.

fpNeg :: SBV a -> SBV a Source #

Compute the unary negation. Note that 0 - x is not equivalent to -x for floating-point, since -0 and 0 are different.

fpAdd :: SRoundingMode -> SBV a -> SBV a -> SBV a Source #

Add two floating point values, using the given rounding mode

fpSub :: SRoundingMode -> SBV a -> SBV a -> SBV a Source #

Subtract two floating point values, using the given rounding mode

fpMul :: SRoundingMode -> SBV a -> SBV a -> SBV a Source #

Multiply two floating point values, using the given rounding mode

fpDiv :: SRoundingMode -> SBV a -> SBV a -> SBV a Source #

Divide two floating point values, using the given rounding mode

fpFMA :: SRoundingMode -> SBV a -> SBV a -> SBV a -> SBV a Source #

Fused-multiply-add three floating point values, using the given rounding mode. fpFMA x y z = x*y+z but with only one rounding done for the whole operation; not two. Note that we will never concretely evaluate this function since Haskell lacks an FMA implementation.

fpSqrt :: SRoundingMode -> SBV a -> SBV a Source #

Compute the square-root of a float, using the given rounding mode

fpRem :: SBV a -> SBV a -> SBV a Source #

Compute the remainder: x - y * n, where n is the truncated integer nearest to x/y. The rounding mode is implicitly assumed to be RoundNearestTiesToEven.

fpRoundToIntegral :: SRoundingMode -> SBV a -> SBV a Source #

Round to the nearest integral value, using the given rounding mode.

fpMin :: SBV a -> SBV a -> SBV a Source #

Compute the minimum of two floats, respects infinity and NaN values

fpMax :: SBV a -> SBV a -> SBV a Source #

Compute the maximum of two floats, respects infinity and NaN values

fpIsEqualObject :: SBV a -> SBV a -> SBool Source #

Are the two given floats exactly the same. That is, NaN will compare equal to itself, +0 will not compare equal to -0 etc. This is the object level equality, as opposed to the semantic equality. (For the latter, just use .==.)

fpIsNormal :: SBV a -> SBool Source #

Is the floating-point number a normal value. (i.e., not denormalized.)

fpIsSubnormal :: SBV a -> SBool Source #

Is the floating-point number a subnormal value. (Also known as denormal.)

fpIsZero :: SBV a -> SBool Source #

Is the floating-point number 0? (Note that both +0 and -0 will satisfy this predicate.)

fpIsInfinite :: SBV a -> SBool Source #

Is the floating-point number infinity? (Note that both +oo and -oo will satisfy this predicate.)

fpIsNaN :: SBV a -> SBool Source #

Is the floating-point number a NaN value?

fpIsNegative :: SBV a -> SBool Source #

Is the floating-point number negative? Note that -0 satisfies this predicate but +0 does not.

fpIsPositive :: SBV a -> SBool Source #

Is the floating-point number positive? Note that +0 satisfies this predicate but -0 does not.

fpIsNegativeZero :: SBV a -> SBool Source #

Is the floating point number -0?

fpIsPositiveZero :: SBV a -> SBool Source #

Is the floating point number +0?

fpIsPoint :: SBV a -> SBool Source #

Is the floating-point number a regular floating point, i.e., not NaN, nor +oo, nor -oo. Normals or denormals are allowed.

Instances
IEEEFloating Double Source #

SDouble instance

Instance details

Defined in Data.SBV.Core.Floating

IEEEFloating Float Source #

SFloat instance

Instance details

Defined in Data.SBV.Core.Floating

data RoundingMode Source #

Rounding mode to be used for the IEEE floating-point operations. Note that Haskell's default is RoundNearestTiesToEven. If you use a different rounding mode, then the counter-examples you get may not match what you observe in Haskell.

Constructors

RoundNearestTiesToEven

Round to nearest representable floating point value. If precisely at half-way, pick the even number. (In this context, even means the lowest-order bit is zero.)

RoundNearestTiesToAway

Round to nearest representable floating point value. If precisely at half-way, pick the number further away from 0. (That is, for positive values, pick the greater; for negative values, pick the smaller.)

RoundTowardPositive

Round towards positive infinity. (Also known as rounding-up or ceiling.)

RoundTowardNegative

Round towards negative infinity. (Also known as rounding-down or floor.)

RoundTowardZero

Round towards zero. (Also known as truncation.)

Instances
Bounded RoundingMode Source # 
Instance details

Defined in Data.SBV.Core.Symbolic

Enum RoundingMode Source # 
Instance details

Defined in Data.SBV.Core.Symbolic

Eq RoundingMode Source # 
Instance details

Defined in Data.SBV.Core.Symbolic

Data RoundingMode Source # 
Instance details

Defined in Data.SBV.Core.Symbolic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoundingMode -> c RoundingMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RoundingMode #

toConstr :: RoundingMode -> Constr #

dataTypeOf :: RoundingMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RoundingMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RoundingMode) #

gmapT :: (forall b. Data b => b -> b) -> RoundingMode -> RoundingMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoundingMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoundingMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> RoundingMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoundingMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoundingMode -> m RoundingMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoundingMode -> m RoundingMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoundingMode -> m RoundingMode #

Ord RoundingMode Source # 
Instance details

Defined in Data.SBV.Core.Symbolic

Read RoundingMode Source # 
Instance details

Defined in Data.SBV.Core.Symbolic

Show RoundingMode Source # 
Instance details

Defined in Data.SBV.Core.Symbolic

HasKind RoundingMode Source #

RoundingMode kind

Instance details

Defined in Data.SBV.Core.Symbolic

SymVal RoundingMode Source #

RoundingMode can be used symbolically

Instance details

Defined in Data.SBV.Core.Data

SatModel RoundingMode Source #

A rounding mode, extracted from a model. (Default definition suffices)

Instance details

Defined in Data.SBV.SMT.SMT

Methods

parseCVs :: [CV] -> Maybe (RoundingMode, [CV]) Source #

cvtModel :: (RoundingMode -> Maybe b) -> Maybe (RoundingMode, [CV]) -> Maybe (b, [CV]) Source #

type SRoundingMode = SBV RoundingMode Source #

The symbolic variant of RoundingMode

nan :: Floating a => a Source #

Not-A-Number for Double and Float. Surprisingly, Haskell Prelude doesn't have this value defined, so we provide it here.

infinity :: Floating a => a Source #

Infinity for Double and Float. Surprisingly, Haskell Prelude doesn't have this value defined, so we provide it here.

sNaN :: (Floating a, SymVal a) => SBV a Source #

Symbolic variant of Not-A-Number. This value will inhabit both SDouble and SFloat.

sInfinity :: (Floating a, SymVal a) => SBV a Source #

Symbolic variant of infinity. This value will inhabit both SDouble and SFloat.

Rounding modes

Conversion to/from floats

class SymVal a => IEEEFloatConvertible a where Source #

Capture convertability from/to FloatingPoint representations.

Conversions to float: toSFloat and toSDouble simply return the nearest representable float from the given type based on the rounding mode provided.

Conversions from float: fromSFloat and fromSDouble functions do the reverse conversion. However some care is needed when given values that are not representable in the integral target domain. For instance, converting an SFloat to an SInt8 is problematic. The rules are as follows:

If the input value is a finite point and when rounded in the given rounding mode to an integral value lies within the target bounds, then that result is returned. (This is the regular interpretation of rounding in IEEE754.)

Otherwise (i.e., if the integral value in the float or double domain) doesn't fit into the target type, then the result is unspecified. Note that if the input is +oo, -oo, or NaN, then the result is unspecified.

Due to the unspecified nature of conversions, SBV will never constant fold conversions from floats to integral values. That is, you will always get a symbolic value as output. (Conversions from floats to other floats will be constant folded. Conversions from integral values to floats will also be constant folded.)

Note that unspecified really means unspecified: In particular, SBV makes no guarantees about matching the behavior between what you might get in Haskell, via SMT-Lib, or the C-translation. If the input value is out-of-bounds as defined above, or is NaN or oo or -oo, then all bets are off. In particular C and SMTLib are decidedly undefine this case, though that doesn't mean they do the same thing! Same goes for Haskell, which seems to convert via Int64, but we do not model that behavior in SBV as it doesn't seem to be intentional nor well documented.

You can check for NaN, oo and -oo, using the predicates fpIsNaN, fpIsInfinite, and fpIsPositive, fpIsNegative predicates, respectively; and do the proper conversion based on your needs. (0 is a good choice, as are min/max bounds of the target type.)

Currently, SBV provides no predicates to check if a value would lie within range for a particular conversion task, as this depends on the rounding mode and the types involved and can be rather tricky to determine. (See http://github.com/LeventErkok/sbv/issues/456 for a discussion of the issues involved.) In a future release, we hope to be able to provide underflow and overflow predicates for these conversions as well.

Minimal complete definition

Nothing

Methods

fromSFloat :: SRoundingMode -> SFloat -> SBV a Source #

Convert from an IEEE74 single precision float.

toSFloat :: SRoundingMode -> SBV a -> SFloat Source #

Convert to an IEEE-754 Single-precision float.

>>> :{
roundTrip :: forall a. (Eq a, IEEEFloatConvertible a) => SRoundingMode -> SBV a -> SBool
roundTrip m x = fromSFloat m (toSFloat m x) .== x
:}
>>> prove $ roundTrip @Int8
Q.E.D.
>>> prove $ roundTrip @Word8
Q.E.D.
>>> prove $ roundTrip @Int16
Q.E.D.
>>> prove $ roundTrip @Word16
Q.E.D.
>>> prove $ roundTrip @Int32
Falsifiable. Counter-example:
  s0 = RoundNearestTiesToEven :: RoundingMode
  s1 =            -2130176960 :: Int32

Note how we get a failure on Int32. The counter-example value is not representable exactly as a single precision float:

>>> toRational (-2130176960 :: Float)
(-2130177024) % 1

Note how the numerator is different, it is off by 64. This is hardly surprising, since floats become sparser as the magnitude increases to be able to cover all the integer values representable.

toSFloat :: Integral a => SRoundingMode -> SBV a -> SFloat Source #

Convert to an IEEE-754 Single-precision float.

>>> :{
roundTrip :: forall a. (Eq a, IEEEFloatConvertible a) => SRoundingMode -> SBV a -> SBool
roundTrip m x = fromSFloat m (toSFloat m x) .== x
:}
>>> prove $ roundTrip @Int8
Q.E.D.
>>> prove $ roundTrip @Word8
Q.E.D.
>>> prove $ roundTrip @Int16
Q.E.D.
>>> prove $ roundTrip @Word16
Q.E.D.
>>> prove $ roundTrip @Int32
Falsifiable. Counter-example:
  s0 = RoundNearestTiesToEven :: RoundingMode
  s1 =            -2130176960 :: Int32

Note how we get a failure on Int32. The counter-example value is not representable exactly as a single precision float:

>>> toRational (-2130176960 :: Float)
(-2130177024) % 1

Note how the numerator is different, it is off by 64. This is hardly surprising, since floats become sparser as the magnitude increases to be able to cover all the integer values representable.

fromSDouble :: SRoundingMode -> SDouble -> SBV a Source #

Convert from an IEEE74 double precision float.

toSDouble :: SRoundingMode -> SBV a -> SDouble Source #

Convert to an IEEE-754 Double-precision float.

>>> :{
roundTrip :: forall a. (Eq a, IEEEFloatConvertible a) => SRoundingMode -> SBV a -> SBool
roundTrip m x = fromSDouble m (toSDouble m x) .== x
:}
>>> prove $ roundTrip @Int8
Q.E.D.
>>> prove $ roundTrip @Word8
Q.E.D.
>>> prove $ roundTrip @Int16
Q.E.D.
>>> prove $ roundTrip @Word16
Q.E.D.
>>> prove $ roundTrip @Int32
Q.E.D.
>>> prove $ roundTrip @Word32
Q.E.D.
>>> prove $ roundTrip @Int64
Falsifiable. Counter-example:
  s0 = RoundNearestTiesToEven :: RoundingMode
  s1 =    4611686018427387902 :: Int64

Just like in the SFloat case, once we reach 64-bits, we no longer can exactly represent the integer value for all possible values:

>>> toRational (4611686018427387902 ::Double)
4611686018427387904 % 1

In this case the numerator is off by 2!

toSDouble :: Integral a => SRoundingMode -> SBV a -> SDouble Source #

Convert to an IEEE-754 Double-precision float.

>>> :{
roundTrip :: forall a. (Eq a, IEEEFloatConvertible a) => SRoundingMode -> SBV a -> SBool
roundTrip m x = fromSDouble m (toSDouble m x) .== x
:}
>>> prove $ roundTrip @Int8
Q.E.D.
>>> prove $ roundTrip @Word8
Q.E.D.
>>> prove $ roundTrip @Int16
Q.E.D.
>>> prove $ roundTrip @Word16
Q.E.D.
>>> prove $ roundTrip @Int32
Q.E.D.
>>> prove $ roundTrip @Word32
Q.E.D.
>>> prove $ roundTrip @Int64
Falsifiable. Counter-example:
  s0 = RoundNearestTiesToEven :: RoundingMode
  s1 =    4611686018427387902 :: Int64

Just like in the SFloat case, once we reach 64-bits, we no longer can exactly represent the integer value for all possible values:

>>> toRational (4611686018427387902 ::Double)
4611686018427387904 % 1

In this case the numerator is off by 2!

Instances
IEEEFloatConvertible Double Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Float Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Int8 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Int16 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Int32 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Int64 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Integer Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Word8 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Word16 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Word32 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible Word64 Source # 
Instance details

Defined in Data.SBV.Core.Floating

IEEEFloatConvertible AlgReal Source # 
Instance details

Defined in Data.SBV.Core.Floating

Bit-pattern conversions

sFloatAsSWord32 :: SFloat -> SWord32 Source #

Convert an SFloat to an SWord32, preserving the bit-correspondence. Note that since the representation for NaNs are not unique, this function will return a symbolic value when given a concrete NaN.

Implementation note: Since there's no corresponding function in SMTLib for conversion to bit-representation due to partiality, we use a translation trick by allocating a new word variable, converting it to float, and requiring it to be equivalent to the input. In code-generation mode, we simply map it to a simple conversion.

sWord32AsSFloat :: SWord32 -> SFloat Source #

Reinterpret the bits in a 32-bit word as a single-precision floating point number

sDoubleAsSWord64 :: SDouble -> SWord64 Source #

Convert an SDouble to an SWord64, preserving the bit-correspondence. Note that since the representation for NaNs are not unique, this function will return a symbolic value when given a concrete NaN.

See the implementation note for sFloatAsSWord32, as it applies here as well.

sWord64AsSDouble :: SWord64 -> SDouble Source #

Reinterpret the bits in a 32-bit word as a single-precision floating point number

blastSFloat :: SFloat -> (SBool, [SBool], [SBool]) Source #

Extract the sign/exponent/mantissa of a single-precision float. The output will have 8 bits in the second argument for exponent, and 23 in the third for the mantissa.

blastSDouble :: SDouble -> (SBool, [SBool], [SBool]) Source #

Extract the sign/exponent/mantissa of a single-precision float. The output will have 11 bits in the second argument for exponent, and 52 in the third for the mantissa.

Enumerations

mkSymbolicEnumeration :: Name -> Q [Dec] Source #

Make an enumeration a symbolic type.

Uninterpreted sorts, constants, and functions

class Uninterpreted a where Source #

Uninterpreted constants and functions. An uninterpreted constant is a value that is indexed by its name. The only property the prover assumes about these values are that they are equivalent to themselves; i.e., (for functions) they return the same results when applied to same arguments. We support uninterpreted-functions as a general means of black-box'ing operations that are irrelevant for the purposes of the proof; i.e., when the proofs can be performed without any knowledge about the function itself.

Minimal complete definition: sbvUninterpret. However, most instances in practice are already provided by SBV, so end-users should not need to define their own instances.

Minimal complete definition

sbvUninterpret

Methods

uninterpret :: String -> a Source #

Uninterpret a value, receiving an object that can be used instead. Use this version when you do not need to add an axiom about this value.

cgUninterpret :: String -> [String] -> a -> a Source #

Uninterpret a value, only for the purposes of code-generation. For execution and verification the value is used as is. For code-generation, the alternate definition is used. This is useful when we want to take advantage of native libraries on the target languages.

sbvUninterpret :: Maybe ([String], a) -> String -> a Source #

Most generalized form of uninterpretation, this function should not be needed by end-user-code, but is rather useful for the library development.

Instances
HasKind a => Uninterpreted (SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

(SymVal c, SymVal b, HasKind a) => Uninterpreted ((SBV c, SBV b) -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> (SBV c, SBV b) -> SBV a Source #

cgUninterpret :: String -> [String] -> ((SBV c, SBV b) -> SBV a) -> (SBV c, SBV b) -> SBV a Source #

sbvUninterpret :: Maybe ([String], (SBV c, SBV b) -> SBV a) -> String -> (SBV c, SBV b) -> SBV a Source #

(SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted ((SBV d, SBV c, SBV b) -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> (SBV d, SBV c, SBV b) -> SBV a Source #

cgUninterpret :: String -> [String] -> ((SBV d, SBV c, SBV b) -> SBV a) -> (SBV d, SBV c, SBV b) -> SBV a Source #

sbvUninterpret :: Maybe ([String], (SBV d, SBV c, SBV b) -> SBV a) -> String -> (SBV d, SBV c, SBV b) -> SBV a Source #

(SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted ((SBV e, SBV d, SBV c, SBV b) -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> (SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

cgUninterpret :: String -> [String] -> ((SBV e, SBV d, SBV c, SBV b) -> SBV a) -> (SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

sbvUninterpret :: Maybe ([String], (SBV e, SBV d, SBV c, SBV b) -> SBV a) -> String -> (SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

(SymVal f, SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted ((SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> (SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

cgUninterpret :: String -> [String] -> ((SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) -> (SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

sbvUninterpret :: Maybe ([String], (SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) -> String -> (SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

(SymVal g, SymVal f, SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted ((SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> (SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

cgUninterpret :: String -> [String] -> ((SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) -> (SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

sbvUninterpret :: Maybe ([String], (SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) -> String -> (SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

(SymVal h, SymVal g, SymVal f, SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted ((SBV h, SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> (SBV h, SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

cgUninterpret :: String -> [String] -> ((SBV h, SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) -> (SBV h, SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

sbvUninterpret :: Maybe ([String], (SBV h, SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a) -> String -> (SBV h, SBV g, SBV f, SBV e, SBV d, SBV c, SBV b) -> SBV a Source #

(SymVal h, SymVal g, SymVal f, SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted (SBV h -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> SBV h -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

cgUninterpret :: String -> [String] -> (SBV h -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> SBV h -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

sbvUninterpret :: Maybe ([String], SBV h -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> String -> SBV h -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

(SymVal g, SymVal f, SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted (SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

cgUninterpret :: String -> [String] -> (SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

sbvUninterpret :: Maybe ([String], SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> String -> SBV g -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

(SymVal f, SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted (SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

cgUninterpret :: String -> [String] -> (SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

sbvUninterpret :: Maybe ([String], SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> String -> SBV f -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

(SymVal e, SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted (SBV e -> SBV d -> SBV c -> SBV b -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

cgUninterpret :: String -> [String] -> (SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

sbvUninterpret :: Maybe ([String], SBV e -> SBV d -> SBV c -> SBV b -> SBV a) -> String -> SBV e -> SBV d -> SBV c -> SBV b -> SBV a Source #

(SymVal d, SymVal c, SymVal b, HasKind a) => Uninterpreted (SBV d -> SBV c -> SBV b -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> SBV d -> SBV c -> SBV b -> SBV a Source #

cgUninterpret :: String -> [String] -> (SBV d -> SBV c -> SBV b -> SBV a) -> SBV d -> SBV c -> SBV b -> SBV a Source #

sbvUninterpret :: Maybe ([String], SBV d -> SBV c -> SBV b -> SBV a) -> String -> SBV d -> SBV c -> SBV b -> SBV a Source #

(SymVal c, SymVal b, HasKind a) => Uninterpreted (SBV c -> SBV b -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> SBV c -> SBV b -> SBV a Source #

cgUninterpret :: String -> [String] -> (SBV c -> SBV b -> SBV a) -> SBV c -> SBV b -> SBV a Source #

sbvUninterpret :: Maybe ([String], SBV c -> SBV b -> SBV a) -> String -> SBV c -> SBV b -> SBV a Source #

(SymVal b, HasKind a) => Uninterpreted (SBV b -> SBV a) Source # 
Instance details

Defined in Data.SBV.Core.Model

Methods

uninterpret :: String -> SBV b -> SBV a Source #

cgUninterpret :: String -> [String] -> (SBV b -> SBV a) -> SBV b -> SBV a Source #

sbvUninterpret :: Maybe ([String], SBV b -> SBV a) -> String -> SBV b -> SBV a Source #

addAxiom :: MonadSymbolic m => String -> [String] -> m () Source #

Generalization of addAxiom

Properties, proofs, and satisfiability

type Predicate = Symbolic SBool Source #

A predicate is a symbolic program that returns a (symbolic) boolean value. For all intents and purposes, it can be treated as an n-ary function from symbolic-values to a boolean. The Symbolic monad captures the underlying representation, and can/should be ignored by the users of the library, unless you are building further utilities on top of SBV itself. Instead, simply use the Predicate type when necessary.

type Goal = Symbolic () Source #

A goal is a symbolic program that returns no values. The idea is that the constraints/min-max goals will serve as appropriate directives for sat/prove calls.

class ExtractIO m => MProvable m a where Source #

A type a is provable if we can turn it into a predicate. Note that a predicate can be made from a curried function of arbitrary arity, where each element is either a symbolic type or up-to a 7-tuple of symbolic-types. So predicates can be constructed from almost arbitrary Haskell functions that have arbitrary shapes. (See the instance declarations below.)

Minimal complete definition

forAll_, forAll, forSome_, forSome

Methods

forAll_ :: a -> SymbolicT m SBool Source #

Generalization of forAll_

forAll :: [String] -> a -> SymbolicT m SBool Source #

Generalization of forAll

forSome_ :: a -> SymbolicT m SBool Source #

Generalization of forSome_

forSome :: [String] -> a -> SymbolicT m SBool Source #

Generalization of forSome

prove :: a -> m ThmResult Source #

Generalization of prove

proveWith :: SMTConfig -> a -> m ThmResult Source #

Generalization of proveWith

sat :: a -> m SatResult Source #

Generalization of sat

satWith :: SMTConfig -> a -> m SatResult Source #

Generalization of satWith

allSat :: a -> m AllSatResult Source #

Generalization of allSat

allSatWith :: SMTConfig -> a -> m AllSatResult Source #

Generalization of allSatWith

optimize :: OptimizeStyle -> a -> m OptimizeResult Source #

Generalization of optimize

optimizeWith :: SMTConfig -> OptimizeStyle -> a -> m OptimizeResult Source #

Generalization of optimizeWith

isVacuous :: a -> m Bool Source #

Generalization of isVacuous

isVacuousWith :: SMTConfig -> a -> m Bool Source #

Generalization of isVacuousWith

isTheorem :: a -> m Bool Source #

Generalization of isTheorem

isTheoremWith :: SMTConfig -> a -> m Bool Source #

Generalization of isTheoremWith

isSatisfiable :: a -> m Bool Source #

Generalization of isSatisfiable

isSatisfiableWith :: SMTConfig -> a -> m Bool Source #

Generalization of isSatisfiableWith

validate :: Bool -> SMTConfig -> a -> SMTResult -> m SMTResult Source #

Validate a model obtained from the solver

Instances
ExtractIO m => MProvable m SBool Source # 
Instance details

Defined in Data.SBV.Provers.Prover

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, SymVal g, MProvable m p) => MProvable m ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> SymbolicT m SBool Source #

forSome_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> SymbolicT m SBool Source #

prove :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m ThmResult Source #

sat :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m SatResult Source #

satWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m SatResult Source #

allSat :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m OptimizeResult Source #

isVacuous :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m Bool Source #

isTheorem :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m Bool Source #

isSatisfiable :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> SMTResult -> m SMTResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, MProvable m p) => MProvable m ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> SymbolicT m SBool Source #

forSome_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> SymbolicT m SBool Source #

prove :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m ThmResult Source #

sat :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m SatResult Source #

satWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m SatResult Source #

allSat :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m OptimizeResult Source #

isVacuous :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m Bool Source #

isTheorem :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m Bool Source #

isSatisfiable :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> SMTResult -> m SMTResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, MProvable m p) => MProvable m ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> SymbolicT m SBool Source #

forSome_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> SymbolicT m SBool Source #

prove :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m ThmResult Source #

sat :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m SatResult Source #

satWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m SatResult Source #

allSat :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m OptimizeResult Source #

isVacuous :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m Bool Source #

isTheorem :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m Bool Source #

isSatisfiable :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> SMTResult -> m SMTResult Source #

(SymVal a, SymVal b, SymVal c, SymVal d, MProvable m p) => MProvable m ((SBV a, SBV b, SBV c, SBV d) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> SymbolicT m SBool Source #

forSome_ :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> SymbolicT m SBool Source #

prove :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m ThmResult Source #

sat :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> m SatResult Source #

satWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m SatResult Source #

allSat :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m OptimizeResult Source #

isVacuous :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m Bool Source #

isTheorem :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m Bool Source #

isSatisfiable :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> SMTResult -> m SMTResult Source #

(SymVal a, SymVal b, SymVal c, MProvable m p) => MProvable m ((SBV a, SBV b, SBV c) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: ((SBV a, SBV b, SBV c) -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> ((SBV a, SBV b, SBV c) -> p) -> SymbolicT m SBool Source #

forSome_ :: ((SBV a, SBV b, SBV c) -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> ((SBV a, SBV b, SBV c) -> p) -> SymbolicT m SBool Source #

prove :: ((SBV a, SBV b, SBV c) -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> m ThmResult Source #

sat :: ((SBV a, SBV b, SBV c) -> p) -> m SatResult Source #

satWith :: SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> m SatResult Source #

allSat :: ((SBV a, SBV b, SBV c) -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> ((SBV a, SBV b, SBV c) -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> ((SBV a, SBV b, SBV c) -> p) -> m OptimizeResult Source #

isVacuous :: ((SBV a, SBV b, SBV c) -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> m Bool Source #

isTheorem :: ((SBV a, SBV b, SBV c) -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> m Bool Source #

isSatisfiable :: ((SBV a, SBV b, SBV c) -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> SMTResult -> m SMTResult Source #

(SymVal a, SymVal b, MProvable m p) => MProvable m ((SBV a, SBV b) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: ((SBV a, SBV b) -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> ((SBV a, SBV b) -> p) -> SymbolicT m SBool Source #

forSome_ :: ((SBV a, SBV b) -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> ((SBV a, SBV b) -> p) -> SymbolicT m SBool Source #

prove :: ((SBV a, SBV b) -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> ((SBV a, SBV b) -> p) -> m ThmResult Source #

sat :: ((SBV a, SBV b) -> p) -> m SatResult Source #

satWith :: SMTConfig -> ((SBV a, SBV b) -> p) -> m SatResult Source #

allSat :: ((SBV a, SBV b) -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> ((SBV a, SBV b) -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> ((SBV a, SBV b) -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> ((SBV a, SBV b) -> p) -> m OptimizeResult Source #

isVacuous :: ((SBV a, SBV b) -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> ((SBV a, SBV b) -> p) -> m Bool Source #

isTheorem :: ((SBV a, SBV b) -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> ((SBV a, SBV b) -> p) -> m Bool Source #

isSatisfiable :: ((SBV a, SBV b) -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> ((SBV a, SBV b) -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> ((SBV a, SBV b) -> p) -> SMTResult -> m SMTResult Source #

(HasKind a, HasKind b, MProvable m p) => MProvable m (SFunArray a b -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

(HasKind a, HasKind b, MProvable m p) => MProvable m (SArray a b -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: (SArray a b -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> (SArray a b -> p) -> SymbolicT m SBool Source #

forSome_ :: (SArray a b -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> (SArray a b -> p) -> SymbolicT m SBool Source #

prove :: (SArray a b -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> (SArray a b -> p) -> m ThmResult Source #

sat :: (SArray a b -> p) -> m SatResult Source #

satWith :: SMTConfig -> (SArray a b -> p) -> m SatResult Source #

allSat :: (SArray a b -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> (SArray a b -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> (SArray a b -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> (SArray a b -> p) -> m OptimizeResult Source #

isVacuous :: (SArray a b -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> (SArray a b -> p) -> m Bool Source #

isTheorem :: (SArray a b -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> (SArray a b -> p) -> m Bool Source #

isSatisfiable :: (SArray a b -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> (SArray a b -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> (SArray a b -> p) -> SMTResult -> m SMTResult Source #

(SymVal a, MProvable m p) => MProvable m (SBV a -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

forAll_ :: (SBV a -> p) -> SymbolicT m SBool Source #

forAll :: [String] -> (SBV a -> p) -> SymbolicT m SBool Source #

forSome_ :: (SBV a -> p) -> SymbolicT m SBool Source #

forSome :: [String] -> (SBV a -> p) -> SymbolicT m SBool Source #

prove :: (SBV a -> p) -> m ThmResult Source #

proveWith :: SMTConfig -> (SBV a -> p) -> m ThmResult Source #

sat :: (SBV a -> p) -> m SatResult Source #

satWith :: SMTConfig -> (SBV a -> p) -> m SatResult Source #

allSat :: (SBV a -> p) -> m AllSatResult Source #

allSatWith :: SMTConfig -> (SBV a -> p) -> m AllSatResult Source #

optimize :: OptimizeStyle -> (SBV a -> p) -> m OptimizeResult Source #

optimizeWith :: SMTConfig -> OptimizeStyle -> (SBV a -> p) -> m OptimizeResult Source #

isVacuous :: (SBV a -> p) -> m Bool Source #

isVacuousWith :: SMTConfig -> (SBV a -> p) -> m Bool Source #

isTheorem :: (SBV a -> p) -> m Bool Source #

isTheoremWith :: SMTConfig -> (SBV a -> p) -> m Bool Source #

isSatisfiable :: (SBV a -> p) -> m Bool Source #

isSatisfiableWith :: SMTConfig -> (SBV a -> p) -> m Bool Source #

validate :: Bool -> SMTConfig -> (SBV a -> p) -> SMTResult -> m SMTResult Source #

ExtractIO m => MProvable m (SymbolicT m SBool) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

ExtractIO m => MProvable m (SymbolicT m ()) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

type Provable = MProvable IO Source #

Provable is specialization of MProvable to the IO monad. Unless you are using transformers explicitly, this is the type you should prefer.

proveWithAll :: Provable a => [SMTConfig] -> a -> IO [(Solver, NominalDiffTime, ThmResult)] Source #

Prove a property with multiple solvers, running them in separate threads. The results will be returned in the order produced.

proveWithAny :: Provable a => [SMTConfig] -> a -> IO (Solver, NominalDiffTime, ThmResult) Source #

Prove a property with multiple solvers, running them in separate threads. Only the result of the first one to finish will be returned, remaining threads will be killed. Note that we send a ThreadKilled to the losing processes, but we do *not* actually wait for them to finish. In rare cases this can lead to zombie processes. In previous experiments, we found that some processes take their time to terminate. So, this solution favors quick turnaround.

satWithAll :: Provable a => [SMTConfig] -> a -> IO [(Solver, NominalDiffTime, SatResult)] Source #

Find a satisfying assignment to a property with multiple solvers, running them in separate threads. The results will be returned in the order produced.

satWithAny :: Provable a => [SMTConfig] -> a -> IO (Solver, NominalDiffTime, SatResult) Source #

Find a satisfying assignment to a property with multiple solvers, running them in separate threads. Only the result of the first one to finish will be returned, remaining threads will be killed. Note that we send a ThreadKilled to the losing processes, but we do *not* actually wait for them to finish. In rare cases this can lead to zombie processes. In previous experiments, we found that some processes take their time to terminate. So, this solution favors quick turnaround.

generateSMTBenchmark :: (MonadIO m, MProvable m a) => Bool -> a -> m String Source #

Create an SMT-Lib2 benchmark. The Bool argument controls whether this is a SAT instance, i.e., translate the query directly, or a PROVE instance, i.e., translate the negated query.

solve :: MonadSymbolic m => [SBool] -> m SBool Source #

Generalization of solve

Constraints

General constraints

constrain :: SolverContext m => SBool -> m () Source #

Add a constraint, any satisfying instance must satisfy this condition.

softConstrain :: SolverContext m => SBool -> m () Source #

Add a soft constraint. The solver will try to satisfy this condition if possible, but won't if it cannot.

Constraint Vacuity

Named constraints and attributes

namedConstraint :: SolverContext m => String -> SBool -> m () Source #

Add a named constraint. The name is used in unsat-core extraction.

constrainWithAttribute :: SolverContext m => [(String, String)] -> SBool -> m () Source #

Add a constraint, with arbitrary attributes. Used in interpolant generation.

Unsat cores

Cardinality constraints

pbAtMost :: [SBool] -> Int -> SBool Source #

sTrue if at most k of the input arguments are sTrue

pbAtLeast :: [SBool] -> Int -> SBool Source #

sTrue if at least k of the input arguments are sTrue

pbExactly :: [SBool] -> Int -> SBool Source #

sTrue if exactly k of the input arguments are sTrue

pbLe :: [(Int, SBool)] -> Int -> SBool Source #

sTrue if the sum of coefficients for sTrue elements is at most k. Generalizes pbAtMost.

pbGe :: [(Int, SBool)] -> Int -> SBool Source #

sTrue if the sum of coefficients for sTrue elements is at least k. Generalizes pbAtLeast.

pbEq :: [(Int, SBool)] -> Int -> SBool Source #

sTrue if the sum of coefficients for sTrue elements is exactly least k. Useful for coding exactly K-of-N constraints, and in particular mutex constraints.

pbMutexed :: [SBool] -> SBool Source #

sTrue if there is at most one set bit

pbStronglyMutexed :: [SBool] -> SBool Source #

sTrue if there is exactly one set bit

Checking safety

sAssert :: HasKind a => Maybe CallStack -> String -> SBool -> SBV a -> SBV a Source #

Symbolic assert. Check that the given boolean condition is always sTrue in the given path. The optional first argument can be used to provide call-stack info via GHC's location facilities.

isSafe :: SafeResult -> Bool Source #

Check if a safe-call was safe or not, turning a SafeResult to a Bool.

class ExtractIO m => SExecutable m a where Source #

Symbolically executable program fragments. This class is mainly used for safe calls, and is sufficently populated internally to cover most use cases. Users can extend it as they wish to allow safe checks for SBV programs that return/take types that are user-defined.

Minimal complete definition

sName_, sName

Methods

sName_ :: a -> SymbolicT m () Source #

Generalization of sName_

sName :: [String] -> a -> SymbolicT m () Source #

Generalization of sName

safe :: a -> m [SafeResult] Source #

Generalization of safe

safeWith :: SMTConfig -> a -> m [SafeResult] Source #

Generalization of safeWith

Instances
ExtractIO m => SExecutable m () Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: () -> SymbolicT m () Source #

sName :: [String] -> () -> SymbolicT m () Source #

safe :: () -> m [SafeResult] Source #

safeWith :: SMTConfig -> () -> m [SafeResult] Source #

ExtractIO m => SExecutable m [SBV a] Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: [SBV a] -> SymbolicT m () Source #

sName :: [String] -> [SBV a] -> SymbolicT m () Source #

safe :: [SBV a] -> m [SafeResult] Source #

safeWith :: SMTConfig -> [SBV a] -> m [SafeResult] Source #

ExtractIO m => SExecutable m (SBV a) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: SBV a -> SymbolicT m () Source #

sName :: [String] -> SBV a -> SymbolicT m () Source #

safe :: SBV a -> m [SafeResult] Source #

safeWith :: SMTConfig -> SBV a -> m [SafeResult] Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, SymVal g, SExecutable m p) => SExecutable m ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> SymbolicT m () Source #

sName :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> SymbolicT m () Source #

safe :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m [SafeResult] Source #

safeWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> m [SafeResult] Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SymVal f, SExecutable m p) => SExecutable m ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> SymbolicT m () Source #

sName :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> SymbolicT m () Source #

safe :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m [SafeResult] Source #

safeWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> m [SafeResult] Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SymVal e, SExecutable m p) => SExecutable m ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> SymbolicT m () Source #

sName :: [String] -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> SymbolicT m () Source #

safe :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m [SafeResult] Source #

safeWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> m [SafeResult] Source #

(SymVal a, SymVal b, SymVal c, SymVal d, SExecutable m p) => SExecutable m ((SBV a, SBV b, SBV c, SBV d) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> SymbolicT m () Source #

sName :: [String] -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> SymbolicT m () Source #

safe :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> m [SafeResult] Source #

safeWith :: SMTConfig -> ((SBV a, SBV b, SBV c, SBV d) -> p) -> m [SafeResult] Source #

(SymVal a, SymVal b, SymVal c, SExecutable m p) => SExecutable m ((SBV a, SBV b, SBV c) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: ((SBV a, SBV b, SBV c) -> p) -> SymbolicT m () Source #

sName :: [String] -> ((SBV a, SBV b, SBV c) -> p) -> SymbolicT m () Source #

safe :: ((SBV a, SBV b, SBV c) -> p) -> m [SafeResult] Source #

safeWith :: SMTConfig -> ((SBV a, SBV b, SBV c) -> p) -> m [SafeResult] Source #

(SymVal a, SymVal b, SExecutable m p) => SExecutable m ((SBV a, SBV b) -> p) Source # 
Instance details

Defined in Data.SBV.Provers.Prover

Methods

sName_ :: ((SBV a, SBV b) -> p) ->