{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Documentation.SBV.Examples.Lists.CountOutAndTransfer where
import Prelude hiding (length, take, drop, reverse, (++))
import Data.SBV
import Data.SBV.List
coat :: SymVal a => SInteger -> SList a -> SList a
coat :: forall a. SymVal a => SInteger -> SList a -> SList a
coat SInteger
k SList a
cards = SInteger -> SList a -> SList a
forall a. SymVal a => SInteger -> SList a -> SList a
drop SInteger
k SList a
cards SList a -> SList a -> SList a
forall a. SymVal a => SList a -> SList a -> SList a
++ SList a -> SList a
forall a. SymVal a => SList a -> SList a
reverse (SInteger -> SList a -> SList a
forall a. SymVal a => SInteger -> SList a -> SList a
take SInteger
k SList a
cards)
fourCoat :: SymVal a => SInteger -> SList a -> SList a
fourCoat :: forall a. SymVal a => SInteger -> SList a -> SList a
fourCoat SInteger
k = SInteger -> SList a -> SList a
forall a. SymVal a => SInteger -> SList a -> SList a
coat SInteger
k (SList a -> SList a) -> (SList a -> SList a) -> SList a -> SList a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SInteger -> SList a -> SList a
forall a. SymVal a => SInteger -> SList a -> SList a
coat SInteger
k (SList a -> SList a) -> (SList a -> SList a) -> SList a -> SList a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SInteger -> SList a -> SList a
forall a. SymVal a => SInteger -> SList a -> SList a
coat SInteger
k (SList a -> SList a) -> (SList a -> SList a) -> SList a -> SList a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SInteger -> SList a -> SList a
forall a. SymVal a => SInteger -> SList a -> SList a
coat SInteger
k
type Deck = SList Integer
coatCheck :: Integer -> IO ThmResult
coatCheck :: Integer -> IO ThmResult
coatCheck Integer
n = SymbolicT IO SBool -> IO ThmResult
forall a. Provable a => a -> IO ThmResult
prove (SymbolicT IO SBool -> IO ThmResult)
-> SymbolicT IO SBool -> IO ThmResult
forall a b. (a -> b) -> a -> b
$ do
deck :: Deck <- String -> Symbolic Deck
forall a. SymVal a => String -> Symbolic (SBV a)
free String
"deck"
k <- free "k"
constrain $ length deck .== literal n
constrain $ 2*k .>= literal n
pure $ deck .== fourCoat k deck