@@ -67,7 +67,7 @@ data Term (t :: Type) where
67
67
68
68
Return :: Expr t -> Term t
69
69
Throw :: Expr a -> Term t
70
- Catch :: Term t -> Expr a -> Term t -> Term t
70
+ Catch :: Term t -> Term t -> Term t
71
71
Retry :: Term t
72
72
73
73
ReadTVar :: Name (TyVar t ) -> Term t
@@ -310,6 +310,30 @@ evalTerm !env !heap !allocs term = case term of
310
310
where
311
311
e' = evalExpr env e
312
312
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
+
313
337
Retry -> (NfRetry , heap, allocs)
314
338
315
339
-- Rule READ
@@ -438,7 +462,7 @@ extendExecEnv (Name name _tyrep) v (ExecEnv env) =
438
462
439
463
-- | Execute an STM 'Term' in the 'STM' monad.
440
464
--
441
- execTerm :: (MonadSTM m , MonadThrow (STM m ))
465
+ execTerm :: (MonadSTM m , MonadThrow (STM m ), MonadCatch ( STM m ) )
442
466
=> ExecEnv m
443
467
-> Term t
444
468
-> STM m (ExecValue m t )
@@ -452,6 +476,8 @@ execTerm env t =
452
476
let e' = execExpr env e
453
477
throwSTM =<< snapshotExecValue e'
454
478
479
+ Catch t1 t2 -> execTerm env t1 `catch` \ (_ :: ImmValue ) -> execTerm env t2
480
+
455
481
Retry -> retry
456
482
457
483
ReadTVar n -> do
@@ -492,7 +518,7 @@ snapshotExecValue (ExecValInt x) = return (ImmValInt x)
492
518
snapshotExecValue (ExecValVar v _) = fmap ImmValVar
493
519
(snapshotExecValue =<< readTVar v)
494
520
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 ) )
496
522
=> Term t -> m TxResult
497
523
execAtomically t =
498
524
toTxResult <$> try (atomically action')
@@ -658,7 +684,7 @@ genTerm env tyrep =
658
684
Nothing )
659
685
]
660
686
661
- binTerm = frequency [ (2 , bindTerm), (1 , orElseTerm)]
687
+ binTerm = frequency [ (2 , bindTerm), (1 , orElseTerm), ( 1 , catchTerm) ]
662
688
663
689
bindTerm =
664
690
sized $ \ sz -> do
@@ -676,6 +702,11 @@ genTerm env tyrep =
676
702
OrElse <$> genTerm env tyrep
677
703
<*> genTerm env tyrep
678
704
705
+ catchTerm =
706
+ sized $ \ sz -> resize (sz `div` 2 ) $
707
+ Catch <$> genTerm env tyrep
708
+ <*> genTerm env tyrep
709
+
679
710
genSomeExpr :: GenEnv -> Gen SomeExpr
680
711
genSomeExpr env =
681
712
oneof'
@@ -714,6 +745,9 @@ shrinkTerm t =
714
745
case t of
715
746
Return e -> [Return e' | e' <- shrinkExpr e]
716
747
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 ]
717
751
Retry -> []
718
752
ReadTVar _ -> []
719
753
@@ -739,6 +773,7 @@ shrinkExpr (ExprName (Name _ (TyRepVar _))) = []
739
773
freeNamesTerm :: Term t -> Set NameId
740
774
freeNamesTerm (Return e) = freeNamesExpr e
741
775
freeNamesTerm (Throw e) = freeNamesExpr e
776
+ freeNamesTerm (Catch t1 t2) = freeNamesTerm t1 <> freeNamesTerm t2
742
777
freeNamesTerm Retry = Set. empty
743
778
freeNamesTerm (ReadTVar n) = Set. singleton (nameId n)
744
779
freeNamesTerm (WriteTVar n e) = Set. singleton (nameId n) <> freeNamesExpr e
@@ -769,6 +804,7 @@ prop_genSomeTerm (SomeTerm tyrep term) =
769
804
termSize :: Term a -> Int
770
805
termSize Return {} = 1
771
806
termSize Throw {} = 1
807
+ termSize (Catch a b) = 1 + termSize a + termSize b
772
808
termSize Retry {} = 1
773
809
termSize ReadTVar {} = 1
774
810
termSize WriteTVar {} = 1
@@ -779,6 +815,7 @@ termSize (OrElse a b) = 1 + termSize a + termSize b
779
815
termDepth :: Term a -> Int
780
816
termDepth Return {} = 1
781
817
termDepth Throw {} = 1
818
+ termDepth (Catch a b) = 1 + max (termDepth a) (termDepth b)
782
819
termDepth Retry {} = 1
783
820
termDepth ReadTVar {} = 1
784
821
termDepth WriteTVar {} = 1
@@ -791,6 +828,9 @@ showTerm p (Return e) = showParen (p > 10) $
791
828
showString " return " . showExpr 11 e
792
829
showTerm p (Throw e) = showParen (p > 10 ) $
793
830
showString " throwSTM " . showExpr 11 e
831
+ showTerm p (Catch t1 t2) = showParen (p > 9 ) $
832
+ showTerm 10 t1 . showString " `catch` "
833
+ . showTerm 10 t2
794
834
showTerm _ Retry = showString " retry"
795
835
showTerm p (ReadTVar n) = showParen (p > 10 ) $
796
836
showString " readTVar " . showName n
0 commit comments