
I'd like to be able to give up on an STM transaction: roll back and don't retry. I've cooked up something with exceptions but it feels a bit icky to use exceptions for something like this - is there a better way?: data Rollback = Rollback deriving (Show) instance Exception Rollback rollback :: STM x rollback = throwSTM Rollback atomicallyWithRollback :: STM x -> IO (Maybe x) atomicallyWithRollback a = (Just <$> atomically a) `catch` (\Rollback -> pure Nothing) The alternative I've found is something like: otherWay :: STM x -> IO (Maybe x) otherWay a = atomically $ (Just <$> a) `orElse` pure Nothing But this turns any "retry" in "a" into a rollback, and I'd like to have the option to do either (retry or rollback). Thanks, Tom

As far as I understand you can call throwSTM and get desired effect. — Alexander Vershilov
29 нояб. 2020 г., в 00:07, amindfv--- via Haskell-Cafe
написал(а): I'd like to be able to give up on an STM transaction: roll back and don't retry. I've cooked up something with exceptions but it feels a bit icky to use exceptions for something like this - is there a better way?:
data Rollback = Rollback deriving (Show) instance Exception Rollback
rollback :: STM x rollback = throwSTM Rollback
atomicallyWithRollback :: STM x -> IO (Maybe x) atomicallyWithRollback a = (Just <$> atomically a) `catch` (\Rollback -> pure Nothing)
The alternative I've found is something like:
otherWay :: STM x -> IO (Maybe x) otherWay a = atomically $ (Just <$> a) `orElse` pure Nothing
But this turns any "retry" in "a" into a rollback, and I'd like to have the option to do either (retry or rollback).
Thanks, Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

I think how you want to do this depends on the motivation of why you want to rollback. Note that rolling back based on information *inside* the transaction means that the transaction must be consistent to successfully rollback. If you want to trigger rolling back from *outside* the transaction you can do something like this: atomicallyWithCancel :: TVar Bool -> STM x -> IO (Maybe x) atomicallyWithCancel cancel act = atomically ((readTVar cancel >>= check . not >> return Nothing) `orElse` (Just <$> act)) Note that this still has to have a consistent view of memory to successfully "cancel", but if it reaches the end of the transaction it will notice an inconsistent read of the "cancel" tvar and restart the transaction. Then it will quickly commit the cancel transaction that only reads a single TVar and returns Nothing. Ryan On Sat, Nov 28, 2020 at 4:07 PM amindfv--- via Haskell-Cafe < haskell-cafe@haskell.org> wrote:
I'd like to be able to give up on an STM transaction: roll back and don't retry. I've cooked up something with exceptions but it feels a bit icky to use exceptions for something like this - is there a better way?:
data Rollback = Rollback deriving (Show) instance Exception Rollback
rollback :: STM x rollback = throwSTM Rollback
atomicallyWithRollback :: STM x -> IO (Maybe x) atomicallyWithRollback a = (Just <$> atomically a) `catch` (\Rollback -> pure Nothing)
The alternative I've found is something like:
otherWay :: STM x -> IO (Maybe x) otherWay a = atomically $ (Just <$> a) `orElse` pure Nothing
But this turns any "retry" in "a" into a rollback, and I'd like to have the option to do either (retry or rollback).
Thanks, Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

The exception based solution is the best as far as I can tell for now (But I'm not authoritative of course). Maybe a dedicated `Rollback` algebraic effect and its respective handler would feel less "icky"? But the machinery is not generally available yet, and maybe an algebraic effects based solution will be overkill taking the ergonomic cost it'll impose, even if practically doable? Regards, Compl
On 2020-11-29, at 05:05, amindfv--- via Haskell-Cafe
wrote: I'd like to be able to give up on an STM transaction: roll back and don't retry. I've cooked up something with exceptions but it feels a bit icky to use exceptions for something like this - is there a better way?:
data Rollback = Rollback deriving (Show) instance Exception Rollback
rollback :: STM x rollback = throwSTM Rollback
atomicallyWithRollback :: STM x -> IO (Maybe x) atomicallyWithRollback a = (Just <$> atomically a) `catch` (\Rollback -> pure Nothing)
The alternative I've found is something like:
otherWay :: STM x -> IO (Maybe x) otherWay a = atomically $ (Just <$> a) `orElse` pure Nothing
But this turns any "retry" in "a" into a rollback, and I'd like to have the option to do either (retry or rollback).
Thanks, Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

From a contract design perspective, rolling back means that an operation failed and had to be undone. (If everything was fine, you wouldn't want to rollback, wouldn't you?) So if rollback is the reaction to some failure, then triggering it via an exception is the Right Thing To Do, actually. Oh, and you always want to rollback if there's an exception somewhere. Now that contract thing warrants a few more words. Yes, you can word your contracts so that they include failure. It's just that they get more complicated. Usually so much more complicated that it's not worth it. Also, you want any exception (i.e. breach of contract) to go into a rollback. Now in Haskell, rolling back means just abandoning the computation since things aren't mutable and there is no state that you need to restore. Technically, not even in STM - so there *is* reason to make the rollback non-exceptional here: One could argue that STM is *supposed* to include the rollback in the contract. In the end, it depends on your use case: Do you want the rollback in the contract or not? Now for STM itself, yeah using an exception to trigger a rollback is a bit hacky. OTOH it works. OT3H it might be a good idea to have a rollback function for STM. Technically it would just trigger the same exception, but it would indicate that the rollback is part of the contract. OT4H throwing Rollback is essentially an indicator of non-failure rollback (otherwise you'd be throwing whatever exception is appropriate, or get aborted by some library functionality that throws an exception). Regards, Jo Am 28.11.20 um 22:05 schrieb amindfv--- via Haskell-Cafe:
I'd like to be able to give up on an STM transaction: roll back and don't retry. I've cooked up something with exceptions but it feels a bit icky to use exceptions for something like this - is there a better way?:
data Rollback = Rollback deriving (Show) instance Exception Rollback
rollback :: STM x rollback = throwSTM Rollback
atomicallyWithRollback :: STM x -> IO (Maybe x) atomicallyWithRollback a = (Just <$> atomically a) `catch` (\Rollback -> pure Nothing)
The alternative I've found is something like:
otherWay :: STM x -> IO (Maybe x) otherWay a = atomically $ (Just <$> a) `orElse` pure Nothing
But this turns any "retry" in "a" into a rollback, and I'd like to have the option to do either (retry or rollback).
Thanks, Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

I made an STM implementation for work with the ability to give a "reason"
for retrying, which I have found very useful. A Haskell version might look
something like this:
data STM e a
instance Monad (STM e)
-- These also form a monad, but we'd need a newtype to define the instance.
retry :: e -> STM e a
orElse :: STM e1 a -> (e1 -> STM e2 a) -> STM e2 a
With this interface, you could define something like this:
possiblyRollback :: STM (Either e a) b -> STM e (Either a b)
possiblyRollback stm = fmap stm Right `orElse` either retry (return . Left)
With this, you can retry as normal with `retry (Left e)`, locally rollback
with `retry (Right a)`, or return as normal with `return b`.
On Mon, Nov 30, 2020 at 3:47 AM Joachim Durchholz
From a contract design perspective, rolling back means that an operation failed and had to be undone. (If everything was fine, you wouldn't want to rollback, wouldn't you?)
So if rollback is the reaction to some failure, then triggering it via an exception is the Right Thing To Do, actually. Oh, and you always want to rollback if there's an exception somewhere.
Now that contract thing warrants a few more words. Yes, you can word your contracts so that they include failure. It's just that they get more complicated. Usually so much more complicated that it's not worth it. Also, you want any exception (i.e. breach of contract) to go into a rollback. Now in Haskell, rolling back means just abandoning the computation since things aren't mutable and there is no state that you need to restore. Technically, not even in STM - so there *is* reason to make the rollback non-exceptional here: One could argue that STM is *supposed* to include the rollback in the contract. In the end, it depends on your use case: Do you want the rollback in the contract or not?
Now for STM itself, yeah using an exception to trigger a rollback is a bit hacky. OTOH it works. OT3H it might be a good idea to have a rollback function for STM. Technically it would just trigger the same exception, but it would indicate that the rollback is part of the contract. OT4H throwing Rollback is essentially an indicator of non-failure rollback (otherwise you'd be throwing whatever exception is appropriate, or get aborted by some library functionality that throws an exception).
Regards, Jo
I'd like to be able to give up on an STM transaction: roll back and don't retry. I've cooked up something with exceptions but it feels a bit icky to use exceptions for something like this - is there a better way?:
data Rollback = Rollback deriving (Show) instance Exception Rollback
rollback :: STM x rollback = throwSTM Rollback
atomicallyWithRollback :: STM x -> IO (Maybe x) atomicallyWithRollback a = (Just <$> atomically a) `catch` (\Rollback -> pure Nothing)
The alternative I've found is something like:
otherWay :: STM x -> IO (Maybe x) otherWay a = atomically $ (Just <$> a) `orElse` pure Nothing
But this turns any "retry" in "a" into a rollback, and I'd like to have
Am 28.11.20 um 22:05 schrieb amindfv--- via Haskell-Cafe: the option to do either (retry or rollback).
Thanks, Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Sorry for the noise. My code is wrong. Here is a corrected version:
possiblyRollback :: STM (Either e a) b -> STM e (Either a b)
possiblyRollback stm = fmap Right stm `orElse` either retry (return . Left)
On Fri, Dec 4, 2020 at 5:38 PM Jake McArthur
I made an STM implementation for work with the ability to give a "reason" for retrying, which I have found very useful. A Haskell version might look something like this:
data STM e a instance Monad (STM e)
-- These also form a monad, but we'd need a newtype to define the instance. retry :: e -> STM e a orElse :: STM e1 a -> (e1 -> STM e2 a) -> STM e2 a
With this interface, you could define something like this:
possiblyRollback :: STM (Either e a) b -> STM e (Either a b) possiblyRollback stm = fmap stm Right `orElse` either retry (return . Left)
With this, you can retry as normal with `retry (Left e)`, locally rollback with `retry (Right a)`, or return as normal with `return b`.
On Mon, Nov 30, 2020 at 3:47 AM Joachim Durchholz
wrote: From a contract design perspective, rolling back means that an operation failed and had to be undone. (If everything was fine, you wouldn't want to rollback, wouldn't you?)
So if rollback is the reaction to some failure, then triggering it via an exception is the Right Thing To Do, actually. Oh, and you always want to rollback if there's an exception somewhere.
Now that contract thing warrants a few more words. Yes, you can word your contracts so that they include failure. It's just that they get more complicated. Usually so much more complicated that it's not worth it. Also, you want any exception (i.e. breach of contract) to go into a rollback. Now in Haskell, rolling back means just abandoning the computation since things aren't mutable and there is no state that you need to restore. Technically, not even in STM - so there *is* reason to make the rollback non-exceptional here: One could argue that STM is *supposed* to include the rollback in the contract. In the end, it depends on your use case: Do you want the rollback in the contract or not?
Now for STM itself, yeah using an exception to trigger a rollback is a bit hacky. OTOH it works. OT3H it might be a good idea to have a rollback function for STM. Technically it would just trigger the same exception, but it would indicate that the rollback is part of the contract. OT4H throwing Rollback is essentially an indicator of non-failure rollback (otherwise you'd be throwing whatever exception is appropriate, or get aborted by some library functionality that throws an exception).
Regards, Jo
I'd like to be able to give up on an STM transaction: roll back and don't retry. I've cooked up something with exceptions but it feels a bit icky to use exceptions for something like this - is there a better way?:
data Rollback = Rollback deriving (Show) instance Exception Rollback
rollback :: STM x rollback = throwSTM Rollback
atomicallyWithRollback :: STM x -> IO (Maybe x) atomicallyWithRollback a = (Just <$> atomically a) `catch` (\Rollback -> pure Nothing)
The alternative I've found is something like:
otherWay :: STM x -> IO (Maybe x) otherWay a = atomically $ (Just <$> a) `orElse` pure Nothing
But this turns any "retry" in "a" into a rollback, and I'd like to have
Am 28.11.20 um 22:05 schrieb amindfv--- via Haskell-Cafe: the option to do either (retry or rollback).
Thanks, Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (6)
-
Alexander Vershilov
-
amindfv@mailbox.org
-
Jake McArthur
-
Joachim Durchholz
-
Ryan Yates
-
YueCompl