sbv-13.1: 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.Queries.FourFours

Description

A query based solution to the four-fours puzzle. Inspired by http://www.gigamonkeys.com/trees/

Try to make every number between 0 and 20 using only four 4s and any
mathematical operation, with all four 4s being used each time.

We pretty much follow the structure of http://www.gigamonkeys.com/trees/, with the exception that we generate the trees filled with symbolic operators and ask the SMT solver to find the appropriate fillings.

Synopsis

Documentation

data BinOp Source #

Supported binary operators. To keep the search-space small, we will only allow division by 2 or 4, and exponentiation will only be to the power 0. This does restrict the search space, but is sufficient to solve all the instances.

Constructors

Plus 
Minus 
Times 
Divide 
Expt 

Instances

Instances details
Arbitrary BinOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

arbitrary :: Gen BinOp #

shrink :: BinOp -> [BinOp] #

Show BinOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Eq BinOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

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

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

SymVal BinOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

HasKind BinOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

EnumSymbolic BinOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

SatModel BinOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

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

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

OrdSymbolic (SBV BinOp) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Show (T BinOp UnOp) Source #

A rudimentary Show instance for trees, nothing fancy.

Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

HasInductionSchema (Forall ta BinOp -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta BinOp -> SBool) -> ProofObj Source #

SymVal extraT => HasInductionSchema (Forall ta BinOp -> Forall extraS extraT -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta BinOp -> Forall extraS extraT -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2) => HasInductionSchema (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2, SymVal extraT3) => HasInductionSchema (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2, SymVal extraT3, SymVal extraT4) => HasInductionSchema (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2, SymVal extraT3, SymVal extraT4, SymVal extraT5) => HasInductionSchema (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> Forall extraS5 extraT5 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta BinOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> Forall extraS5 extraT5 -> SBool) -> ProofObj Source #

cv2BinOp :: String -> [CV] -> BinOp Source #

Conversion from SMT values to BinOp values.

_undefiner_BinOp :: a Source #

Autogenerated definition to avoid unused-variable warnings from GHC.

type SBinOp = SBV BinOp Source #

Symbolic version of the type BinOp.

sPlus :: SBV BinOp Source #

Symbolic version of the constructor Plus.

sMinus :: SBV BinOp Source #

Symbolic version of the constructor Minus.

sTimes :: SBV BinOp Source #

Symbolic version of the constructor Times.

sDivide :: SBV BinOp Source #

Symbolic version of the constructor Divide.

sExpt :: SBV BinOp Source #

Symbolic version of the constructor Expt.

isPlus :: SBV BinOp -> SBool Source #

Field recognizer predicate.

isMinus :: SBV BinOp -> SBool Source #

Field recognizer predicate.

isTimes :: SBV BinOp -> SBool Source #

Field recognizer predicate.

isDivide :: SBV BinOp -> SBool Source #

Field recognizer predicate.

isExpt :: SBV BinOp -> SBool Source #

Field recognizer predicate.

sCaseBinOp :: Mergeable result => SBV BinOp -> result -> result -> result -> result -> result -> result Source #

Case analyzer for the type BinOp.

data UnOp Source #

Supported unary operators. Similar to BinOp case, we will restrict square-root and factorial to be only applied to the value @4.

Constructors

Negate 
Sqrt 
Factorial 

Instances

Instances details
Arbitrary UnOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

arbitrary :: Gen UnOp #

shrink :: UnOp -> [UnOp] #

Eq UnOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

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

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

SymVal UnOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

HasKind UnOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

EnumSymbolic UnOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

SatModel UnOp Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

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

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

OrdSymbolic (SBV UnOp) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Show (T BinOp UnOp) Source #

A rudimentary Show instance for trees, nothing fancy.

Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

HasInductionSchema (Forall ta UnOp -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta UnOp -> SBool) -> ProofObj Source #

SymVal extraT => HasInductionSchema (Forall ta UnOp -> Forall extraS extraT -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta UnOp -> Forall extraS extraT -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2) => HasInductionSchema (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2, SymVal extraT3) => HasInductionSchema (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2, SymVal extraT3, SymVal extraT4) => HasInductionSchema (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> SBool) -> ProofObj Source #

(SymVal extraT1, SymVal extraT2, SymVal extraT3, SymVal extraT4, SymVal extraT5) => HasInductionSchema (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> Forall extraS5 extraT5 -> SBool) Source # 
Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

Methods

inductionSchema :: (Forall ta UnOp -> Forall extraS1 extraT1 -> Forall extraS2 extraT2 -> Forall extraS3 extraT3 -> Forall extraS4 extraT4 -> Forall extraS5 extraT5 -> SBool) -> ProofObj Source #

cv2UnOp :: String -> [CV] -> UnOp Source #

Conversion from SMT values to UnOp values.

_undefiner_UnOp :: a Source #

Autogenerated definition to avoid unused-variable warnings from GHC.

type SUnOp = SBV UnOp Source #

Symbolic version of the type UnOp.

sNegate :: SBV UnOp Source #

Symbolic version of the constructor Negate.

sSqrt :: SBV UnOp Source #

Symbolic version of the constructor Sqrt.

sFactorial :: SBV UnOp Source #

Symbolic version of the constructor Factorial.

isNegate :: SBV UnOp -> SBool Source #

Field recognizer predicate.

isSqrt :: SBV UnOp -> SBool Source #

Field recognizer predicate.

isFactorial :: SBV UnOp -> SBool Source #

Field recognizer predicate.

sCaseUnOp :: Mergeable result => SBV UnOp -> result -> result -> result -> result Source #

Case analyzer for the type UnOp.

data T b u Source #

The shape of a tree, either a binary node, or a unary node, or the number 4, represented here by the constructor F. We parameterize by the operator type: When doing symbolic computations, we'll fill those with SBinOp and SUnOp. When finding the shapes, we will simply put unit values, i.e., holes.

Constructors

B b (T b u) (T b u) 
U u (T b u) 
F 

Instances

Instances details
Show (T BinOp UnOp) Source #

A rudimentary Show instance for trees, nothing fancy.

Instance details

Defined in Documentation.SBV.Examples.Queries.FourFours

allPossibleTrees :: [T () ()] Source #

Construct all possible tree shapes. The argument here follows the logic in http://www.gigamonkeys.com/trees/: We simply construct all possible shapes and extend with the operators. The number of such trees is:

>>> length allPossibleTrees
640

Note that this is a lot smaller than what is generated by http://www.gigamonkeys.com/trees/. (There, the number of trees is 10240000: 16000 times more than what we have to consider!)

fill :: T () () -> Symbolic (T SBinOp SUnOp) Source #

Given a tree with hols, fill it with symbolic operators. This is the trick that allows us to consider only 640 trees as opposed to over 10 million.

cases :: (Eq a, SymVal a, Mergeable v) => SBV a -> [(a, v)] -> v Source #

Minor helper for writing "symbolic" case statements. Simply walks down a list of values to match against a symbolic version of the key.

eval :: T SBinOp SUnOp -> Symbolic SInteger Source #

Evaluate a symbolic tree, obtaining a symbolic value. Note how we structure this evaluation so we impose extra constraints on what values square-root, divide etc. can take. This is the power of the symbolic approach: We can put arbitrary symbolic constraints as we evaluate the tree.

generate :: Integer -> T () () -> IO (Maybe (T BinOp UnOp)) Source #

In the query mode, find a filling of a given tree shape t, such that it evaluates to the requested number i. Note that we return back a concrete tree.

find :: Integer -> IO () Source #

Given an integer, walk through all possible tree shapes (at most 640 of them), and find a filling that solves the puzzle.

puzzle :: IO () Source #

Solution to the puzzle. When you run this puzzle, the solver can produce different results than what's shown here, but the expressions should still be all valid!

ghci> puzzle
 0 [OK]: (4 - (4 + (4 - 4)))
 1 [OK]: (4 / (4 + (4 - 4)))
 2 [OK]: sqrt((4 + (4 * (4 - 4))))
 3 [OK]: (4 - (4 ^ (4 - 4)))
 4 [OK]: (4 + (4 * (4 - 4)))
 5 [OK]: (4 + (4 ^ (4 - 4)))
 6 [OK]: (4 + sqrt((4 * (4 / 4))))
 7 [OK]: (4 + (4 - (4 / 4)))
 8 [OK]: (4 - (4 - (4 + 4)))
 9 [OK]: (4 + (4 + (4 / 4)))
10 [OK]: (4 + (4 + (4 - sqrt(4))))
11 [OK]: (4 + ((4 + 4!) / 4))
12 [OK]: (4 * (4 - (4 / 4)))
13 [OK]: (4! + ((sqrt(4) - 4!) / sqrt(4)))
14 [OK]: (4 + (4 + (4 + sqrt(4))))
15 [OK]: (4 + ((4! - sqrt(4)) / sqrt(4)))
16 [OK]: (4 * (4 * (4 / 4)))
17 [OK]: (4 + ((sqrt(4) + 4!) / sqrt(4)))
18 [OK]: -(4 + (4 - (sqrt(4) + 4!)))
19 [OK]: -(4 - (4! - (4 / 4)))
20 [OK]: (4 * (4 + (4 / 4)))