{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedLists #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Documentation.SBV.Examples.WeakestPreconditions.Append where
import Data.SBV
import Data.SBV.Control
import Data.SBV.List ((.++))
import qualified Data.SBV.List as L
import Data.SBV.Tools.WeakestPreconditions
import GHC.Generics (Generic)
data AppS a = AppS { AppS a -> SList a
xs :: SList a
, AppS a -> SList a
ys :: SList a
, AppS a -> SList a
ts :: SList a
, AppS a -> SList a
zs :: SList a
}
deriving ((forall x. AppS a -> Rep (AppS a) x)
-> (forall x. Rep (AppS a) x -> AppS a) -> Generic (AppS a)
forall x. Rep (AppS a) x -> AppS a
forall x. AppS a -> Rep (AppS a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (AppS a) x -> AppS a
forall a x. AppS a -> Rep (AppS a) x
$cto :: forall a x. Rep (AppS a) x -> AppS a
$cfrom :: forall a x. AppS a -> Rep (AppS a) x
Generic, Bool -> SBool -> AppS a -> AppS a -> AppS a
(Bool -> SBool -> AppS a -> AppS a -> AppS a)
-> (forall b.
(Ord b, SymVal b, Num b) =>
[AppS a] -> AppS a -> SBV b -> AppS a)
-> Mergeable (AppS a)
forall b.
(Ord b, SymVal b, Num b) =>
[AppS a] -> AppS a -> SBV b -> AppS a
forall a. SymVal a => Bool -> SBool -> AppS a -> AppS a -> AppS a
forall a b.
(SymVal a, Ord b, SymVal b, Num b) =>
[AppS a] -> AppS a -> SBV b -> AppS a
forall a.
(Bool -> SBool -> a -> a -> a)
-> (forall b. (Ord b, SymVal b, Num b) => [a] -> a -> SBV b -> a)
-> Mergeable a
select :: [AppS a] -> AppS a -> SBV b -> AppS a
$cselect :: forall a b.
(SymVal a, Ord b, SymVal b, Num b) =>
[AppS a] -> AppS a -> SBV b -> AppS a
symbolicMerge :: Bool -> SBool -> AppS a -> AppS a -> AppS a
$csymbolicMerge :: forall a. SymVal a => Bool -> SBool -> AppS a -> AppS a -> AppS a
Mergeable)
data AppC a = AppC [a] [a] [a] [a]
instance {-# OVERLAPS #-} (SymVal a, Show a) => Show (AppS a) where
show :: AppS a -> String
show (AppS SList a
xs SList a
ys SList a
ts SList a
zs) = String
"{xs = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SList a -> String
forall a. (SymVal a, Show a) => SBV a -> String
sh SList a
xs String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", ys = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SList a -> String
forall a. (SymVal a, Show a) => SBV a -> String
sh SList a
ys String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", ts = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SList a -> String
forall a. (SymVal a, Show a) => SBV a -> String
sh SList a
ts String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", zs = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ SList a -> String
forall a. (SymVal a, Show a) => SBV a -> String
sh SList a
zs String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"}"
where sh :: SBV a -> String
sh SBV a
v = case SBV a -> Maybe a
forall a. SymVal a => SBV a -> Maybe a
unliteral SBV a
v of
Maybe a
Nothing -> String
"<symbolic>"
Just a
i -> a -> String
forall a. Show a => a -> String
show a
i
instance Show a => Show (AppC a) where
show :: AppC a -> String
show (AppC [a]
xs [a]
ys [a]
ts [a]
zs) = String
"{xs = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => a -> String
show [a]
xs String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", ys = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => a -> String
show [a]
ys String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", ts = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => a -> String
show [a]
ts String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", zs = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => a -> String
show [a]
zs String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"}"
instance Queriable IO (AppS Integer) (AppC Integer) where
create :: QueryT IO (AppS Integer)
create = SList Integer
-> SList Integer -> SList Integer -> SList Integer -> AppS Integer
forall a. SList a -> SList a -> SList a -> SList a -> AppS a
AppS (SList Integer
-> SList Integer -> SList Integer -> SList Integer -> AppS Integer)
-> QueryT IO (SList Integer)
-> QueryT
IO
(SList Integer -> SList Integer -> SList Integer -> AppS Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> QueryT IO (SList Integer)
forall a. SymVal a => Query (SBV a)
freshVar_ QueryT
IO
(SList Integer -> SList Integer -> SList Integer -> AppS Integer)
-> QueryT IO (SList Integer)
-> QueryT IO (SList Integer -> SList Integer -> AppS Integer)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> QueryT IO (SList Integer)
forall a. SymVal a => Query (SBV a)
freshVar_ QueryT IO (SList Integer -> SList Integer -> AppS Integer)
-> QueryT IO (SList Integer)
-> QueryT IO (SList Integer -> AppS Integer)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> QueryT IO (SList Integer)
forall a. SymVal a => Query (SBV a)
freshVar_ QueryT IO (SList Integer -> AppS Integer)
-> QueryT IO (SList Integer) -> QueryT IO (AppS Integer)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> QueryT IO (SList Integer)
forall a. SymVal a => Query (SBV a)
freshVar_
project :: AppS Integer -> QueryT IO (AppC Integer)
project (AppS SList Integer
xs SList Integer
ys SList Integer
ts SList Integer
zs) = [Integer] -> [Integer] -> [Integer] -> [Integer] -> AppC Integer
forall a. [a] -> [a] -> [a] -> [a] -> AppC a
AppC ([Integer] -> [Integer] -> [Integer] -> [Integer] -> AppC Integer)
-> QueryT IO [Integer]
-> QueryT IO ([Integer] -> [Integer] -> [Integer] -> AppC Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SList Integer -> QueryT IO [Integer]
forall a. SymVal a => SBV a -> Query a
getValue SList Integer
xs QueryT IO ([Integer] -> [Integer] -> [Integer] -> AppC Integer)
-> QueryT IO [Integer]
-> QueryT IO ([Integer] -> [Integer] -> AppC Integer)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SList Integer -> QueryT IO [Integer]
forall a. SymVal a => SBV a -> Query a
getValue SList Integer
ys QueryT IO ([Integer] -> [Integer] -> AppC Integer)
-> QueryT IO [Integer] -> QueryT IO ([Integer] -> AppC Integer)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SList Integer -> QueryT IO [Integer]
forall a. SymVal a => SBV a -> Query a
getValue SList Integer
ts QueryT IO ([Integer] -> AppC Integer)
-> QueryT IO [Integer] -> QueryT IO (AppC Integer)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SList Integer -> QueryT IO [Integer]
forall a. SymVal a => SBV a -> Query a
getValue SList Integer
zs
embed :: AppC Integer -> QueryT IO (AppS Integer)
embed (AppC [Integer]
xs [Integer]
ys [Integer]
ts [Integer]
zs) = AppS Integer -> QueryT IO (AppS Integer)
forall (m :: * -> *) a. Monad m => a -> m a
return (AppS Integer -> QueryT IO (AppS Integer))
-> AppS Integer -> QueryT IO (AppS Integer)
forall a b. (a -> b) -> a -> b
$ SList Integer
-> SList Integer -> SList Integer -> SList Integer -> AppS Integer
forall a. SList a -> SList a -> SList a -> SList a -> AppS a
AppS ([Integer] -> SList Integer
forall a. SymVal a => a -> SBV a
literal [Integer]
xs) ([Integer] -> SList Integer
forall a. SymVal a => a -> SBV a
literal [Integer]
ys) ([Integer] -> SList Integer
forall a. SymVal a => a -> SBV a
literal [Integer]
ts) ([Integer] -> SList Integer
forall a. SymVal a => a -> SBV a
literal [Integer]
zs)
type A = AppS Integer
algorithm :: Stmt A
algorithm :: Stmt (AppS Integer)
algorithm = [Stmt (AppS Integer)] -> Stmt (AppS Integer)
forall st. [Stmt st] -> Stmt st
Seq [ (AppS Integer -> AppS Integer) -> Stmt (AppS Integer)
forall st. (st -> st) -> Stmt st
Assign ((AppS Integer -> AppS Integer) -> Stmt (AppS Integer))
-> (AppS Integer -> AppS Integer) -> Stmt (AppS Integer)
forall a b. (a -> b) -> a -> b
$ \AppS Integer
st -> AppS Integer
st{zs :: SList Integer
zs = []}
, (AppS Integer -> AppS Integer) -> Stmt (AppS Integer)
forall st. (st -> st) -> Stmt st
Assign ((AppS Integer -> AppS Integer) -> Stmt (AppS Integer))
-> (AppS Integer -> AppS Integer) -> Stmt (AppS Integer)
forall a b. (a -> b) -> a -> b
$ \st :: AppS Integer
st@AppS{SList Integer
xs :: SList Integer
xs :: forall a. AppS a -> SList a
xs} -> AppS Integer
st{ts :: SList Integer
ts = SList Integer
xs}
, String -> Invariant (AppS Integer) -> Stmt (AppS Integer)
forall a. SymVal a => String -> Invariant (AppS a) -> Stmt (AppS a)
loop String
"xs" (\AppS{SList Integer
xs :: SList Integer
xs :: forall a. AppS a -> SList a
xs, SList Integer
zs :: SList Integer
zs :: forall a. AppS a -> SList a
zs, SList Integer
ts :: SList Integer
ts :: forall a. AppS a -> SList a
ts} -> SList Integer
xs SList Integer -> SList Integer -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.== SList Integer
zs SList Integer -> SList Integer -> SList Integer
forall a. SymVal a => SList a -> SList a -> SList a
.++ SList Integer
ts)
, (AppS Integer -> AppS Integer) -> Stmt (AppS Integer)
forall st. (st -> st) -> Stmt st
Assign ((AppS Integer -> AppS Integer) -> Stmt (AppS Integer))
-> (AppS Integer -> AppS Integer) -> Stmt (AppS Integer)
forall a b. (a -> b) -> a -> b
$ \st :: AppS Integer
st@AppS{SList Integer
ys :: SList Integer
ys :: forall a. AppS a -> SList a
ys} -> AppS Integer
st{ts :: SList Integer
ts = SList Integer
ys}
, String -> Invariant (AppS Integer) -> Stmt (AppS Integer)
forall a. SymVal a => String -> Invariant (AppS a) -> Stmt (AppS a)
loop String
"ys" (\AppS{SList Integer
xs :: SList Integer
xs :: forall a. AppS a -> SList a
xs, SList Integer
ys :: SList Integer
ys :: forall a. AppS a -> SList a
ys, SList Integer
zs :: SList Integer
zs :: forall a. AppS a -> SList a
zs, SList Integer
ts :: SList Integer
ts :: forall a. AppS a -> SList a
ts} -> SList Integer
xs SList Integer -> SList Integer -> SList Integer
forall a. SymVal a => SList a -> SList a -> SList a
.++ SList Integer
ys SList Integer -> SList Integer -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.== SList Integer
zs SList Integer -> SList Integer -> SList Integer
forall a. SymVal a => SList a -> SList a -> SList a
.++ SList Integer
ts)
]
where loop :: String -> Invariant (AppS a) -> Stmt (AppS a)
loop String
w Invariant (AppS a)
inv = String
-> Invariant (AppS a)
-> Maybe (Measure (AppS a))
-> Invariant (AppS a)
-> Stmt (AppS a)
-> Stmt (AppS a)
forall st.
String
-> Invariant st
-> Maybe (Measure st)
-> Invariant st
-> Stmt st
-> Stmt st
While (String
"walk over " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
w)
Invariant (AppS a)
inv
(Measure (AppS a) -> Maybe (Measure (AppS a))
forall a. a -> Maybe a
Just (\AppS{SList a
ts :: SList a
ts :: forall a. AppS a -> SList a
ts} -> [SList a -> SInteger
forall a. SymVal a => SList a -> SInteger
L.length SList a
ts]))
(\AppS{SList a
ts :: SList a
ts :: forall a. AppS a -> SList a
ts} -> SBool -> SBool
sNot (SList a -> SBool
forall a. SymVal a => SList a -> SBool
L.null SList a
ts))
(Stmt (AppS a) -> Stmt (AppS a)) -> Stmt (AppS a) -> Stmt (AppS a)
forall a b. (a -> b) -> a -> b
$ [Stmt (AppS a)] -> Stmt (AppS a)
forall st. [Stmt st] -> Stmt st
Seq [ (AppS a -> AppS a) -> Stmt (AppS a)
forall st. (st -> st) -> Stmt st
Assign ((AppS a -> AppS a) -> Stmt (AppS a))
-> (AppS a -> AppS a) -> Stmt (AppS a)
forall a b. (a -> b) -> a -> b
$ \st :: AppS a
st@AppS{SList a
ts :: SList a
ts :: forall a. AppS a -> SList a
ts, SList a
zs :: SList a
zs :: forall a. AppS a -> SList a
zs} -> AppS a
st{zs :: SList a
zs = SList a
zs SList a -> SBV a -> SList a
forall a. SymVal a => SList a -> SBV a -> SList a
`L.snoc` SList a -> SBV a
forall a. SymVal a => SList a -> SBV a
L.head SList a
ts}
, (AppS a -> AppS a) -> Stmt (AppS a)
forall st. (st -> st) -> Stmt st
Assign ((AppS a -> AppS a) -> Stmt (AppS a))
-> (AppS a -> AppS a) -> Stmt (AppS a)
forall a b. (a -> b) -> a -> b
$ \st :: AppS a
st@AppS{SList a
ts :: SList a
ts :: forall a. AppS a -> SList a
ts} -> AppS a
st{ts :: SList a
ts = SList a -> SList a
forall a. SymVal a => SList a -> SList a
L.tail SList a
ts }
]
imperativeAppend :: Program A
imperativeAppend :: Program (AppS Integer)
imperativeAppend = Program :: forall st.
Symbolic ()
-> (st -> SBool)
-> Stmt st
-> (st -> SBool)
-> Stable st
-> Program st
Program { setup :: Symbolic ()
setup = () -> Symbolic ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, precondition :: Invariant (AppS Integer)
precondition = SBool -> Invariant (AppS Integer)
forall a b. a -> b -> a
const SBool
sTrue
, program :: Stmt (AppS Integer)
program = Stmt (AppS Integer)
algorithm
, postcondition :: Invariant (AppS Integer)
postcondition = Invariant (AppS Integer)
postcondition
, stability :: Stable (AppS Integer)
stability = Stable (AppS Integer)
noChange
}
where
postcondition :: A -> SBool
postcondition :: Invariant (AppS Integer)
postcondition AppS{SList Integer
xs :: SList Integer
xs :: forall a. AppS a -> SList a
xs, SList Integer
ys :: SList Integer
ys :: forall a. AppS a -> SList a
ys, SList Integer
zs :: SList Integer
zs :: forall a. AppS a -> SList a
zs} = SList Integer
zs SList Integer -> SList Integer -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.== SList Integer
xs SList Integer -> SList Integer -> SList Integer
forall a. SymVal a => SList a -> SList a -> SList a
.++ SList Integer
ys
noChange :: Stable (AppS Integer)
noChange = [String
-> (AppS Integer -> SList Integer)
-> AppS Integer
-> AppS Integer
-> (String, SBool)
forall a st.
EqSymbolic a =>
String -> (st -> a) -> st -> st -> (String, SBool)
stable String
"xs" AppS Integer -> SList Integer
forall a. AppS a -> SList a
xs, String
-> (AppS Integer -> SList Integer)
-> AppS Integer
-> AppS Integer
-> (String, SBool)
forall a st.
EqSymbolic a =>
String -> (st -> a) -> st -> st -> (String, SBool)
stable String
"ys" AppS Integer -> SList Integer
forall a. AppS a -> SList a
ys]
correctness :: IO (ProofResult (AppC Integer))
correctness :: IO (ProofResult (AppC Integer))
correctness = WPConfig
-> Program (AppS Integer) -> IO (ProofResult (AppC Integer))
forall st res.
(Show res, Mergeable st, Queriable IO st res) =>
WPConfig -> Program st -> IO (ProofResult res)
wpProveWith WPConfig
defaultWPCfg{wpVerbose :: Bool
wpVerbose=Bool
True} Program (AppS Integer)
imperativeAppend