[Haskell-cafe] Throwing an exception in STM without rolling back state?
Tom Ellis
tom-lists-haskell-cafe-2023 at jaguarpaw.co.uk
Wed Dec 18 08:31:37 UTC 2024
Thanks Ryan. I discovered that I can obtain the behaviour I want just
by providing a different version of catch (specifically, wrapping IO's
version of catch).
Does this seem like a reasonable thing to do? Is there a reason that
I shouldn't have this version of catch as an *alternative* method of
catching exceptions in STM (not as the only one -- the original one
will still remain).
Is it somehow unsafe, or violating of some guarantee needed by STM?
If not then I think it would be a good addition (to Bluefin's version
of STM at least, if not the standard one).
Tom
{-# LANGUAGE GHC2021 #-}
{-# LANGUAGE UnboxedTuples #-}
import GHC.Conc
import GHC.IO
import GHC.Exception
data MyEx = MyEx deriving Show
instance Exception MyEx
myCatchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
myCatchSTM m f =
(STM . unIO) ((catch (IO (unSTM m)) (IO . unSTM . f)))
where
unSTM = (\(STM s) -> s)
-- > main
-- True
main = do
r <- atomically $ do
v <- newTVar False
catchSTM @MyEx
(do
writeTVar v True
throwSTM MyEx
)
(\_ -> pure ())
readTVar v
print r
On Tue, Dec 17, 2024 at 10:00:20PM -0500, Ryan Yates wrote:
> Hi Tom,
>
> I think the implementation choices around exceptions in STM are well
> informed and reasoned choices, but other choices could have been made. One
> motivating reason for exceptions having abort semantics, for instance, is
> asynchronous exceptions (see the *Exceptions* section of *Composable Memory
> Transactions*). Caught exceptions thrown within a transaction have the
> same abort semantics for the nested transaction (as your example shows),
> but there is no way to know that `MyEx` isn't thrown asynchronously leading
> to rather difficult to reason about outcomes. I think it would be straight
> forward to modify this behavior in the RTS, simply do not discard the
> transactional record of the nested transaction (
> https://github.com/ghc/ghc/blob/master/rts/PrimOps.cmm#L1390).
>
> Ryan
>
> On Tue, Dec 17, 2024 at 3:33 AM Tom Ellis <
> tom-lists-haskell-cafe-2023 at jaguarpaw.co.uk> wrote:
>
> > Dear Cafe,
> >
> > Is it possible to throw an exception in STM without rolling back
> > state? (See program below for an demonstration that throwing an
> > exception does roll back state.)
> >
> > I'm having a great deal of success using exceptions in my effect
> > system Bluefin, to simulate early return and jumps:
> >
> > *
> > https://hackage.haskell.org/package/bluefin-0.0.14.0/docs/Bluefin-EarlyReturn.html
> >
> > *
> > https://hackage.haskell.org/package/bluefin-0.0.14.0/docs/Bluefin-Jump.html
> >
> > I'm interested in making a Bluefin interface to STM too, but the
> > value of that would be significantly diminished if all exceptions roll
> > back state.
> >
> > Instead I would like to be able to say "throwing this exception
> > _shouldn't_ roll back state". Is that possible? If not in practice,
> > is it possible in theory, if I were to modify the RTS somehow?
> >
> > {-# LANGUAGE GHC2021 #-}
> >
> > import GHC.Conc
> > import GHC.Exception
> >
> > data MyEx = MyEx deriving Show
> >
> > instance Exception MyEx
> >
> > -- > main
> > -- False
> > main = do
> > r <- atomically $ do
> > v <- newTVar False
> >
> > catchSTM @MyEx
> > (do
> > writeTVar v True
> > -- same with throw MyEx`
> > throwSTM MyEx
> > )
> > (\_ -> pure ())
> >
> > readTVar v
> >
> > print r
More information about the Haskell-Cafe
mailing list