Skip to content

Commit ba46a95

Browse files
Yogesh Sajanikaryogeshsajanikar
authored andcommitted
Add Catch term to reference STM evaluation
1 parent 7c22a2a commit ba46a95

File tree

2 files changed

+45
-5
lines changed

2 files changed

+45
-5
lines changed

io-sim/test/Test/IOSim.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1049,7 +1049,7 @@ prop_stm_referenceSim t =
10491049
-- | Compare the behaviour of the STM reference operational semantics with
10501050
-- the behaviour of any 'MonadSTM' STM implementation.
10511051
--
1052-
prop_stm_referenceM :: (MonadSTM m, MonadThrow (STM m), MonadCatch m)
1052+
prop_stm_referenceM :: (MonadSTM m, MonadThrow (STM m), MonadCatch m, LazySTM.MonadSTM m, MonadCatch (LazySTM.STM m))
10531053
=> SomeTerm -> m Property
10541054
prop_stm_referenceM (SomeTerm _tyrep t) = do
10551055
let (r1, _heap) = evalAtomically t

io-sim/test/Test/STM.hs

Lines changed: 44 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -67,7 +67,7 @@ data Term (t :: Type) where
6767

6868
Return :: Expr t -> Term t
6969
Throw :: Expr a -> Term t
70-
Catch :: Term t -> Expr a -> Term t -> Term t
70+
Catch :: Term t -> Term t -> Term t
7171
Retry :: Term t
7272

7373
ReadTVar :: Name (TyVar t) -> Term t
@@ -310,6 +310,30 @@ evalTerm !env !heap !allocs term = case term of
310310
where
311311
e' = evalExpr env e
312312

313+
-- Exception semantics are detailed in "Appendix A Exception semantics" p 12-13 of
314+
-- <https://research.microsoft.com/en-us/um/people/simonpj/papers/stm/stm.pdf>
315+
Catch t1 t2 ->
316+
let (nf1, heap', allocs') = evalTerm env heap mempty t1 in case nf1 of
317+
318+
-- Rule XSTM1
319+
-- M; heap, {} => return P; heap', allocs'
320+
-- --------------------------------------------------------
321+
-- S[catch M N]; heap, allocs => S[return P]; heap', allocs'
322+
NfReturn v -> (NfReturn v, heap', allocs `mappend` allocs')
323+
324+
-- Rule XSTM2
325+
-- M; heap, {} => throw P; heap', allocs'
326+
-- --------------------------------------------------------
327+
-- S[catch M N]; heap, allocs => S[N P]; heap U allocs', allocs U allocs'
328+
NfThrow _ -> evalTerm env (heap `mappend` allocs') (allocs `mappend` allocs') t2
329+
330+
-- Rule XSTM3
331+
-- M; heap, {} => retry; heap', allocs'
332+
-- --------------------------------------------------------
333+
-- S[catch M N]; heap, allocs => S[retry]; heap, allocs
334+
NfRetry -> (NfRetry, heap, allocs)
335+
336+
313337
Retry -> (NfRetry, heap, allocs)
314338

315339
-- Rule READ
@@ -438,7 +462,7 @@ extendExecEnv (Name name _tyrep) v (ExecEnv env) =
438462

439463
-- | Execute an STM 'Term' in the 'STM' monad.
440464
--
441-
execTerm :: (MonadSTM m, MonadThrow (STM m))
465+
execTerm :: (MonadSTM m, MonadThrow (STM m), MonadCatch (STM m))
442466
=> ExecEnv m
443467
-> Term t
444468
-> STM m (ExecValue m t)
@@ -452,6 +476,8 @@ execTerm env t =
452476
let e' = execExpr env e
453477
throwSTM =<< snapshotExecValue e'
454478

479+
Catch t1 t2 -> execTerm env t1 `catch` \(_ :: ImmValue) -> execTerm env t2
480+
455481
Retry -> retry
456482

457483
ReadTVar n -> do
@@ -492,7 +518,7 @@ snapshotExecValue (ExecValInt x) = return (ImmValInt x)
492518
snapshotExecValue (ExecValVar v _) = fmap ImmValVar
493519
(snapshotExecValue =<< readTVar v)
494520

495-
execAtomically :: forall m t. (MonadSTM m, MonadThrow (STM m), MonadCatch m)
521+
execAtomically :: forall m t. (MonadSTM m, MonadThrow (STM m), MonadCatch m, MonadCatch (STM m))
496522
=> Term t -> m TxResult
497523
execAtomically t =
498524
toTxResult <$> try (atomically action')
@@ -658,7 +684,7 @@ genTerm env tyrep =
658684
Nothing)
659685
]
660686

661-
binTerm = frequency [ (2, bindTerm), (1, orElseTerm)]
687+
binTerm = frequency [ (2, bindTerm), (1, orElseTerm), (1, catchTerm)]
662688

663689
bindTerm =
664690
sized $ \sz -> do
@@ -676,6 +702,11 @@ genTerm env tyrep =
676702
OrElse <$> genTerm env tyrep
677703
<*> genTerm env tyrep
678704

705+
catchTerm =
706+
sized $ \sz -> resize (sz `div` 2) $
707+
Catch <$> genTerm env tyrep
708+
<*> genTerm env tyrep
709+
679710
genSomeExpr :: GenEnv -> Gen SomeExpr
680711
genSomeExpr env =
681712
oneof'
@@ -714,6 +745,9 @@ shrinkTerm t =
714745
case t of
715746
Return e -> [Return e' | e' <- shrinkExpr e]
716747
Throw e -> [Throw e' | e' <- shrinkExpr e]
748+
Catch t1 t2 -> [t1, t2]
749+
++ [Catch t1' t2 | t1' <- shrinkTerm t1 ]
750+
++ [Catch t1 t2' | t2' <- shrinkTerm t2 ]
717751
Retry -> []
718752
ReadTVar _ -> []
719753

@@ -739,6 +773,7 @@ shrinkExpr (ExprName (Name _ (TyRepVar _))) = []
739773
freeNamesTerm :: Term t -> Set NameId
740774
freeNamesTerm (Return e) = freeNamesExpr e
741775
freeNamesTerm (Throw e) = freeNamesExpr e
776+
freeNamesTerm (Catch t1 t2) = freeNamesTerm t1 <> freeNamesTerm t2
742777
freeNamesTerm Retry = Set.empty
743778
freeNamesTerm (ReadTVar n) = Set.singleton (nameId n)
744779
freeNamesTerm (WriteTVar n e) = Set.singleton (nameId n) <> freeNamesExpr e
@@ -769,6 +804,7 @@ prop_genSomeTerm (SomeTerm tyrep term) =
769804
termSize :: Term a -> Int
770805
termSize Return{} = 1
771806
termSize Throw{} = 1
807+
termSize (Catch a b) = 1 + termSize a + termSize b
772808
termSize Retry{} = 1
773809
termSize ReadTVar{} = 1
774810
termSize WriteTVar{} = 1
@@ -779,6 +815,7 @@ termSize (OrElse a b) = 1 + termSize a + termSize b
779815
termDepth :: Term a -> Int
780816
termDepth Return{} = 1
781817
termDepth Throw{} = 1
818+
termDepth (Catch a b) = 1 + max (termDepth a) (termDepth b)
782819
termDepth Retry{} = 1
783820
termDepth ReadTVar{} = 1
784821
termDepth WriteTVar{} = 1
@@ -791,6 +828,9 @@ showTerm p (Return e) = showParen (p > 10) $
791828
showString "return " . showExpr 11 e
792829
showTerm p (Throw e) = showParen (p > 10) $
793830
showString "throwSTM " . showExpr 11 e
831+
showTerm p (Catch t1 t2) = showParen (p > 9) $
832+
showTerm 10 t1 . showString " `catch` "
833+
. showTerm 10 t2
794834
showTerm _ Retry = showString "retry"
795835
showTerm p (ReadTVar n) = showParen (p > 10) $
796836
showString "readTVar " . showName n

0 commit comments

Comments
 (0)