{-# OPTIONS_GHC -Wall -Werror #-}
module Documentation.SBV.Examples.Puzzles.DogCatMouse where
import Data.SBV
puzzle :: IO AllSatResult
puzzle :: IO AllSatResult
puzzle = SymbolicT IO SBool -> IO AllSatResult
forall a. Satisfiable a => a -> IO AllSatResult
allSat (SymbolicT IO SBool -> IO AllSatResult)
-> SymbolicT IO SBool -> IO AllSatResult
forall a b. (a -> b) -> a -> b
$ do
[dog, cat, mouse] <- [String] -> Symbolic [SInteger]
sIntegers [String
"dog", String
"cat", String
"mouse"]
solve [ dog .>= 1
, cat .>= 1
, mouse .>= 1
, dog + cat + mouse .== 100
, 15 `per` dog + 1 `per` cat + 0.25 `per` mouse .== 100
]
where SReal
p per :: SReal -> SBV a -> SReal
`per` SBV a
q = SReal
p SReal -> SReal -> SReal
forall a. Num a => a -> a -> a
* (SBV a -> SReal
forall a b.
(Integral a, HasKind a, Num a, SymVal a, HasKind b, Num b,
SymVal b) =>
SBV a -> SBV b
sFromIntegral SBV a
q :: SReal)