sbv-8.9: SMT Based Verification: Symbolic Haskell theorem prover using SMT solving.
Copyright(c) Levent Erkok
LicenseBSD3
Maintainererkokl@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Documentation.SBV.Examples.Uninterpreted.UISortAllSat

Description

Demonstrates uninterpreted sorts and how all-sat behaves for them. Thanks to Eric Seidel for the idea.

Synopsis

Documentation

data L Source #

A "list-like" data type, but one we plan to uninterpret at the SMT level. The actual shape is really immaterial for us.

Instances

Instances details
Data L Source # 
Instance details

Defined in Documentation.SBV.Examples.Uninterpreted.UISortAllSat

Methods

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

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

toConstr :: L -> Constr #

dataTypeOf :: L -> DataType #

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

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

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

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

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

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

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

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

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

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

Read L Source # 
Instance details

Defined in Documentation.SBV.Examples.Uninterpreted.UISortAllSat

Show L Source # 
Instance details

Defined in Documentation.SBV.Examples.Uninterpreted.UISortAllSat

Methods

showsPrec :: Int -> L -> ShowS #

show :: L -> String #

showList :: [L] -> ShowS #

HasKind L Source # 
Instance details

Defined in Documentation.SBV.Examples.Uninterpreted.UISortAllSat

SymVal L Source # 
Instance details

Defined in Documentation.SBV.Examples.Uninterpreted.UISortAllSat

SatModel L Source # 
Instance details

Defined in Documentation.SBV.Examples.Uninterpreted.UISortAllSat

Methods

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

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

type SL = SBV L Source #

Make L into an uninterpreted sort, automatically introducing SL as a synonym for SBV L.

classify :: SL -> SInteger Source #

An uninterpreted "classify" function. Really, we only care about the fact that such a function exists, not what it does.

genLs :: Predicate Source #

Formulate a query that essentially asserts a cardinality constraint on the uninterpreted sort L. The goal is to say there are precisely 3 such things, as it might be the case. We manage this by declaring four elements, and asserting that for a free variable of this sort, the shape of the data matches one of these three instances. That is, we assert that all the instances of the data L can be classified into 3 equivalence classes. Then, allSat returns all the possible instances, which of course are all uninterpreted.

As expected, we have:

>>> allSat genLs
Solution #1:
  l  = L!val!0 :: L
  l0 = L!val!0 :: L
  l1 = L!val!1 :: L
  l2 = L!val!2 :: L

  classify :: L -> Integer
  classify L!val!2 = 2
  classify L!val!1 = 1
  classify _       = 0
Solution #2:
  l  = L!val!1 :: L
  l0 = L!val!0 :: L
  l1 = L!val!1 :: L
  l2 = L!val!2 :: L

  classify :: L -> Integer
  classify L!val!2 = 2
  classify L!val!1 = 1
  classify _       = 0
Solution #3:
  l  = L!val!2 :: L
  l0 = L!val!0 :: L
  l1 = L!val!1 :: L
  l2 = L!val!2 :: L

  classify :: L -> Integer
  classify L!val!2 = 2
  classify L!val!1 = 1
  classify _       = 0
Found 3 different solutions.