Copyright | (c) Levent Erkok |
---|---|
License | BSD3 |
Maintainer | erkokl@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Demonstrates uninterpreted sorts and how they can be used for deduction. This example is inspired by the discussion at http://stackoverflow.com/questions/10635783/using-axioms-for-deductions-in-z3, essentially showing how to show the required deduction using SBV.
Representing uninterpreted booleans
The uninterpreted sort B
, corresponding to the carrier.
To prevent SBV from translating it to an enumerated type, we simply attach an unused field
B () |
Instances
Eq B Source # | |
Data B Source # | |
Defined in Documentation.SBV.Examples.Uninterpreted.Deduce gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> B -> c B # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c B # dataTypeOf :: B -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c B) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c B) # gmapT :: (forall b. Data b => b -> b) -> B -> B # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> B -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> B -> r # gmapQ :: (forall d. Data d => d -> u) -> B -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> B -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> B -> m B # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> B -> m B # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> B -> m B # | |
Ord B Source # | |
Read B Source # | |
Show B Source # | |
HasKind B Source # | |
SymWord B Source # | |
Defined in Documentation.SBV.Examples.Uninterpreted.Deduce forall :: String -> Symbolic (SBV B) Source # forall_ :: Symbolic (SBV B) Source # mkForallVars :: Int -> Symbolic [SBV B] Source # exists :: String -> Symbolic (SBV B) Source # exists_ :: Symbolic (SBV B) Source # mkExistVars :: Int -> Symbolic [SBV B] Source # free :: String -> Symbolic (SBV B) Source # free_ :: Symbolic (SBV B) Source # mkFreeVars :: Int -> Symbolic [SBV B] Source # symbolic :: String -> Symbolic (SBV B) Source # symbolics :: [String] -> Symbolic [SBV B] Source # literal :: B -> SBV B Source # unliteral :: SBV B -> Maybe B Source # isConcrete :: SBV B -> Bool Source # isSymbolic :: SBV B -> Bool Source # isConcretely :: SBV B -> (B -> Bool) -> Bool Source # mkSymWord :: Maybe Quantifier -> Maybe String -> Symbolic (SBV B) Source # |
Uninterpreted connectives over B
Axioms of the logical system
Distributivity of OR over AND, as an axiom in terms of
the uninterpreted functions we have introduced. Note how
variables range over the uninterpreted sort B
.
One of De Morgan's laws, again as an axiom in terms of our uninterpeted logical connectives.