{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.Tools.WeakestPreconditions (
Program(..), Stmt(..), assert, stable
, Invariant, Measure, Stable
, VC(..)
, ProofResult(..)
, WPConfig(..), defaultWPCfg
, wpProve, wpProveWith
, traceExecution, Status(..)
) where
import Data.List (intercalate)
import Data.Maybe (fromJust, isJust, isNothing)
import Control.Monad (when)
import Data.SBV
import Data.SBV.Control
data Program st = Program { forall st. Program st -> Symbolic ()
setup :: Symbolic ()
, forall st. Program st -> st -> SBool
precondition :: st -> SBool
, forall st. Program st -> Stmt st
program :: Stmt st
, forall st. Program st -> st -> SBool
postcondition :: st -> SBool
, forall st. Program st -> Stable st
stability :: Stable st
}
type Stable st = [st -> st -> (String, SBool)]
type Invariant st = st -> SBool
type Measure st = st -> [SInteger]
data Stmt st = Skip
| Abort String
| Assign (st -> st)
| If (st -> SBool) (Stmt st) (Stmt st)
| While String (Invariant st) (Maybe (Measure st)) (st -> SBool) (Stmt st)
| Seq [Stmt st]
assert :: String -> (st -> SBool) -> Stmt st
assert :: forall st. String -> (st -> SBool) -> Stmt st
assert String
nm st -> SBool
cond = (st -> SBool) -> Stmt st -> Stmt st -> Stmt st
forall st. (st -> SBool) -> Stmt st -> Stmt st -> Stmt st
If st -> SBool
cond Stmt st
forall st. Stmt st
Skip (String -> Stmt st
forall st. String -> Stmt st
Abort String
nm)
stable :: EqSymbolic a => String -> (st -> a) -> st -> st -> (String, SBool)
stable :: forall a st.
EqSymbolic a =>
String -> (st -> a) -> st -> st -> (String, SBool)
stable String
nm st -> a
f st
before st
after = (String
nm, st -> a
f st
before a -> a -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.=== st -> a
f st
after)
isTotal :: Stmt st -> Bool
isTotal :: forall st. Stmt st -> Bool
isTotal Stmt st
Skip = Bool
True
isTotal (Abort String
_) = Bool
True
isTotal (Assign st -> st
_) = Bool
True
isTotal (If st -> SBool
_ Stmt st
tb Stmt st
fb) = (Stmt st -> Bool) -> [Stmt st] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Stmt st -> Bool
forall st. Stmt st -> Bool
isTotal [Stmt st
tb, Stmt st
fb]
isTotal (While String
_ st -> SBool
_ Maybe (Measure st)
msr st -> SBool
_ Stmt st
s) = Maybe (Measure st) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Measure st)
msr Bool -> Bool -> Bool
&& Stmt st -> Bool
forall st. Stmt st -> Bool
isTotal Stmt st
s
isTotal (Seq [Stmt st]
ss) = (Stmt st -> Bool) -> [Stmt st] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Stmt st -> Bool
forall st. Stmt st -> Bool
isTotal [Stmt st]
ss
data VC st m = BadPrecondition st
| BadPostcondition st st
| Unstable String st st
| AbortReachable String st st
| InvariantPre String st
| InvariantMaintain String st st
| MeasureBound String (st, [m])
| MeasureDecrease String (st, [m]) (st, [m])
dispVC :: String -> [(String, String)] -> String
dispVC :: String -> [(String, String)] -> String
dispVC String
tag [(String, String)]
flds = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> String
col String
tag String -> [String] -> [String]
forall a. a -> [a] -> [a]
: ((String, String) -> String) -> [(String, String)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> String
showField [(String, String)]
flds
where col :: String -> String
col String
"" = String
""
col String
t = String
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":"
showField :: (String, String) -> String
showField (String
t, String
c) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (Int -> String -> String) -> [Int] -> [String] -> [String]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> String -> String
mark [(Int
1::Int)..] (String -> [String]
lines String
c)
where tt :: String
tt = if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
t then String
"" else String -> String
col String
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" "
sp :: String
sp = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
tt) Char
' '
mark :: Int -> String -> String
mark Int
i String
s = String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (if Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then String
tt else String
sp) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
showMeasure :: Show a => [a] -> String
showMeasure :: forall a. Show a => [a] -> String
showMeasure [a
x] = a -> String
forall a. Show a => a -> String
show a
x
showMeasure [a]
xs = [a] -> String
forall a. Show a => a -> String
show [a]
xs
instance (Show st, Show m) => Show (VC st m) where
show :: VC st m -> String
show (BadPrecondition st
s) = String -> [(String, String)] -> String
dispVC String
"Precondition fails"
[(String
"", st -> String
forall a. Show a => a -> String
show st
s)]
show (BadPostcondition st
s1 st
s2) = String -> [(String, String)] -> String
dispVC String
"Postcondition fails"
[ (String
"Start", st -> String
forall a. Show a => a -> String
show st
s1)
, (String
"End ", st -> String
forall a. Show a => a -> String
show st
s2)
]
show (Unstable String
m st
s1 st
s2) = String -> [(String, String)] -> String
dispVC (String
"Stability fails for " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
m)
[ (String
"Before", st -> String
forall a. Show a => a -> String
show st
s1)
, (String
"After ", st -> String
forall a. Show a => a -> String
show st
s2)
]
show (AbortReachable String
nm st
s1 st
s2) = String -> [(String, String)] -> String
dispVC (String
"Abort " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
nm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" condition is satisfiable")
[ (String
"Before", st -> String
forall a. Show a => a -> String
show st
s1)
, (String
"After ", st -> String
forall a. Show a => a -> String
show st
s2)
]
show (InvariantPre String
nm st
s) = String -> [(String, String)] -> String
dispVC (String
"Invariant for loop " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
nm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" fails upon entry")
[(String
"", st -> String
forall a. Show a => a -> String
show st
s)]
show (InvariantMaintain String
nm st
s1 st
s2) = String -> [(String, String)] -> String
dispVC (String
"Invariant for loop " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
nm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not maintained by the body")
[ (String
"Before", st -> String
forall a. Show a => a -> String
show st
s1)
, (String
"After ", st -> String
forall a. Show a => a -> String
show st
s2)
]
show (MeasureBound String
nm (st
s, [m]
m)) = String -> [(String, String)] -> String
dispVC (String
"Measure for loop " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
nm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is negative")
[ (String
"State ", st -> String
forall a. Show a => a -> String
show st
s)
, (String
"Measure", [m] -> String
forall a. Show a => [a] -> String
showMeasure [m]
m )
]
show (MeasureDecrease String
nm (st
s1, [m]
m1) (st
s2, [m]
m2)) = String -> [(String, String)] -> String
dispVC (String
"Measure for loop " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
nm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" does not decrease")
[ (String
"Before ", st -> String
forall a. Show a => a -> String
show st
s1)
, (String
"Measure", [m] -> String
forall a. Show a => [a] -> String
showMeasure [m]
m1)
, (String
"After ", st -> String
forall a. Show a => a -> String
show st
s2)
, (String
"Measure", [m] -> String
forall a. Show a => [a] -> String
showMeasure [m]
m2)
]
data ProofResult res = Proven Bool
| Indeterminate String
| Failed [VC res Integer]
instance Show res => Show (ProofResult res) where
show :: ProofResult res -> String
show (Proven Bool
True) = String
"Q.E.D."
show (Proven Bool
False) = String
"Q.E.D. [Partial: not all termination measures were provided.]"
show (Indeterminate String
s) = String
"Indeterminate: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
show (Failed [VC res Integer]
vcs) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String
"Proof failure. Failing verification condition" String -> String -> String
forall a. [a] -> [a] -> [a]
++ if [VC res Integer] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [VC res Integer]
vcs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then String
"s:" else String
":")
String -> [String] -> [String]
forall a. a -> [a] -> [a]
: (VC res Integer -> String) -> [VC res Integer] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\VC res Integer
vc -> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l | String
l <- String -> [String]
lines (VC res Integer -> String
forall a. Show a => a -> String
show VC res Integer
vc)]) [VC res Integer]
vcs
wpProveWith :: forall st res. (Show res, Mergeable st, Queriable IO st, res ~ QueryResult st) => WPConfig -> Program st -> IO (ProofResult res)
wpProveWith :: forall st res.
(Show res, Mergeable st, Queriable IO st, res ~ QueryResult st) =>
WPConfig -> Program st -> IO (ProofResult res)
wpProveWith cfg :: WPConfig
cfg@WPConfig{Bool
wpVerbose :: Bool
wpVerbose :: WPConfig -> Bool
wpVerbose} Program{Symbolic ()
setup :: forall st. Program st -> Symbolic ()
setup :: Symbolic ()
setup, st -> SBool
precondition :: forall st. Program st -> st -> SBool
precondition :: st -> SBool
precondition, Stmt st
program :: forall st. Program st -> Stmt st
program :: Stmt st
program, st -> SBool
postcondition :: forall st. Program st -> st -> SBool
postcondition :: st -> SBool
postcondition, Stable st
stability :: forall st. Program st -> Stable st
stability :: Stable st
stability} =
SMTConfig -> Symbolic (ProofResult res) -> IO (ProofResult res)
forall a. SMTConfig -> Symbolic a -> IO a
runSMTWith (WPConfig -> SMTConfig
wpSolver WPConfig
cfg) (Symbolic (ProofResult res) -> IO (ProofResult res))
-> Symbolic (ProofResult res) -> IO (ProofResult res)
forall a b. (a -> b) -> a -> b
$ do Symbolic ()
setup
Query (ProofResult res) -> Symbolic (ProofResult res)
forall a. Query a -> Symbolic a
query Query (ProofResult res)
q
where q :: Query (ProofResult res)
q = do start <- QueryT IO st
forall (m :: * -> *) a. Queriable m a => QueryT m a
create
weakestPrecondition <- wp start program (\st
st -> [(st -> SBool
postcondition st
st, st -> st -> VC st SInteger
forall st m. st -> st -> VC st m
BadPostcondition st
start st
st)])
let vcs = st -> [(SBool, VC st SInteger)]
weakestPrecondition st
start
constrain $ sNot $ precondition start .=> sAnd (map fst vcs)
cs <- checkSat
case cs of
CheckSatResult
Unk -> String -> ProofResult res
forall res. String -> ProofResult res
Indeterminate (String -> ProofResult res)
-> (SMTReasonUnknown -> String)
-> SMTReasonUnknown
-> ProofResult res
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SMTReasonUnknown -> String
forall a. Show a => a -> String
show (SMTReasonUnknown -> ProofResult res)
-> QueryT IO SMTReasonUnknown -> Query (ProofResult res)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> QueryT IO SMTReasonUnknown
getUnknownReason
CheckSatResult
Unsat -> do let t :: Bool
t = Stmt st -> Bool
forall st. Stmt st -> Bool
isTotal Stmt st
program
if Bool
t then String -> QueryT IO ()
msg String
"Total correctness is established."
else String -> QueryT IO ()
msg String
"Partial correctness is established."
ProofResult res -> Query (ProofResult res)
forall a. a -> QueryT IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ProofResult res -> Query (ProofResult res))
-> ProofResult res -> Query (ProofResult res)
forall a b. (a -> b) -> a -> b
$ Bool -> ProofResult res
forall res. Bool -> ProofResult res
Proven Bool
t
DSat{} -> ProofResult res -> Query (ProofResult res)
forall a. a -> QueryT IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ProofResult res -> Query (ProofResult res))
-> ProofResult res -> Query (ProofResult res)
forall a b. (a -> b) -> a -> b
$ String -> ProofResult res
forall res. String -> ProofResult res
Indeterminate String
"Unsupported: Solver returned a delta-satisfiable answer."
CheckSatResult
Sat -> do let checkVC :: (SBool, VC st SInteger) -> Query [VC res Integer]
checkVC :: (SBool, VC st SInteger) -> Query [VC res Integer]
checkVC (SBool
cond, VC st SInteger
vc) = do c <- SBool -> Query Bool
forall a. SymVal a => SBV a -> Query a
getValue SBool
cond
if c
then return []
else do vc' <- case vc of
BadPrecondition st
s -> res -> VC res Integer
forall st m. st -> VC st m
BadPrecondition (res -> VC res Integer)
-> QueryT IO res -> QueryT IO (VC res Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s
BadPostcondition st
s1 st
s2 -> res -> res -> VC res Integer
forall st m. st -> st -> VC st m
BadPostcondition (res -> res -> VC res Integer)
-> QueryT IO res -> QueryT IO (res -> VC res Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s1 QueryT IO (res -> VC res Integer)
-> QueryT IO res -> QueryT IO (VC res Integer)
forall a b. QueryT IO (a -> b) -> QueryT IO a -> QueryT IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s2
Unstable String
l st
s1 st
s2 -> String -> res -> res -> VC res Integer
forall st m. String -> st -> st -> VC st m
Unstable String
l (res -> res -> VC res Integer)
-> QueryT IO res -> QueryT IO (res -> VC res Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s1 QueryT IO (res -> VC res Integer)
-> QueryT IO res -> QueryT IO (VC res Integer)
forall a b. QueryT IO (a -> b) -> QueryT IO a -> QueryT IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s2
AbortReachable String
l st
s1 st
s2 -> String -> res -> res -> VC res Integer
forall st m. String -> st -> st -> VC st m
AbortReachable String
l (res -> res -> VC res Integer)
-> QueryT IO res -> QueryT IO (res -> VC res Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s1 QueryT IO (res -> VC res Integer)
-> QueryT IO res -> QueryT IO (VC res Integer)
forall a b. QueryT IO (a -> b) -> QueryT IO a -> QueryT IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s2
InvariantPre String
l st
s -> String -> res -> VC res Integer
forall st m. String -> st -> VC st m
InvariantPre String
l (res -> VC res Integer)
-> QueryT IO res -> QueryT IO (VC res Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s
InvariantMaintain String
l st
s1 st
s2 -> String -> res -> res -> VC res Integer
forall st m. String -> st -> st -> VC st m
InvariantMaintain String
l (res -> res -> VC res Integer)
-> QueryT IO res -> QueryT IO (res -> VC res Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s1 QueryT IO (res -> VC res Integer)
-> QueryT IO res -> QueryT IO (VC res Integer)
forall a b. QueryT IO (a -> b) -> QueryT IO a -> QueryT IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s2
MeasureBound String
l (st
s, [SInteger]
m) -> do r <- st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s
v <- mapM getValue m
return $ MeasureBound l (r, v)
MeasureDecrease String
l (st
s1, [SInteger]
i1) (st
s2, [SInteger]
i2) -> do r1 <- st -> QueryT IO (QueryResult st)
forall (m :: * -> *) a.
Queriable m a =>
a -> QueryT m (QueryResult a)
project st
s1
v1 <- mapM getValue i1
r2 <- project s2
v2 <- mapM getValue i2
return $ MeasureDecrease l (r1, v1) (r2, v2)
return [vc']
badVCs <- [[VC res Integer]] -> [VC res Integer]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[VC res Integer]] -> [VC res Integer])
-> QueryT IO [[VC res Integer]] -> Query [VC res Integer]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((SBool, VC st SInteger) -> Query [VC res Integer])
-> [(SBool, VC st SInteger)] -> QueryT IO [[VC res Integer]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (SBool, VC st SInteger) -> Query [VC res Integer]
checkVC [(SBool, VC st SInteger)]
vcs
when (null badVCs) $ error "Data.SBV.proveWP: Impossible happened. Proof failed, but no failing VC found!"
let plu String
w (a
_:a
_:[a]
_) = String
w String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"s"
plu String
w [a]
_ = String
w
m = String
"Following proof " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [VC res Integer] -> String
forall {a}. String -> [a] -> String
plu String
"obligation" [VC res Integer]
badVCs String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" failed:"
msg m
msg $ replicate (length m) '='
let disp VC res Integer
c = (String -> QueryT IO ()) -> [String] -> QueryT IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> QueryT IO ()
msg [String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l | String
l <- String -> [String]
lines (VC res Integer -> String
forall a. Show a => a -> String
show VC res Integer
c)]
mapM_ disp badVCs
return $ Failed badVCs
msg :: String -> QueryT IO ()
msg = IO () -> QueryT IO ()
forall a. IO a -> Query a
io (IO () -> QueryT IO ())
-> (String -> IO ()) -> String -> QueryT IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
wpVerbose (IO () -> IO ()) -> (String -> IO ()) -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
putStrLn
wp :: st -> Stmt st -> (st -> [(SBool, VC st SInteger)]) -> Query (st -> [(SBool, VC st SInteger)])
wp :: st
-> Stmt st
-> (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
wp st
_ Stmt st
Skip st -> [(SBool, VC st SInteger)]
post = (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
forall a. a -> QueryT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return st -> [(SBool, VC st SInteger)]
post
wp st
start (Abort String
nm) st -> [(SBool, VC st SInteger)]
_ = (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
forall a. a -> QueryT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)]))
-> (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
forall a b. (a -> b) -> a -> b
$ \st
st -> [(SBool
sFalse, String -> st -> st -> VC st SInteger
forall st m. String -> st -> st -> VC st m
AbortReachable String
nm st
start st
st)]
wp st
_ (Assign st -> st
f) st -> [(SBool, VC st SInteger)]
post = (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
forall a. a -> QueryT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)]))
-> (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
forall a b. (a -> b) -> a -> b
$ \st
st -> let st' :: st
st' = st -> st
f st
st
vcs :: [(SBool, VC st SInteger)]
vcs = ((st -> st -> (String, SBool)) -> (SBool, VC st SInteger))
-> Stable st -> [(SBool, VC st SInteger)]
forall a b. (a -> b) -> [a] -> [b]
map (\st -> st -> (String, SBool)
s -> let (String
nm, SBool
b) = st -> st -> (String, SBool)
s st
st st
st' in (SBool
b, String -> st -> st -> VC st SInteger
forall st m. String -> st -> st -> VC st m
Unstable String
nm st
st st
st')) Stable st
stability
in [(SBool, VC st SInteger)]
vcs [(SBool, VC st SInteger)]
-> [(SBool, VC st SInteger)] -> [(SBool, VC st SInteger)]
forall a. [a] -> [a] -> [a]
++ st -> [(SBool, VC st SInteger)]
post st
st'
wp st
start (If st -> SBool
c Stmt st
tb Stmt st
fb) st -> [(SBool, VC st SInteger)]
post = do tWP <- st
-> Stmt st
-> (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
wp st
start Stmt st
tb st -> [(SBool, VC st SInteger)]
post
fWP <- wp start fb post
return $ \st
st -> let cond :: SBool
cond = st -> SBool
c st
st
in [( SBool
cond SBool -> SBool -> SBool
.=> SBool
b, VC st SInteger
v) | (SBool
b, VC st SInteger
v) <- st -> [(SBool, VC st SInteger)]
tWP st
st]
[(SBool, VC st SInteger)]
-> [(SBool, VC st SInteger)] -> [(SBool, VC st SInteger)]
forall a. [a] -> [a] -> [a]
++ [(SBool -> SBool
sNot SBool
cond SBool -> SBool -> SBool
.=> SBool
b, VC st SInteger
v) | (SBool
b, VC st SInteger
v) <- st -> [(SBool, VC st SInteger)]
fWP st
st]
wp st
_ (Seq []) st -> [(SBool, VC st SInteger)]
post = (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
forall a. a -> QueryT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return st -> [(SBool, VC st SInteger)]
post
wp st
start (Seq (Stmt st
s:[Stmt st]
ss)) st -> [(SBool, VC st SInteger)]
post = st
-> Stmt st
-> (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
wp st
start Stmt st
s ((st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)]))
-> Query (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< st
-> Stmt st
-> (st -> [(SBool, VC st SInteger)])
-> Query (st -> [(SBool, VC st SInteger)])
wp st
start ([Stmt st] -> Stmt st
forall st. [Stmt st] -> Stmt st
Seq [Stmt st]
ss) st -> [(SBool, VC st SInteger)]
post
wp st
start (While String
nm st -> SBool
inv Maybe (Measure st)
mm st -> SBool
cond Stmt st
body) st -> [(SBool, VC st SInteger)]
post = do
st' <- QueryT IO st
forall (m :: * -> *) a. Queriable m a => QueryT m a
create
let noMeasure = Maybe (Measure st) -> Bool
forall a. Maybe a -> Bool
isNothing Maybe (Measure st)
mm
m = Maybe (Measure st) -> Measure st
forall a. HasCallStack => Maybe a -> a
fromJust Maybe (Measure st)
mm
curM = Measure st
m st
st'
zero = (SInteger -> SInteger) -> [SInteger] -> [SInteger]
forall a b. (a -> b) -> [a] -> [b]
map (SInteger -> SInteger -> SInteger
forall a b. a -> b -> a
const SInteger
0) [SInteger]
curM
iterates = st -> SBool
inv st
st' SBool -> SBool -> SBool
.&& st -> SBool
cond st
st'
terminates = st -> SBool
inv st
st' SBool -> SBool -> SBool
.&& SBool -> SBool
sNot (st -> SBool
cond st
st')
invHoldsPrior <- wp start Skip (\st
st -> [(st -> SBool
inv st
st, String -> st -> VC st SInteger
forall st m. String -> st -> VC st m
InvariantPre String
nm st
st)])
invMaintained <- wp st' body (\st
st -> [(SBool
iterates SBool -> SBool -> SBool
.=> st -> SBool
inv st
st, String -> st -> st -> VC st SInteger
forall st m. String -> st -> st -> VC st m
InvariantMaintain String
nm st
st' st
st)])
invEstablish <- wp st' body (const [(terminates .=> b, v) | (b, v) <- post st'])
measureNonNegative <- if noMeasure
then return (const [])
else wp st' Skip (const [(iterates .=> curM .>= zero, MeasureBound nm (st', curM))])
measureDecreases <- if noMeasure
then return (const [])
else wp st' body (\st
st -> let prevM :: [SInteger]
prevM = Measure st
m st
st in [(SBool
iterates SBool -> SBool -> SBool
.=> [SInteger]
prevM [SInteger] -> [SInteger] -> SBool
forall a. OrdSymbolic a => a -> a -> SBool
.< [SInteger]
curM, String -> (st, [SInteger]) -> (st, [SInteger]) -> VC st SInteger
forall st m. String -> (st, [m]) -> (st, [m]) -> VC st m
MeasureDecrease String
nm (st
st', [SInteger]
curM) (st
st, [SInteger]
prevM))])
return $ \st
st -> st -> [(SBool, VC st SInteger)]
invHoldsPrior st
st
[(SBool, VC st SInteger)]
-> [(SBool, VC st SInteger)] -> [(SBool, VC st SInteger)]
forall a. [a] -> [a] -> [a]
++ st -> [(SBool, VC st SInteger)]
invMaintained st
st'
[(SBool, VC st SInteger)]
-> [(SBool, VC st SInteger)] -> [(SBool, VC st SInteger)]
forall a. [a] -> [a] -> [a]
++ st -> [(SBool, VC st SInteger)]
invEstablish st
st'
[(SBool, VC st SInteger)]
-> [(SBool, VC st SInteger)] -> [(SBool, VC st SInteger)]
forall a. [a] -> [a] -> [a]
++ st -> [(SBool, VC st SInteger)]
measureNonNegative st
st'
[(SBool, VC st SInteger)]
-> [(SBool, VC st SInteger)] -> [(SBool, VC st SInteger)]
forall a. [a] -> [a] -> [a]
++ st -> [(SBool, VC st SInteger)]
measureDecreases st
st'
wpProve :: (Show res, Mergeable st, Queriable IO st, res ~ QueryResult st) => Program st -> IO (ProofResult res)
wpProve :: forall res st.
(Show res, Mergeable st, Queriable IO st, res ~ QueryResult st) =>
Program st -> IO (ProofResult res)
wpProve = WPConfig -> Program st -> IO (ProofResult res)
forall st res.
(Show res, Mergeable st, Queriable IO st, res ~ QueryResult st) =>
WPConfig -> Program st -> IO (ProofResult res)
wpProveWith WPConfig
defaultWPCfg
data WPConfig = WPConfig { WPConfig -> SMTConfig
wpSolver :: SMTConfig
, WPConfig -> Bool
wpVerbose :: Bool
}
defaultWPCfg :: WPConfig
defaultWPCfg :: WPConfig
defaultWPCfg = WPConfig { wpSolver :: SMTConfig
wpSolver = SMTConfig
defaultSMTCfg
, wpVerbose :: Bool
wpVerbose = Bool
False
}
data Location = Line Int
| Iteration Int
type Loc = [Location]
data Status st = Good st
| Stuck (VC st Integer)
instance Show st => Show (Status st) where
show :: Status st -> String
show (Good st
st) = String
"Program terminated successfully. Final state:\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l | String
l <- String -> [String]
lines (st -> String
forall a. Show a => a -> String
show st
st)]
show (Stuck VC st Integer
vc) = String
"Program is stuck.\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ VC st Integer -> String
forall a. Show a => a -> String
show VC st Integer
vc
traceExecution :: forall st. Show st
=> Program st
-> st
-> IO (Status st)
traceExecution :: forall st. Show st => Program st -> st -> IO (Status st)
traceExecution Program{st -> SBool
precondition :: forall st. Program st -> st -> SBool
precondition :: st -> SBool
precondition, Stmt st
program :: forall st. Program st -> Stmt st
program :: Stmt st
program, st -> SBool
postcondition :: forall st. Program st -> st -> SBool
postcondition :: st -> SBool
postcondition, Stable st
stability :: forall st. Program st -> Stable st
stability :: Stable st
stability} st
start = do
status <- if Loc -> String -> SBool -> Bool
forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap [] String
"checking precondition" (st -> SBool
precondition st
start)
then Loc -> Stmt st -> Status st -> IO (Status st)
go [Int -> Location
Line Int
1] Stmt st
program (Status st -> IO (Status st)) -> IO (Status st) -> IO (Status st)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Loc -> st -> String -> IO (Status st)
step [] st
start String
"*** Precondition holds, starting execution:"
else st -> VC st Integer -> String -> IO (Status st)
giveUp st
start (st -> VC st Integer
forall st m. st -> VC st m
BadPrecondition st
start) String
"*** Initial state does not satisfy the precondition:"
case status of
s :: Status st
s@Stuck{} -> Status st -> IO (Status st)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Status st
s
Good st
end -> if Loc -> String -> SBool -> Bool
forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap [] String
"checking postcondition" (st -> SBool
postcondition st
end)
then Loc -> st -> String -> IO (Status st)
step [] st
end String
"*** Program successfully terminated, post condition holds of the final state:"
else st -> VC st Integer -> String -> IO (Status st)
giveUp st
end (st -> st -> VC st Integer
forall st m. st -> st -> VC st m
BadPostcondition st
start st
end) String
"*** Failed, final state does not satisfy the postcondition:"
where sLoc :: Loc -> String -> String
sLoc :: Loc -> String -> String
sLoc Loc
l String
m
| Loc -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Loc
l = String
m
| Bool
True = String
"===> [" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." ((Location -> String) -> Loc -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Location -> String
sh (Loc -> Loc
forall a. [a] -> [a]
reverse Loc
l)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"] " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
m
where sh :: Location -> String
sh (Line Int
i) = Int -> String
forall a. Show a => a -> String
show Int
i
sh (Iteration Int
i) = String
"{" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"}"
step :: Loc -> st -> String -> IO (Status st)
step :: Loc -> st -> String -> IO (Status st)
step Loc
l st
st String
m = do String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Loc -> String -> String
sLoc Loc
l String
m
st -> IO ()
printST st
st
Status st -> IO (Status st)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Status st -> IO (Status st)) -> Status st -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ st -> Status st
forall st. st -> Status st
Good st
st
stop :: Loc -> VC st Integer -> String -> IO (Status st)
stop :: Loc -> VC st Integer -> String -> IO (Status st)
stop Loc
l VC st Integer
vc String
m = do String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Loc -> String -> String
sLoc Loc
l String
m
Status st -> IO (Status st)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Status st -> IO (Status st)) -> Status st -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ VC st Integer -> Status st
forall st. VC st Integer -> Status st
Stuck VC st Integer
vc
giveUp :: st -> VC st Integer -> String -> IO (Status st)
giveUp :: st -> VC st Integer -> String -> IO (Status st)
giveUp st
st VC st Integer
vc String
m = do r <- Loc -> VC st Integer -> String -> IO (Status st)
stop [] VC st Integer
vc String
m
printST st
return r
dispST :: st -> String
dispST :: st -> String
dispST st
st = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l | String
l <- String -> [String]
lines (st -> String
forall a. Show a => a -> String
show st
st)]
printST :: st -> IO ()
printST :: st -> IO ()
printST = String -> IO ()
putStrLn (String -> IO ()) -> (st -> String) -> st -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. st -> String
dispST
unwrap :: SymVal a => Loc -> String -> SBV a -> a
unwrap :: forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap Loc
l String
m SBV a
v = case SBV a -> Maybe a
forall a. SymVal a => SBV a -> Maybe a
unliteral SBV a
v of
Just a
c -> a
c
Maybe a
Nothing -> String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [ String
""
, String
"*** Data.SBV.WeakestPreconditions.traceExecution:"
, String
"***"
, String
"*** Unable to extract concrete value:"
, String
"*** " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Loc -> String -> String
sLoc Loc
l String
m
, String
"***"
, String
"*** Make sure the starting state is fully concrete and"
, String
"*** there are no uninterpreted functions in play!"
]
go :: Loc -> Stmt st -> Status st -> IO (Status st)
go :: Loc -> Stmt st -> Status st -> IO (Status st)
go Loc
_ Stmt st
_ s :: Status st
s@Stuck{} = Status st -> IO (Status st)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Status st
s
go Loc
loc Stmt st
p (Good st
st) = Stmt st -> IO (Status st)
analyze Stmt st
p
where analyze :: Stmt st -> IO (Status st)
analyze Stmt st
Skip = Loc -> st -> String -> IO (Status st)
step Loc
loc st
st String
"Skip"
analyze (Abort String
nm) = Loc -> VC st Integer -> String -> IO (Status st)
stop Loc
loc (String -> st -> st -> VC st Integer
forall st m. String -> st -> st -> VC st m
AbortReachable String
nm st
start st
st) (String -> IO (Status st)) -> String -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ String
"Abort command executed, labeled: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
nm
analyze (Assign st -> st
f) = case [String
nm | st -> st -> (String, SBool)
s <- Stable st
stability, let (String
nm, SBool
b) = st -> st -> (String, SBool)
s st
st st
st', Bool -> Bool
not (Loc -> String -> SBool -> Bool
forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap Loc
loc (String
"evaluation stability condition " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
nm) SBool
b)] of
[] -> Loc -> st -> String -> IO (Status st)
step Loc
loc st
st' String
"Assign"
[String]
nms -> let comb :: String
comb = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
nms
bad :: VC st Integer
bad = String -> st -> st -> VC st Integer
forall st m. String -> st -> st -> VC st m
Unstable String
comb st
st st
st'
in Loc -> VC st Integer -> String -> IO (Status st)
stop Loc
loc VC st Integer
bad (String -> IO (Status st)) -> String -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ String
"Stability condition fails for: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
comb
where st' :: st
st' = st -> st
f st
st
analyze (If st -> SBool
c Stmt st
tb Stmt st
eb)
| Bool
branchTrue = Loc -> Stmt st -> Status st -> IO (Status st)
go (Int -> Location
Line Int
1 Location -> Loc -> Loc
forall a. a -> [a] -> [a]
: Loc
loc) Stmt st
tb (Status st -> IO (Status st)) -> IO (Status st) -> IO (Status st)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Loc -> st -> String -> IO (Status st)
step Loc
loc st
st String
"Conditional, taking the \"then\" branch"
| Bool
True = Loc -> Stmt st -> Status st -> IO (Status st)
go (Int -> Location
Line Int
2 Location -> Loc -> Loc
forall a. a -> [a] -> [a]
: Loc
loc) Stmt st
eb (Status st -> IO (Status st)) -> IO (Status st) -> IO (Status st)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Loc -> st -> String -> IO (Status st)
step Loc
loc st
st String
"Conditional, taking the \"else\" branch"
where branchTrue :: Bool
branchTrue = Loc -> String -> SBool -> Bool
forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap Loc
loc String
"evaluating the test condition" (st -> SBool
c st
st)
analyze (Seq [Stmt st]
stmts) = [Stmt st] -> Int -> Status st -> IO (Status st)
walk [Stmt st]
stmts Int
1 (st -> Status st
forall st. st -> Status st
Good st
st)
where walk :: [Stmt st] -> Int -> Status st -> IO (Status st)
walk [] Int
_ Status st
is = Status st -> IO (Status st)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Status st
is
walk (Stmt st
s:[Stmt st]
ss) Int
c Status st
is = [Stmt st] -> Int -> Status st -> IO (Status st)
walk [Stmt st]
ss (Int
cInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Status st -> IO (Status st)) -> IO (Status st) -> IO (Status st)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Loc -> Stmt st -> Status st -> IO (Status st)
go (Int -> Location
Line Int
c Location -> Loc -> Loc
forall a. a -> [a] -> [a]
: Loc
loc) Stmt st
s Status st
is
analyze (While String
loopName st -> SBool
invariant Maybe (Measure st)
mbMeasure st -> SBool
condition Stmt st
body)
| st -> Bool
currentInvariant st
st
= Int -> st -> Maybe [Integer] -> Status st -> IO (Status st)
while Int
1 st
st Maybe [Integer]
forall a. Maybe a
Nothing (st -> Status st
forall st. st -> Status st
Good st
st)
| Bool
True
= Loc -> VC st Integer -> String -> IO (Status st)
stop Loc
loc (String -> st -> VC st Integer
forall st m. String -> st -> VC st m
InvariantPre String
loopName st
st) (String -> IO (Status st)) -> String -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ String -> String
tag String
"invariant fails to hold prior to loop entry"
where tag :: String -> String
tag String
s = String
"Loop " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
loopName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
hasMeasure :: Bool
hasMeasure = Maybe (Measure st) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (Measure st)
mbMeasure
measure :: Measure st
measure = Maybe (Measure st) -> Measure st
forall a. HasCallStack => Maybe a -> a
fromJust Maybe (Measure st)
mbMeasure
currentCondition :: st -> Bool
currentCondition = Loc -> String -> SBool -> Bool
forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap Loc
loc (String -> String
tag String
"evaluating the while condition") (SBool -> Bool) -> (st -> SBool) -> st -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. st -> SBool
condition
currentMeasure :: st -> [Integer]
currentMeasure = (SInteger -> Integer) -> [SInteger] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Loc -> String -> SInteger -> Integer
forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap Loc
loc (String -> String
tag String
"evaluating the measure")) ([SInteger] -> [Integer]) -> Measure st -> st -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measure st
measure
currentInvariant :: st -> Bool
currentInvariant = Loc -> String -> SBool -> Bool
forall a. SymVal a => Loc -> String -> SBV a -> a
unwrap Loc
loc (String -> String
tag String
"evaluating the invariant") (SBool -> Bool) -> (st -> SBool) -> st -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. st -> SBool
invariant
while :: Int -> st -> Maybe [Integer] -> Status st -> IO (Status st)
while Int
_ st
_ Maybe [Integer]
_ s :: Status st
s@Stuck{} = Status st -> IO (Status st)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Status st
s
while Int
c st
prevST Maybe [Integer]
mbPrev (Good st
is)
| Bool -> Bool
not (st -> Bool
currentCondition st
is)
= Loc -> st -> String -> IO (Status st)
step Loc
loc st
is (String -> IO (Status st)) -> String -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ String -> String
tag String
"condition fails, terminating"
| Bool -> Bool
not (st -> Bool
currentInvariant st
is)
= Loc -> VC st Integer -> String -> IO (Status st)
stop Loc
loc (String -> st -> st -> VC st Integer
forall st m. String -> st -> st -> VC st m
InvariantMaintain String
loopName st
prevST st
is) (String -> IO (Status st)) -> String -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ String -> String
tag String
"invariant fails to hold in iteration " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
c
| Bool
hasMeasure Bool -> Bool -> Bool
&& [Integer]
mCur [Integer] -> [Integer] -> Bool
forall a. Ord a => a -> a -> Bool
< [Integer]
zero
= Loc -> VC st Integer -> String -> IO (Status st)
stop Loc
loc (String -> (st, [Integer]) -> VC st Integer
forall st m. String -> (st, [m]) -> VC st m
MeasureBound String
loopName (st
is, [Integer]
mCur)) (String -> IO (Status st)) -> String -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ String -> String
tag String
"measure must be non-negative, evaluated to: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Integer] -> String
forall a. Show a => a -> String
show [Integer]
mCur
| Bool
hasMeasure, Just [Integer]
mPrev <- Maybe [Integer]
mbPrev, [Integer]
mCur [Integer] -> [Integer] -> Bool
forall a. Ord a => a -> a -> Bool
>= [Integer]
mPrev
= Loc -> VC st Integer -> String -> IO (Status st)
stop Loc
loc (String -> (st, [Integer]) -> (st, [Integer]) -> VC st Integer
forall st m. String -> (st, [m]) -> (st, [m]) -> VC st m
MeasureDecrease String
loopName (st
prevST, [Integer]
mPrev) (st
is, [Integer]
mCur)) (String -> IO (Status st)) -> String -> IO (Status st)
forall a b. (a -> b) -> a -> b
$ String -> String
tag (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
"measure failed to decrease, prev = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Integer] -> String
forall a. Show a => a -> String
show [Integer]
mPrev String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", current = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [Integer] -> String
forall a. Show a => a -> String
show [Integer]
mCur
| Bool
True
= do nextState <- Loc -> Stmt st -> Status st -> IO (Status st)
go (Int -> Location
Iteration Int
c Location -> Loc -> Loc
forall a. a -> [a] -> [a]
: Loc
loc) Stmt st
body (Status st -> IO (Status st)) -> IO (Status st) -> IO (Status st)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Loc -> st -> String -> IO (Status st)
step Loc
loc st
is (String -> String
tag String
"condition holds, executing the body")
while (c+1) is (Just mCur) nextState
where mCur :: [Integer]
mCur = st -> [Integer]
currentMeasure st
is
zero :: [Integer]
zero = (Integer -> Integer) -> [Integer] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> Integer -> Integer
forall a b. a -> b -> a
const Integer
0) [Integer]
mCur