Open parsonsmatt opened 4 years ago
Huh, that's... interesting. I think it would work. I wouldn't have thought of this, because I have a knee-jerk reaction to not mix explicit error returns and runtime exceptions.
There is one potential flaw here. In the contract for ExceptT
, you have a difference between "runtime exception of type E
" and "Left
value of type E
". This approach would erase that difference. I think it's possible to argue that that would lead to confusion and maybe even violate some of the laws around MonadUnliftIO
, but I haven't thought it through.
I'm definitely not ruling this out, it may be worthwhile. It additionally begs some questions around things like StateT
and WriterT
and whether we can smuggle the mutable state into them via an implicitly created IORef
. But that sounds even crazier...
Maybe the StateT
comments were overeager... ignore me :)
instance (MonadUnliftIO m) => MonadUnliftIO (StateT s m) where
withRunInIO stateToIO =
StateT $ \s -> do
r <- newIORef s
a <- withRunInIO $ \runInIO ->
stateToIO $ \stateAction ->
runInIO $ do
(a, s') <- runStateT stateAction s
writeIORef r s'
pure a
s' <- readIORef r
pure (a, s')
Yup! This compiles.
There is one potential flaw here. In the contract for ExceptT, you have a difference between "runtime exception of type E" and "Left value of type E". This approach would erase that difference. I think it's possible to argue that that would lead to confusion and maybe even violate some of the laws around MonadUnliftIO, but I haven't thought it through.
I'm not sure that it does (EDIT: okay, now on coffee cup #2, realizing that i'm about to elaborate at length on exactly what you said), since the call to try
means that the e
exception gets pulled out of the runtime channel and put back into the Left
channel. I think the ambiguity may be from the other side - an e
exception thrown via IO
that gets caught into the Left
vs the IO
channel.
I'm trying to think of a scenario where this is a problem.
foo :: ExceptT MyErr IO ()
foo = do
-- :: ExceptT e m _
withRunInIO $ \runInIO -> do
-- :: IO a
if foo
then throwIO MyErr -- originally an IO exception
else runInIO $ throwError MyErr -- orginally an ExceptT Left
In this code block, we have MyErr
thrown both as an IO
exception, and then via ExceptT
(which is converted to an IO
exception by runInIO
).
Most of the time it seems like people want to use runExceptT
as a sort of try :: ExceptT e m a -> m (Either e a)
, where e
is the type of "caught/checked" exceptions and m
carries the ability to throw unchecked exceptions. So this behavior might be bad if you want e
to be conditionally checked or unchecked. Like,
foo :: ExceptT IOException IO ()
foo = do
-- we want to catch IOExceptions in Left from opening files
ExceptT $ try $ openFile "some file" WriteMode
-- but we don't want to catch IOException in Left from other calls
liftIO $ ioError $ userError "i should be an unchecked exception lol"
If we call this in-line, then we should be able to catchError
and handle only "file opening" issues, while userError
gets bubbled up via IO exceptions.
But if we call it via runInIO
, then both of those exception values (of the same type) would get pushed into the Left
channel.
:thinking:
Well, we could use MVar
s :joy:
instance (MonadUnliftIO m) => MonadUnliftIO (ExceptT e m) where
withRunInIO exceptToIO = ExceptT $ do
exceptionRef <- newEmptyMVar
a <- withRunInIO $ \runInIO ->
exceptToIO $ \exceptAction -> do
ea <- runInIO $ runExceptT exceptAction
case ea of
Left err -> do
putMVar exceptionRef err
pure undefined -- wow laziness rules
Right a ->
pure a
merr <- tryTakeMVar exceptionRef
case merr of
Nothing ->
pure (Right a)
Just e ->
pure (Left e)
EDIT: The Exception
constraint is unnecessary.
The analysis makes sense 👍 . I'm not sure how best to proceed from here though. Some possibilities:
ExceptT
instance (and maybe StateT
too, thank you for that)I lean towards (4) overall, but what are your thoughts?
Well, there's the "theory" behind MonadUnliftIO
where it's a higher order Representable functor class, but with a fixed base of IO
. These instances are definitely not in line with that, and it becomes more like "MonadUnliftIO m
is definable if you can use IO
to mimic the behavior of m
in IO
." So we do get WriterT
with the same trick as MonadState
.
So, is this useful? Yeah! Definitely. Does it point to a kinda bad pattern? Yeah. A big point of the ReaderT Design Pattern
is that ReaderT r IO
is just as powerful, quite a bit faster, and a hell of a lot easier to predict than ExceptT e (StateT s (ReaderT r (WriterT w IO))) a
.
These instances prove that - "We can Unlift
your ExceptT
action but it takes careful thought with exceptions and a kinda nasty hack of laziness to make it work okay." "We can Unlift
your StateT
action but it's just an IORef
under the hood, and IO
exceptions roll back the state (just like they always would)." "We can Unlift
your WriterT
action, but it'll build up a huge data structure before you can observe any of it."
Makes me want to write corresponding IO
based transformers that have the different behavior. IOStateT
that does it's actions in an IORef
, so exceptions don't roll back the state. IOWriterT
that dumps output into a TQueue
or similar. I've already written CheckedT
using constraint plucking and IO
exceptions to get the best of all possible worlds there.
That last point is basically what RIO
is doing with the MonadState
instance: https://www.stackage.org/haddock/nightly-2020-11-11/rio-0.1.19.0/RIO.html#t:RIO
Well, we could use
MVar
s "We canUnlift
yourExceptT
action but it takes careful thought with exceptions and a kinda nasty hack of laziness to make it work okay."
No, you have to throw an exception, otherwise you don't get short-circuiting and attempt to continue evaluation when you don't in fact have a value to provide to the second argument of >>=
. I.e. you pass there undefined
and get an explosion. E.g. this
test :: IO ()
test = void . runExceptT $ withRunInIO $ \exceptToIO -> do
x :: Bool <- exceptToIO $ throwError ()
print x
results in
*** Exception: Prelude.undefined
CallStack (from HasCallStack):
error, called at libraries/base/GHC/Err.hs:80:14 in base:GHC.Err
So can you simply wrap errors thrown via throwError
into a data type like
newtype ViaUnliftIO e = ViaUnliftIO e
and catch those? Then an e
thrown via throwIO
won't get caught.
However that still requires e
to be an Exception
. Maybe it's best to mix the two approaches and use an MVar
to store the thrown error and throw a dummy exception for the purpose of short-circuiting.
And what if the underlying action uses unsafeInterleaveIO
? Then your tryTakeMVar
will fire too early and you'll get the wrong result. So it's probably should be the blocking takeMVar
and you should call putMVar
in both the branches (Just err
vs Nothing
, I suppose). This all is rather subtle...
And we haven't even started talking about concurrency.
Great analysis, thanks!
The state instance doesn't do what you want.
put "written from main thread"
UnliftIO.Async.async $ do
get -- "written from main thread"
put "written from thread 1"
get -- "written from thread 1"
threadDelay 2
threadDelay 1
get -- "written from main thread"
UnliftIO.Async.async $ do
threadDelay 10
get -- "written from main thread"
threadDelay 1
get -- "written from thread 1"
Thanks for testing it out! You're right, with an opaque computation like StateT
, that's about as good as can be done. If only it were a free monad computation that could be evaluated step-by-step :wink:
There is one potential flaw here. In the contract for ExceptT, you have a difference between "runtime exception of type E" and "Left value of type E". This approach would erase that difference.
I do agree that it would be a problem because any distinction of how exception was thrown is lost and catch
will catch the E
regardless how it was thrown, be it with throwIO
or something like except
, throwE
or throwError
. However I think it can be easily solved with a newtype
wrapper (some optimizations with coerce
is possible, but omitted for clarity):
newtype InternalException e = InteralException { unInternalException :: e }
deriving (Eq, Show)
instance Exception e => Exception (InternalException e)
instance (MonadUnliftIO m, Exception e) => MonadUnliftIO (ExceptT e m) where
withRunInIO exceptToIO =
withExceptT unInternalException $ ExceptT $ try $
withRunInIO $ \runInIO ->
exceptToIO
(runInIO . (either (throwIO . InteralException) pure <=< runExceptT))
The only other problem I see is that using catchAny
and others that operate on SomeException
, in the ExceptT e m
will still capture the exception e
. Consider:
data FooException = FooException
deriving (Eq, Show)
instance Exception FooException
bar :: IO ()
bar = print =<< runExceptT (action :: ExceptT FooException IO Int)
where
action =
wrapper $ do
liftIO $ print "Starting"
_ <- throwError FooException
liftIO $ print "Impossible"
pure 5
wrapper inner =
catch inner $ \(exc :: FooException) -> 0 <$ liftIO (print $ "WHAT?? " ++ show exc)
This will produce the expected output:
λ> bar
"Starting"
Left FooException
However in example below catchAny
will get in the middle of so called pure exceptions from ExcepT
:
foo :: IO ()
foo = print =<< runExceptT (action :: ExceptT FooException IO Int)
where
action =
wrapper $ do
liftIO $ print "Starting"
_ <- throwError FooException
liftIO $ print "Impossible"
pure 5
wrapper inner = catchAny inner $ \exc -> 0 <$ liftIO (print $ "Gotcha: " ++ show exc)
Therefore instead of the expected Left FooException
we get:
λ> foo
"Starting"
"Gotcha: FooException"
Right 0
Yet again, it would be possible to solve this by singling out InternalException
and preventing it from being caught in a similar way as with ignoring and rethrowing async exceptions. However, this feels somewhat intrusive onto unliftio
package IMHO.
Not sure about MonadUnliftIO
laws, but one way or another the suggested approach will violate MonadError
law:
In short, all "catching" mechanisms in this library will be unable to catch exceptions thrown by functions in the Control.Exception module, and vice-versa.
because regardless of how we adjust catchAny
in unliftio
, Control.Exceptions.catch
, will still be able to catch exceptions that were meant only for ExceptT
monad.
Can the issue with the State instance be patched using STM Chan (or MVar) instead?
instance (MonadUnliftIO m) => MonadUnliftIO (StateT s m) where
withRunInIO stateToIO =
StateT $ \s -> do
r <- newChan
a <- withRunInIO $ \runInIO ->
stateToIO $ \stateAction ->
runInIO $ do
(a, s') <- runStateT stateAction s
writeChan r s'
pure a
s' <- readChan r
pure (a, s')
Then running the async example, I get:
import RIO
import RIO.State
import UnliftIO
import UnliftIO.Async
run :: RIO App ()
run = do
_ <- flip runStateT "" $ do
put "written from main thread"
_ <- async $ do
(logInfo =<< get) -- "written from main thread"
put "written from thread 1"
logInfo =<< get -- "written from thread 1"
threadDelay 2
threadDelay 1
logInfo =<< get -- "written from thread 1"
_ <- async $ do
threadDelay 10
logInfo =<< get -- "written from thread 1"
threadDelay 1
logInfo =<< get -- "written from thread 1"
pure ()
Strong -1 to adding StateT
and ExceptT
. I think the whole point of unliftio is to provide abstraction to ReaderT r IO
, but not to make up instances of other monads using arbitrary constructs. If a user wants escape hatches, we should be using newtypes instead of adding them to the library.
There is one potential flaw here. In the contract for ExceptT, you have a difference between "runtime exception of type E" and "Left value of type E". This approach would erase that difference. I think it's possible to argue that that would lead to confusion and maybe even violate some of the laws around MonadUnliftIO, but I haven't thought it through.
I should admit that most of the arguments are a bit over my head, but here are my two cents... I found this issue while trying (and getting stuck) writing ExceptT instance that I needed to avoid throwing exceptions where otherwise I would have Either. The use case I have is that I needed to convert IO exceptions returned by different libraries into Either ErrorType a
where ErrorType is the type that includes both the possible errors of different dependencies and the logical errors generated by my code - this type is then serialised to be sent back to the user.
Initially I thought to just throw everything as exception and catch it in one place, but besides the fact that it just felt wrong to throw logical errors as exceptions, it was not possible to reliably determine the source of error - different dependencies were throwing the same exception type. So I tried the opposite approach of converting run time exceptions of dependencies into ExceptT exceptions (and my code wasn't throwing anything - it was just threading possible logical errors via ExceptT).
The only other alternatives (all bad) would be to: 1) re-throw errors of dependencies so that they can be differentiated (and still throw logical errors as well) - feels really bad 2) catch runtime exceptions in place and thread Either manually throw the code - very verbose 3) avoid using unliftio entirely and use ExceptT - difficult to handle IO exceptions with ReaderT monad...
So using this instance feels the only correct option, and I don't think that the decision about the instance for ExceptT should depend on the decisions what to do with other instances that were discussed here - these questions seem unrelated.
So +1 to add ExceptT and no opinion on other instances.
The proposed instance works ok, although maybe there is a way to implement it without throwing and immediately catching IO exceptions (it would also remove the need to derive Exception instance)? @parsonsmatt
@snoyberg
I wouldn't have thought of this, because I have a knee-jerk reaction to not mix explicit error returns and runtime exceptions.
That was my instinct as well until I had a use case to uniformly process (i.e. "mix") both the logical errors and run-time exceptions of dependencies...
@fumieval
If a user wants escape hatches, we should be using newtypes instead of adding them to the library.
It is possible, but that would undermine otherwise good ergonomics of unliftio
Also, considering ExceptT and StateT in the same question seems wrong - the arguments are different.
The instance from @lehin in https://github.com/fpco/unliftio/issues/68#issuecomment-727255763 looks to me as if it's using exceptions for controlling program flow. Say what you like about that, but it seems to work for me, the casual user. Could unliftio export a special exception type and handler, specifically for the purpose of writing MonadUnliftIO
instances, which is ignored by catchAny
et al?
-- edit: something like this:
newtype UnliftIOControlException e = UnliftIOControlException { unControlException :: e }
deriving Typeable
instance Show (UnliftIOControlException e) where
show _ = "Internal error in MonadUnliftIO instance"
instance Typeable e => Exception (UnliftIOControlException e)
At first I liked the idea of adding a MonadUnliftIO instance to ExceptT (using mapConcurrently
with types where logic errors are checked would be my favorite use case).
IIUC in @parsonsmatt 's implementation the instance would safeguard pure "exceptions" by first throwing them with throwIO
but immediately catching them and wrapping them with try
.
I don't understand why @lehins 's counterexample https://github.com/fpco/unliftio/issues/68#issuecomment-727255763 should point to a pathological behaviour : isn't the whole point of catchAny
to be a kitchen sink and transform all it catches into a pure value ? (https://hackage.haskell.org/package/unliftio-0.2.14/docs/UnliftIO-Exception.html#v:catchAny)
Edit : I don't understand all tradeoffs of adding this instance, but I think it has some merit.
StateT s IO
has one important benefit over IO
. It's much more efficient for keeping track of additional state in something like an expensive array computation. The StateT
variables can actually be stored in registers, whereas any IO
-based variables will be stored on the heap, and extra shenanigans are required to avoid boxing and concurrency-related overhead. That doesn't mean StateT s IO
should be an instance of MonadUnliftIO
, by any means, but it's something that often seems to be forgotten in these discussions. ExceptT e IO
is similarly beneficial in situations where the "exception" case is actually very common.
I've been needing the ExceptT instance whilst uprading some code to a new version of Persistent. The previous (working) code was
runDB :: AppSql a -> App a
runDB query = asks getPool >>= runSqlPool query
where App is Servant Handler (ExceptT IO under the hood). My work around was something similar (I believe) to the proposed instance but converting the ExceptT IO to a IO (Either ...) using coerce.
The final code looks like
runDB :: forall a . AppSQL a -> App a
runDB query = do
asks getPool >>= coerce . runSqlPool (query')
where query' = coerce query :: SqlPersistT (ReaderT Config IO) (Either ServerError a)
You can see the long story on reddit.
The point is I still don't know if it safe or not (and I reallyw would like to know) and there is a (not so) easy way to work around it by converting the ExceptT to Either; so not adding the instance doesnt' stop people to do it externally.
Finally, if it not safe, why and what is the way correct way to runSqlPool
within a SqlPersistT (ExcepT IO e)
.
@maxigit, the way you have done it is safe. The way proposed at the top of this discussion is a quite different way.
@tomjaguarpaw Then can my way be used to write the ExceptT instance ?
Finally, if it not safe, why and what is the way correct way to runSqlPool within a SqlPersistT (ExcepT IO e).
That depends on whether you want transactions to be rolled back on throwError
as well as throwIO
, or if you want throwError
to allow the transaction to complete.
If you want throwError
to rollback, then you should write something like this:
runDB action = do
pool <- asks sqlPool
flip runSqlPool pool $ coerce action >>= \case
Left err -> do
transactionUndo
pure (Left err)
Right a -> pure a
If you want throwError
to still allow transactions to commit (and only throwIO
to rollback), you can simply do runSqlPool (coerce action) pool
.
I would strongly recommend just using regular exceptions in IO
. I wrote a blog post on the technique. The tl;dr:
toExceptT :: (Exception e) => IO a -> ExceptT e IO a
toExceptT = ExceptT . try
fromExceptT :: (Exception e) => ExceptT e IO a -> IO a
fromExceptT = either throwIO pure . runExceptT
There is no benefit to a type like Handler
which has a "hidden" error channel in ExceptT
as well as another "hidden" error channel in IO
. The type would be strictly better if it were a simple newtype Handler a = Handler { unHandler :: IO a }
, with the runHandler = try . unHandler :: Handler a -> IO (Either ServerError a)
implementation. The only time you really want the MonadError
style of error handling is when you can perform introduction and elimination on the types of exceptions that you're dealing with.
Then can my way be used to write the ExceptT instance?
No, it can't. Your way isn't sufficient to write a MonadUnliftIO (ExceptT e)
instance in general, it's only a way to run runSqlPool
with the particular monad stack you have.
But @parsonsmatt makes an important point that eluded me: your way doesn't roll back the transaction on ExceptT
failure. Do you know whether that differs from the previous version of runSqlPool
(that used MonadBaseControl
)? If it doesn't differ, then your way is fine.
@parsonsmatt
That depends on whether you want transactions to be rolled back on throwError as well as throwIO, or if you want throwError to allow the transaction to complete.
That's a really good point. I just want the old behavior which I assume would rollback transaction on error, which is what you sugested.
@tomjaguarpaw
Do you know whether that differs from the previous version of runSqlPool
I always assumed it would rollback transaction but haven't actually checked or even experienced it. I might try to revert to the all code and test it.
@parsonsmatt
I think your point about transactionUndo
is a good reason why we shouldn't have an instance for ExceptT
. Had we have one, my code with runSqlPool
would have compiled without warning even thought It was incorrect.
Another variation of the same "IORef smuggling" hack from @parsonsmatt, now with WriterT
:
-- | HACK: UnliftIO doesn't legally allow the base @m@ to store mutable state.
-- But see https://github.com/fpco/unliftio/issues/68
instance MonadUnliftIO m => MonadUnliftIO (WriterT w m) where
withRunInIO writerToIO = WriterT $ do
leak <- newIORef []
out <- withRunInIO $ \runInIO ->
writerToIO $ \writerAction -> do
(ret, items) <- runInIO $ runWriterT writerAction
modifyIORef leak (items:) -- this do block is reentrant
pure ret
chunks <- readIORef leak
pure (out, concat (reverse chunks))
Mandatory warning:
We can Unlift your WriterT action, but it'll build up a huge data structure before you can observe any of it.
I hadn't rigorously checked this — it doesn't matter in my particular use-case, with bounded number of small writes into the Writer — but I'm readily convinced that it's true.
Exercise caution to avoid use in full generality.
This is probably Bad for reasons I haven't figured out yet, but it works.