
Dear all, Currently the only way to throw an exception in an STM transaction is via throw. The IO monad has the throwIO function which guarantees ordering with respect to other IO actions. It would be nice to have a similar function for the STM monad: throwSTM :: Exception e => e -> STM a I propose adding this to Control.Monad.STM. Additionally I propose to generalize: catchSTM :: STM a -> (SomeException -> STM a) -> STM a to: catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a to make it consistent with the IO catch function: catch :: Exception e => IO a -> e -> IO a -> IO a and allow packages like exception-monads-fd/tf to define an instance MonadException STM. I don't have a patch because I think these changes also require modifying/extending the rts which I don't feel comfortable with doing right now. Discussion deadline: Three weeks, until Sunday 17th October (because of ICFP). Ticket: http://hackage.haskell.org/trac/ghc/ticket/4343 Regards, Bas

On Sun, Sep 26, 2010 at 10:24 AM, Bas van Dijk
Dear all,
Currently the only way to throw an exception in an STM transaction is via throw. The IO monad has the throwIO function which guarantees ordering with respect to other IO actions. It would be nice to have a similar function for the STM monad:
throwSTM :: Exception e => e -> STM a
I propose adding this to Control.Monad.STM.
Additionally I propose to generalize:
catchSTM :: STM a -> (SomeException -> STM a) -> STM a
to:
catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
to make it consistent with the IO catch function:
catch :: Exception e => IO a -> e -> IO a -> IO a
and allow packages like exception-monads-fd/tf to define an instance MonadException STM.
I don't have a patch because I think these changes also require modifying/extending the rts which I don't feel comfortable with doing right now.
Sounds good to me. Your new catchSTM can be written from the old one:
newCatchSTM stm h = catchSTM stm (h . fromJust . fromException . toException)
The following definition for throwSTM typechecks, and does pretty much exactly what you want, but we'll want someone on GHC to let us know that it is not going to do weird things to the RTS:
throwSTM e = STM (raiseIO# (toException e))
Attached is a file with the implementations of these and some examples of usage. Antoine

On Sun, Sep 26, 2010 at 6:13 PM, Antoine Latter
Your new catchSTM can be written from the old one:
newCatchSTM stm h = catchSTM stm (h . fromJust . fromException . toException)
Thanks! Is the toException necessary? It type checks without it.
The following definition for throwSTM typechecks, and does pretty much exactly what you want, but we'll want someone on GHC to let us know that it is not going to do weird things to the RTS:
throwSTM e = STM (raiseIO# (toException e))
Yes, I was playing with this definition to but where a bit afraid of using raiseIO# inside STM.
Attached is a file with the implementations of these and some examples of usage.
Thanks, I will make a patch out of this and attach it to the ticket. We'll see what the GHC devs think of it. Bas

On 26/09/10 13:55, Bas van Dijk wrote:
On Sun, Sep 26, 2010 at 6:13 PM, Antoine Latter
wrote: Your new catchSTM can be written from the old one:
newCatchSTM stm h = catchSTM stm (h . fromJust . fromException . toException)
Agree in principle, but I don't think that implementation works, does it? If the exception is the wrong type, fromJust will throw an error, whereas you want to just re-throw the original exception.
I will make a patch out of this and attach it to the ticket. We'll see what the GHC devs think of it.
Fine by me. Cheers, Simon

On Sun, 2010-09-26 at 15:46 -0400, Simon Marlow wrote:
On 26/09/10 13:55, Bas van Dijk wrote:
On Sun, Sep 26, 2010 at 6:13 PM, Antoine Latter
wrote: Your new catchSTM can be written from the old one:
newCatchSTM stm h = catchSTM stm (h . fromJust . fromException . toException)
Agree in principle, but I don't think that implementation works, does it? If the exception is the wrong type, fromJust will throw an error, whereas you want to just re-throw the original exception.
I will make a patch out of this and attach it to the ticket. We'll see what the GHC devs think of it.
Fine by me.
Cheers, Simon
newCatchSTM stm h = catchSTM stm (\e -> maybe (throwSTM e) f $ fromException e) Regards

On Sun, Sep 26, 2010 at 3:09 PM, Maciej Piechotka
On Sun, 2010-09-26 at 15:46 -0400, Simon Marlow wrote:
On 26/09/10 13:55, Bas van Dijk wrote:
On Sun, Sep 26, 2010 at 6:13 PM, Antoine Latter
wrote: Your new catchSTM can be written from the old one:
newCatchSTM stm h = catchSTM stm (h . fromJust . fromException . toException)
Agree in principle, but I don't think that implementation works, does it? If the exception is the wrong type, fromJust will throw an error, whereas you want to just re-throw the original exception.
I will make a patch out of this and attach it to the ticket. We'll see what the GHC devs think of it.
Fine by me.
Cheers, Simon
newCatchSTM stm h = catchSTM stm (\e -> maybe (throwSTM e) f $ fromException e)
It also would work to copy the GHC.IO version:
unSTM (STM stm) = stm
catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a catchSTM (STM stm) handler = STM $ catchSTM# stm handler' where handler' e = case fromException e of Just e' -> unSTM (handler e') Nothing -> raiseIO# e
Although the catchException in GHC.IO uses raise# instead of raiseIO# - that may be for a reason. I had thought they were really similar underneath the hood, though. Antoine

On Sun, Sep 26, 2010 at 4:21 PM, Antoine Latter
On Sun, Sep 26, 2010 at 3:09 PM, Maciej Piechotka
wrote: On Sun, 2010-09-26 at 15:46 -0400, Simon Marlow wrote:
On 26/09/10 13:55, Bas van Dijk wrote:
On Sun, Sep 26, 2010 at 6:13 PM, Antoine Latter
wrote: Your new catchSTM can be written from the old one:
newCatchSTM stm h = catchSTM stm (h . fromJust . fromException . toException)
Agree in principle, but I don't think that implementation works, does it? If the exception is the wrong type, fromJust will throw an error, whereas you want to just re-throw the original exception.
I will make a patch out of this and attach it to the ticket. We'll see what the GHC devs think of it.
Fine by me.
Cheers, Simon
newCatchSTM stm h = catchSTM stm (\e -> maybe (throwSTM e) f $ fromException e)
It also would work to copy the GHC.IO version:
unSTM (STM stm) = stm
catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a catchSTM (STM stm) handler = STM $ catchSTM# stm handler' where handler' e = case fromException e of Just e' -> unSTM (handler e') Nothing -> raiseIO# e
Although the catchException in GHC.IO uses raise# instead of raiseIO# - that may be for a reason. I had thought they were really similar underneath the hood, though.
And Bas put that exact code in the ticket two hours ago :-) So that's a +1 from me. It would be nice to get a Hackage analysis to get an idea of what will break from this change. Antoine

On Sun, Sep 26, 2010 at 11:24 PM, Antoine Latter
So that's a +1 from me. It would be nice to get a Hackage analysis to get an idea of what will break from this change.
There are 83 direct reverse dependencies of stm: http://bifunctor.homelinux.net/~roel/cgi-bin/hackage-scripts/revdeps/stm-2.1... None of them define throwSTM, so adding this function will not break anything. 6 of those packages use catchSTM.
From a quick read of the source code all of them seem to keep working with the proposed generalization.
What follows is the detailed analysis: * stm-io-hooks-0.6.0/Control/Concurrent/AdvSTM.hs:88: import qualified Control.Concurrent.STM as S class Monad m => MonadAdvSTM m where ... catchSTM :: Exception e => m a -> (e -> m a) -> m a instance MonadAdvSTM AdvSTM where ... catchSTM action handler = do action' <- unlift action handler' <- unlift1 handler let handler'' e = case fromException e of Nothing -> throw e Just e' -> handler' e' liftAdv $ S.catchSTM action' handler'' This code does not have to be modified. However there's an opportunity to simplify it to just: catchSTM action handler = do action' <- unlift action handler' <- unlift1 handler liftAdv $ S.catchSTM action' handler' * HAppS-State-0.9.3/src/HAppS/State/Monad.hs:86: * happstack-state-0.5.0.2/src/Happstack/State/Monad.hs:82: class CatchEv m where #if __GLASGOW_HASKELL__ < 610 catchEv :: Ev m a -> (Exception -> a) -> Ev m a #else catchEv :: Ev m a -> (SomeException -> a) -> Ev m a #endif instance CatchEv (ReaderT st STM) where catchEv (Ev cmd) fun = Ev $ \s -> ReaderT $ \r -> runReaderT (cmd s) r `catchSTM` (\a -> return (fun a)) instance CatchEv (StateT st STM) where catchEv (Ev cmd) fun = Ev $ \s -> StateT $ \r -> runStateT (cmd s) r `catchSTM` (\a -> return (fun a,r)) This code does not have to be modified. However it would be a nice opportunity to generalize: catchEv :: Exception e => Ev m a -> (e -> a) -> Ev m a * PriorityChansConverger-0.1/Control/Concurrent/ConcurrentUISupport.hs:223: reportExceptionIfAnySTM :: (String -> STM ()) -> String -> STM a -> STM a reportExceptionIfAnySTM reportStr caller_f_name stma = catchSTM stma (\ se@(E.SomeException e) -> reportStr ("An error occurred in function '" ++ caller_f_name ++ "'. Type: " ++ (show $ typeRepTyCon $ typeOf e) ++ ". Representation: " ++ show se) >> E.throw (se :: E.SomeException)) This code does not have to be modified. * Pugs-6.2.13.15/src/Pugs/AST/Eval.hs:181: guardSTM :: STM a -> Eval a guardSTM x = do rv <- stm $ fmap Right x `catchSTM` (return . Left) case rv of Left e -> fail (show e) Right v -> return v This code does not have to be modified. * monadIO-0.9.2.0/src/Control/Concurrent/STM/MonadIO.hs:52: Only reexports catchSTM. There's one package which depends on monadIO: orc. However this package does not use the exported catchSTM. Regards, Bas

On Sun, Sep 26, 2010 at 11:21 PM, Antoine Latter
Although the catchException in GHC.IO uses raise# instead of raiseIO# - that may be for a reason. I had thought they were really similar underneath the hood, though.
I fixed that in the patch I send to this list yesterday. Bas

+1 Consistency is always good, especially with tricky business (exceptions). -- Felipe.

On Sun, Sep 26, 2010 at 5:24 PM, Bas van Dijk
Dear all,
Currently the only way to throw an exception in an STM transaction is via throw. The IO monad has the throwIO function which guarantees ordering with respect to other IO actions. It would be nice to have a similar function for the STM monad:
throwSTM :: Exception e => e -> STM a
I propose adding this to Control.Monad.STM.
Additionally I propose to generalize:
catchSTM :: STM a -> (SomeException -> STM a) -> STM a
to:
catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
to make it consistent with the IO catch function:
catch :: Exception e => IO a -> e -> IO a -> IO a
and allow packages like exception-monads-fd/tf to define an instance MonadException STM.
I don't have a patch because I think these changes also require modifying/extending the rts which I don't feel comfortable with doing right now.
Discussion deadline: Three weeks, until Sunday 17th October (because of ICFP).
Ticket: http://hackage.haskell.org/trac/ghc/ticket/4343
Regards,
Bas
The deadline for this proposal has passed. There were no -1 and three +1s, so I'm setting the status of the ticket to 'patch': http://hackage.haskell.org/trac/ghc/ticket/4343 Do I also have to close the ticket as the Library Submissions Procedure specifies, or should that be done when the patch is actually applied? Thanks, Bas
participants (6)
-
Antoine Latter
-
Bas van Dijk
-
Felipe Lessa
-
Ian Lynagh
-
Maciej Piechotka
-
Simon Marlow