[Haskell-cafe] Throwing an exception in STM without rolling back state?
Tom Ellis
tom-lists-haskell-cafe-2023 at jaguarpaw.co.uk
Tue Dec 17 08:33:27 UTC 2024
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?
Thanks,
Tom
{-# 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