sbv-8.4: 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.Lists.BoundedMutex

Description

Demonstrates use of bounded list utilities, proving a simple mutex algorithm correct up to given bounds.

Synopsis

Documentation

data State Source #

Each agent can be in one of the three states

Constructors

Idle

Regular work

Ready

Intention to enter critical state

Critical

In the critical state

Instances
Eq State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

Methods

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

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

Data State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> State -> c State #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c State #

toConstr :: State -> Constr #

dataTypeOf :: State -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c State) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c State) #

gmapT :: (forall b. Data b => b -> b) -> State -> State #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> State -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> State -> r #

gmapQ :: (forall d. Data d => d -> u) -> State -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> State -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> State -> m State #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> State -> m State #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> State -> m State #

Ord State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

Methods

compare :: State -> State -> Ordering #

(<) :: State -> State -> Bool #

(<=) :: State -> State -> Bool #

(>) :: State -> State -> Bool #

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

max :: State -> State -> State #

min :: State -> State -> State #

Read State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

Show State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

HasKind State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

SymVal State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

SatModel State Source #

Make State a symbolic enumeration

Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

Methods

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

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

SMTValue State Source # 
Instance details

Defined in Documentation.SBV.Examples.Lists.BoundedMutex

Methods

sexprToVal :: SExpr -> Maybe State Source #

type SState = SBV State Source #

The type synonym SState is mnemonic for symbolic state.

idle :: SState Source #

Symbolic version of Idle

ready :: SState Source #

Symbolic version of Ready

critical :: SState Source #

Symbolic version of Critical

mutex :: Int -> SList State -> SList State -> SBool Source #

A bounded mutex property holds for two sequences of state transitions, if they are not in their critical section at the same time up to that given bound.

validSequence :: Int -> Integer -> SList Integer -> SList State -> SBool Source #

A sequence is valid upto a bound if it starts at Idle, and follows the mutex rules. That is:

The variable me identifies the agent id.

validTurns :: Int -> SList Integer -> SList State -> SList State -> SBool Source #

The mutex algorithm, coded implicity as an assignment to turns. Turns start at 1, and at each stage is either 1 or 2; giving preference to that process. The only condition is that if either process is in its critical section, then the turn value stays the same. Note that this is sufficient to satisfy safety (i.e., mutual exclusion), though it does not guarantee liveness.

checkMutex :: Int -> IO () Source #

Check that we have the mutex property so long as validSequence and validTurns holds; i.e., so long as both the agents and the arbiter act according to the rules. The check is bounded up-to-the given concrete bound; so this is an example of a bounded-model-checking style proof. We have:

>>> checkMutex 20
All is good!

notFair :: Int -> IO () Source #

Our algorithm is correct, but it is not fair. It does not guarantee that a process that wants to enter its critical-section will always do so eventually. Demonstrate this by trying to show a bounded trace of length 10, such that the second process is ready but never transitions to critical. We have:

ghci> notFair 10
Fairness is violated at bound: 10
P1: [Idle,Idle,Ready,Critical,Idle,Idle,Ready,Critical,Idle,Idle]
P2: [Idle,Ready,Ready,Ready,Ready,Ready,Ready,Ready,Ready,Ready]
Ts: [1,2,1,1,1,1,1,1,1,1]

As expected, P2 gets ready but never goes critical since the arbiter keeps picking P1 unfairly. (You might get a different trace depending on what z3 happens to produce!)

Exercise for the reader: Change the validTurns function so that it alternates the turns from the previous value if neither process is in critical. Show that this makes the notFair function below no longer exhibits the issue. Is this sufficient? Concurrent programming is tricky!