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

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

Data.SBV.Internals

Contents

Description

Low level functions to access the SBV infrastructure, for developers who want to build further tools on top of SBV. End-users of the library should not need to use this module.

Synopsis

Running symbolic programs manually

data Result Source #

Result of running a symbolic computation

Constructors

Result 

Fields

Instances

Show Result Source #

Show instance for Result. Only for debugging purposes.

NFData Result Source # 

Methods

rnf :: Result -> () #

data SBVRunMode Source #

Different means of running a symbolic piece of code

Constructors

Proof (Bool, SMTConfig)

Fully Symbolic, proof mode.

CodeGen

Code generation mode.

Concrete StdGen

Concrete simulation mode. The StdGen is for the pConstrain acceptance in cross runs.

data Symbolic a Source #

A Symbolic computation. Represented by a reader monad carrying the state of the computation, layered on top of IO for creating unique references to hold onto intermediate results.

runSymbolic :: (Bool, SMTConfig) -> Symbolic a -> IO Result Source #

Run a symbolic computation in Proof mode and return a Result. The boolean argument indicates if this is a sat instance or not.

runSymbolic' :: SBVRunMode -> Symbolic a -> IO (a, Result) Source #

Run a symbolic computation, and return a extra value paired up with the Result

Other internal structures useful for low-level programming

newtype SBV a Source #

The Symbolic value. The parameter a is phantom, but is extremely important in keeping the user interface strongly typed.

Constructors

SBV 

Fields

Instances

Provable SBool Source # 
Provable Predicate Source # 
SDivisible SInteger Source # 
SDivisible SInt64 Source # 
SDivisible SInt32 Source # 
SDivisible SInt16 Source # 
SDivisible SInt8 Source # 
SDivisible SWord64 Source # 
SDivisible SWord32 Source # 
SDivisible SWord16 Source # 
SDivisible SWord8 Source # 
SDivisible SWord4 Source #

SDvisible instance, using default methods

FromBits SInt64 Source # 
FromBits SInt32 Source # 
FromBits SInt16 Source # 
FromBits SInt8 Source # 
FromBits SWord64 Source # 
FromBits SWord32 Source # 
FromBits SWord16 Source # 
FromBits SWord8 Source # 
FromBits SBool Source # 
FromBits SWord4 Source #

Conversion from bits

Polynomial SWord64 Source # 
Polynomial SWord32 Source # 
Polynomial SWord16 Source # 
Polynomial SWord8 Source # 
Splittable SWord64 SWord32 Source # 
Splittable SWord32 SWord16 Source # 
Splittable SWord16 SWord8 Source # 
Eq (SBV a) Source # 

Methods

(==) :: SBV a -> SBV a -> Bool #

(/=) :: SBV a -> SBV a -> Bool #

Show (SBV a) Source # 

Methods

showsPrec :: Int -> SBV a -> ShowS #

show :: SBV a -> String #

showList :: [SBV a] -> ShowS #

NFData (SBV a) Source # 

Methods

rnf :: SBV a -> () #

(Random a, SymWord a) => Random (SBV a) Source # 

Methods

randomR :: RandomGen g => (SBV a, SBV a) -> g -> (SBV a, g)

random :: RandomGen g => g -> (SBV a, g)

randomRs :: RandomGen g => (SBV a, SBV a) -> g -> [SBV a]

randoms :: RandomGen g => g -> [SBV a]

randomRIO :: (SBV a, SBV a) -> IO (SBV a)

randomIO :: IO (SBV a)

HasKind (SBV a) Source # 
SExecutable [SBV a] Source # 

Methods

sName_ :: [SBV a] -> Symbolic () Source #

sName :: [String] -> [SBV a] -> Symbolic () Source #

SExecutable (SBV a) Source # 

Methods

sName_ :: SBV a -> Symbolic () Source #

sName :: [String] -> SBV a -> Symbolic () Source #

(SymWord a, PrettyNum a) => PrettyNum (SBV a) Source # 

Methods

hexS :: SBV a -> String Source #

binS :: SBV a -> String Source #

hex :: SBV a -> String Source #

bin :: SBV a -> String Source #

HasKind a => Uninterpreted (SBV a) Source # 
SymWord a => Mergeable (SBV a) Source # 

Methods

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

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

SymWord a => OrdSymbolic (SBV a) Source # 

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 #

EqSymbolic (SBV a) Source # 

Methods

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

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

(SymWord a, SymWord b, SExecutable p) => SExecutable ((SBV a, SBV b) -> p) Source # 

Methods

sName_ :: ((SBV a, SBV b) -> p) -> Symbolic () Source #

sName :: [String] -> ((SBV a, SBV b) -> p) -> Symbolic () Source #

(SymWord a, SymWord b, SymWord c, SExecutable p) => SExecutable ((SBV a, SBV b, SBV c) -> p) Source # 

Methods

sName_ :: ((SBV a, SBV b, SBV c) -> p) -> Symbolic () Source #

sName :: [String] -> ((SBV a, SBV b, SBV c) -> p) -> Symbolic () Source #

(SymWord a, SymWord b, SymWord c, SymWord d, SExecutable p) => SExecutable ((SBV a, SBV b, SBV c, SBV d) -> p) Source # 

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> Symbolic () Source #

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

(SymWord a, SymWord b, SymWord c, SymWord d, SymWord e, SExecutable p) => SExecutable ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) Source # 

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) -> Symbolic () Source #

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

(SymWord a, SymWord b, SymWord c, SymWord d, SymWord e, SymWord f, SExecutable p) => SExecutable ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) Source # 

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) -> Symbolic () Source #

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

(SymWord a, SymWord b, SymWord c, SymWord d, SymWord e, SymWord f, SymWord g, SExecutable p) => SExecutable ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) Source # 

Methods

sName_ :: ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) -> Symbolic () Source #

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

(SymWord a, SExecutable p) => SExecutable (SBV a -> p) Source # 

Methods

sName_ :: (SBV a -> p) -> Symbolic () Source #

sName :: [String] -> (SBV a -> p) -> Symbolic () Source #

(NFData a, SymWord a, NFData b, SymWord b) => SExecutable (SBV a, SBV b) Source # 

Methods

sName_ :: (SBV a, SBV b) -> Symbolic () Source #

sName :: [String] -> (SBV a, SBV b) -> Symbolic () Source #

(SymWord a, SymWord b, Provable p) => Provable ((SBV a, SBV b) -> p) Source # 

Methods

forAll_ :: ((SBV a, SBV b) -> p) -> Predicate Source #

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

forSome_ :: ((SBV a, SBV b) -> p) -> Predicate Source #

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

(SymWord a, SymWord b, SymWord c, Provable p) => Provable ((SBV a, SBV b, SBV c) -> p) Source # 

Methods

forAll_ :: ((SBV a, SBV b, SBV c) -> p) -> Predicate Source #

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

forSome_ :: ((SBV a, SBV b, SBV c) -> p) -> Predicate Source #

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

(SymWord a, SymWord b, SymWord c, SymWord d, Provable p) => Provable ((SBV a, SBV b, SBV c, SBV d) -> p) Source # 

Methods

forAll_ :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> Predicate Source #

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

forSome_ :: ((SBV a, SBV b, SBV c, SBV d) -> p) -> Predicate Source #

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

(SymWord a, SymWord b, SymWord c, SymWord d, SymWord e, Provable p) => Provable ((SBV a, SBV b, SBV c, SBV d, SBV e) -> p) Source # 

Methods

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

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

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

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

(SymWord a, SymWord b, SymWord c, SymWord d, SymWord e, SymWord f, Provable p) => Provable ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> p) Source # 

Methods

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

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

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

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

(SymWord a, SymWord b, SymWord c, SymWord d, SymWord e, SymWord f, SymWord g, Provable p) => Provable ((SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) -> p) Source # 

Methods

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

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

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

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

(SymWord a, Provable p) => Provable (SBV a -> p) Source # 

Methods

forAll_ :: (SBV a -> p) -> Predicate Source #

forAll :: [String] -> (SBV a -> p) -> Predicate Source #

forSome_ :: (SBV a -> p) -> Predicate Source #

forSome :: [String] -> (SBV a -> p) -> Predicate Source #

(SymWord c, SymWord b, HasKind a) => Uninterpreted ((SBV c, SBV b) -> SBV a) Source # 

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 #

(SymWord d, SymWord c, SymWord b, HasKind a) => Uninterpreted ((SBV d, SBV c, SBV b) -> SBV a) Source # 

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

(SymWord d, SymWord c, SymWord b, HasKind a) => Uninterpreted (SBV d -> SBV c -> SBV b -> SBV a) Source # 

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 #

(SymWord c, SymWord b, HasKind a) => Uninterpreted (SBV c -> SBV b -> SBV a) Source # 

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 #

(SymWord b, HasKind a) => Uninterpreted (SBV b -> SBV a) Source # 

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 #

(SymWord e, Mergeable (SBV e)) => Mergeable (STree i e) Source # 

Methods

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

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

(SymWord a, SymWord b, EqSymbolic z) => Equality ((SBV a, SBV b) -> z) Source # 

Methods

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

(SymWord a, SymWord b, SymWord c, EqSymbolic z) => Equality ((SBV a, SBV b, SBV c) -> z) Source # 

Methods

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

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

Methods

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

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

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 #

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

Methods

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

(SymWord a, SymWord b, SymWord c, EqSymbolic z) => Equality (SBV a -> SBV b -> SBV c -> z) Source # 

Methods

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

(SymWord a, SymWord b, EqSymbolic z) => Equality (SBV a -> SBV b -> z) Source # 

Methods

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

(SymWord a, EqSymbolic z) => Equality (SBV a -> z) Source # 

Methods

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

(NFData a, SymWord a, NFData b, SymWord b, NFData c, SymWord c) => SExecutable (SBV a, SBV b, SBV c) Source # 

Methods

sName_ :: (SBV a, SBV b, SBV c) -> Symbolic () Source #

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

(NFData a, SymWord a, NFData b, SymWord b, NFData c, SymWord c, NFData d, SymWord d) => SExecutable (SBV a, SBV b, SBV c, SBV d) Source # 

Methods

sName_ :: (SBV a, SBV b, SBV c, SBV d) -> Symbolic () Source #

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

(NFData a, SymWord a, NFData b, SymWord b, NFData c, SymWord c, NFData d, SymWord d, NFData e, SymWord e) => SExecutable (SBV a, SBV b, SBV c, SBV d, SBV e) Source # 

Methods

sName_ :: (SBV a, SBV b, SBV c, SBV d, SBV e) -> Symbolic () Source #

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

(NFData a, SymWord a, NFData b, SymWord b, NFData c, SymWord c, NFData d, SymWord d, NFData e, SymWord e, NFData f, SymWord f) => SExecutable (SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) Source # 

Methods

sName_ :: (SBV a, SBV b, SBV c, SBV d, SBV e, SBV f) -> Symbolic () Source #

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

(NFData a, SymWord a, NFData b, SymWord b, NFData c, SymWord c, NFData d, SymWord d, NFData e, SymWord e, NFData f, SymWord f, NFData g, SymWord g) => SExecutable (SBV a, SBV b, SBV c, SBV d, SBV e, SBV f, SBV g) Source # 

Methods

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

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

slet :: forall a b. (HasKind a, HasKind b) => SBV a -> (SBV a -> SBV b) -> SBV b Source #

Explicit sharing combinator. The SBV library has internal caching/hash-consing mechanisms built in, based on Andy Gill's type-safe obervable sharing technique (see: http://ittc.ku.edu/~andygill/paper.php?label=DSLExtract09). However, there might be times where being explicit on the sharing can help, especially in experimental code. The slet combinator ensures that its first argument is computed once and passed on to its continuation, explicitly indicating the intent of sharing. Most use cases of the SBV library should simply use Haskell's let construct for this purpose.

data CW Source #

CW represents a concrete word of a fixed size: Endianness is mostly irrelevant (see the FromBits class). For signed words, the most significant digit is considered to be the sign.

Constructors

CW 

Fields

Instances

Eq CW Source # 

Methods

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

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

Ord CW Source # 

Methods

compare :: CW -> CW -> Ordering #

(<) :: CW -> CW -> Bool #

(<=) :: CW -> CW -> Bool #

(>) :: CW -> CW -> Bool #

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

max :: CW -> CW -> CW #

min :: CW -> CW -> CW #

Show CW Source #

Show instance for CW.

Methods

showsPrec :: Int -> CW -> ShowS #

show :: CW -> String #

showList :: [CW] -> ShowS #

HasKind CW Source #

Kind instance for CW

PrettyNum CW Source # 
SatModel CW Source #

CW as extracted from a model; trivial definition

Methods

parseCWs :: [CW] -> Maybe (CW, [CW]) Source #

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

SDivisible CW Source # 

Methods

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

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

sQuot :: CW -> CW -> CW Source #

sRem :: CW -> CW -> CW Source #

sDiv :: CW -> CW -> CW Source #

sMod :: CW -> CW -> CW Source #

data Kind Source #

Kind of symbolic value

Instances

Eq Kind Source #

We want to equate user-sorts only by name

Methods

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

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

Ord Kind Source #

We want to order user-sorts only by name

Methods

compare :: Kind -> Kind -> Ordering #

(<) :: Kind -> Kind -> Bool #

(<=) :: Kind -> Kind -> Bool #

(>) :: Kind -> Kind -> Bool #

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

max :: Kind -> Kind -> Kind #

min :: Kind -> Kind -> Kind #

Show Kind Source # 

Methods

showsPrec :: Int -> Kind -> ShowS #

show :: Kind -> String #

showList :: [Kind] -> ShowS #

HasKind Kind Source # 

class HasKind a where Source #

A class for capturing values that have a sign and a size (finite or infinite) minimal complete definition: kindOf. This class can be automatically derived for data-types that have a Data instance; this is useful for creating uninterpreted sorts.

Instances

HasKind Bool Source # 
HasKind Double Source # 
HasKind Float Source # 
HasKind Int8 Source # 
HasKind Int16 Source # 
HasKind Int32 Source # 
HasKind Int64 Source # 
HasKind Integer Source # 
HasKind Word8 Source # 
HasKind Word16 Source # 
HasKind Word32 Source # 
HasKind Word64 Source # 
HasKind AlgReal Source # 
HasKind Kind Source # 
HasKind CW Source #

Kind instance for CW

HasKind RoundingMode Source #

RoundingMode kind

HasKind SVal Source # 
HasKind E Source # 
HasKind Word4 Source #

HasKind instance; simply returning the underlying kind for the type

HasKind Sport Source # 
HasKind Pet Source # 
HasKind Beverage Source # 
HasKind Nationality Source # 
HasKind Color Source # 
HasKind Location Source # 
HasKind U2Member Source # 
HasKind B Source # 
HasKind Q Source # 
HasKind L Source #

Similarly, HasKinds default implementation is sufficient.

HasKind (SBV a) Source # 

data CWVal Source #

A constant value

Constructors

CWAlgReal AlgReal

algebraic real

CWInteger Integer

bit-vector/unbounded integer

CWFloat Float

float

CWDouble Double

double

CWUserSort (Maybe Int, String)

value of an uninterpreted/user kind. The Maybe Int shows index position for enumerations

Instances

Eq CWVal Source #

Eq instance for CWVal. Note that we cannot simply derive Eq/Ord, since CWAlgReal doesn't have proper instances for these when values are infinitely precise reals. However, we do need a structural eq/ord for Map indexes; so define custom ones here:

Methods

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

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

Ord CWVal Source #

Ord instance for CWVal. Same comments as the Eq instance why this cannot be derived.

Methods

compare :: CWVal -> CWVal -> Ordering #

(<) :: CWVal -> CWVal -> Bool #

(<=) :: CWVal -> CWVal -> Bool #

(>) :: CWVal -> CWVal -> Bool #

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

max :: CWVal -> CWVal -> CWVal #

min :: CWVal -> CWVal -> CWVal #

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

Constructors

AlgRational Bool Rational 
AlgPolyRoot (Integer, Polynomial) (Maybe String) 

Instances

Eq AlgReal Source # 

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.

Num AlgReal Source # 
Ord AlgReal Source # 
Real AlgReal Source # 
Show AlgReal Source # 
Random AlgReal Source # 

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

Arbitrary AlgReal Source # 

Methods

arbitrary :: Gen AlgReal

shrink :: AlgReal -> [AlgReal]

HasKind AlgReal Source # 
SatModel AlgReal Source #

AlgReal as extracted from a model

Methods

parseCWs :: [CW] -> Maybe (AlgReal, [CW]) Source #

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

IEEEFloatConvertable AlgReal Source # 

data Quantifier Source #

Quantifiers: forall or exists. Note that we allow arbitrary nestings.

Constructors

ALL 
EX 

mkConstCW :: Integral a => Kind -> a -> CW Source #

Create a constant word from an integral.

genVar :: Maybe Quantifier -> Kind -> String -> Symbolic (SBV a) Source #

Generate a finite symbolic bitvector, named

genVar_ :: Maybe Quantifier -> Kind -> Symbolic (SBV a) Source #

Generate a finite symbolic bitvector, unnamed

liftQRem :: SymWord a => SBV a -> SBV a -> (SBV a, SBV a) Source #

Lift QRem to symbolic words. Division by 0 is defined s.t. x/0 = 0; which holds even when x is 0 itself.

liftDMod :: (SymWord a, Num a, SDivisible (SBV a)) => SBV a -> SBV a -> (SBV a, SBV a) Source #

Lift DMod to symbolic words. Division by 0 is defined s.t. x/0 = 0; which holds even when x is 0 itself. Essentially, this is conversion from quotRem (truncate to 0) to divMod (truncate towards negative infinity)

symbolicMergeWithKind :: Kind -> Bool -> SBool -> SBV a -> SBV a -> SBV a Source #

Merge two symbolic values, at kind k, possibly force'ing the branches to make sure they do not evaluate to the same result. This should only be used for internal purposes; as default definitions provided should suffice in many cases. (i.e., End users should only need to define symbolicMerge when needed; which should be rare to start with.)

cache :: (State -> IO a) -> Cached a Source #

Cache a state-based computation

sbvToSW :: State -> SBV a -> IO SW Source #

Convert a symbolic value to a symbolic-word

newExpr :: State -> Kind -> SBVExpr -> IO SW Source #

Create a new expression; hash-cons as necessary

normCW :: CW -> CW Source #

Normalize a CW. Essentially performs modular arithmetic to make sure the value can fit in the given bit-size. Note that this is rather tricky for negative values, due to asymmetry. (i.e., an 8-bit negative number represents values in the range -128 to 127; thus we have to be careful on the negative side.)

data SBVExpr Source #

A symbolic expression

Constructors

SBVApp !Op ![SW] 

Instances

Eq SBVExpr Source # 

Methods

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

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

Ord SBVExpr Source # 
Show SBVExpr Source #

Show instance for SBVExpr. Again, only for debugging purposes.

NFData SBVExpr Source # 

Methods

rnf :: SBVExpr -> () #

data Op Source #

Symbolic operations

Instances

Eq Op Source # 

Methods

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

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

Ord Op Source # 

Methods

compare :: Op -> Op -> Ordering #

(<) :: Op -> Op -> Bool #

(<=) :: Op -> Op -> Bool #

(>) :: Op -> Op -> Bool #

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

max :: Op -> Op -> Op #

min :: Op -> Op -> Op #

Show Op Source #

Show instance for Op. Note that this is largely for debugging purposes, not used for being read by any tool.

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

newtype SBVType Source #

A simple type for SBV computations, used mainly for uninterpreted constants. We keep track of the signedness/size of the arguments. A non-function will have just one entry in the list.

Constructors

SBVType [Kind] 

newUninterpreted :: State -> String -> SBVType -> Maybe [String] -> IO () Source #

Create a new uninterpreted symbol, possibly with user given code

forceSWArg :: SW -> IO () Source #

Forcing an argument; this is a necessary evil to make sure all the arguments to an uninterpreted function and sBranch test conditions are evaluated before called; the semantics of uinterpreted functions is necessarily strict; deviating from Haskell's

Operations useful for instantiating SBV type classes

genLiteral :: Integral a => Kind -> a -> SBV b Source #

Generate a finite constant bitvector

genFromCW :: Integral a => CW -> a Source #

Convert a constant to an integral value

genMkSymVar :: Kind -> Maybe Quantifier -> Maybe String -> Symbolic (SBV a) Source #

Generically make a symbolic var

checkAndConvert :: (Num a, Bits a, SymWord a) => Int -> [SBool] -> SBV a Source #

Perform a sanity check that we should receive precisely the same number of bits as required by the resulting type. The input is little-endian

genParse :: Integral a => Kind -> [CW] -> Maybe (a, [CW]) Source #

Parse a signed/sized value from a sequence of CWs

showModel :: SMTConfig -> SMTModel -> String Source #

Show a model in human readable form. Ignore bindings to those variables that start with "__internal_sbv_" and also those marked as "nonModelVar" in the config; as these are only for internal purposes

data SMTModel Source #

A model, as returned by a solver

Constructors

SMTModel 

Fields

smtLibReservedNames :: [String] Source #

Names reserved by SMTLib. This list is current as of Dec 6 2015; but of course there's no guarantee it'll stay that way.

Polynomial operations that operate on bit-vectors

ites :: SBool -> [SBool] -> [SBool] -> [SBool] Source #

Run down a boolean condition over two lists. Note that this is different than zipWith as shorter list is assumed to be filled with false at the end (i.e., zero-bits); which nicely pads it when considered as an unsigned number in little-endian form.

mdp :: [SBool] -> [SBool] -> ([SBool], [SBool]) Source #

Compute modulus/remainder of polynomials on bit-vectors.

addPoly :: [SBool] -> [SBool] -> [SBool] Source #

Add two polynomials

Compilation to C

compileToC' :: String -> SBVCodeGen () -> IO CgPgmBundle Source #

Lower level version of compileToC, producing a CgPgmBundle

compileToCLib' :: String -> [(String, SBVCodeGen ())] -> IO CgPgmBundle Source #

Lower level version of compileToCLib, producing a CgPgmBundle

data CgPgmBundle Source #

Representation of a collection of generated programs.

Instances

Show CgPgmBundle Source #

A simple way to print bundles, mostly for debugging purposes.

data CgPgmKind Source #

Different kinds of "files" we can produce. Currently this is quite C specific.

Various math utilities around floats

fpRound0 :: (RealFloat a, Integral b) => a -> b Source #

A variant of round; except defaulting to 0 when fed NaN or Infinity

fpRatio0 :: RealFloat a => a -> Rational Source #

A variant of toRational; except defaulting to 0 when fed NaN or Infinity

fpMaxH :: RealFloat a => a -> a -> a Source #

The SMT-Lib (in particular Z3) implementation for min/max for floats does not agree with Haskell's; and also it does not agree with what the hardware does. Sigh.. See: https://ghc.haskell.org/trac/ghc/ticket/10378 https://github.com/Z3Prover/z3/issues/68 So, we codify here what the Z3 (SMTLib) is implementing for fpMax. The discrepancy with Haskell is that the NaN propagation doesn't work in Haskell The discrepancy with x86 is that given +0/-0, x86 returns the second argument; SMTLib is non-deterministic

fpMinH :: RealFloat a => a -> a -> a Source #

SMTLib compliant definition for fpMin. See the comments for fpMax.

fp2fp :: (RealFloat a, RealFloat b) => a -> b Source #

Convert double to float and back. Essentially fromRational . toRational except careful on NaN, Infinities, and -0.

fpRemH :: RealFloat a => a -> a -> a Source #

Compute the "floating-point" remainder function, the float/double value that remains from the division of x and y. There are strict rules around 0's, Infinities, and NaN's as coded below, See http://smt-lib.org/papers/BTRW14.pdf, towards the end of section 4.c.

fpRoundToIntegralH :: RealFloat a => a -> a Source #

Convert a float to the nearest integral representable in that type

fpIsEqualObjectH :: RealFloat a => a -> a -> Bool Source #

Check that two floats are the exact same values, i.e., +0/-0 does not compare equal, and NaN's compare equal to themselves.

fpIsNormalizedH :: RealFloat a => a -> Bool Source #

Check if a number is "normal." Note that +0/-0 is not considered a normal-number and also this is not simply the negation of isDenormalized!