yesodweb / yesod

A RESTful Haskell web framework built on WAI.
http://www.yesodweb.com/
MIT License
2.64k stars 374 forks source link

MonadCatch, MonadMask instances for HandlerFor #1533

Open ocharles opened 6 years ago

ocharles commented 6 years ago

I know that Yesod now prefers unliftio, but there are valid instances that can be written for MonadCatch and MonadMask (I believe this follows from HandlerFor being isomorphic to ReaderT). Would you be open to having those instances?

snoyberg commented 6 years ago

What's the motivating use case for this? I've been on the fence about such instances in a few libraries now.

ocharles commented 6 years ago

Mostly a lot of existing code that uses MonadError in a few places, which we instantiate with ExceptT to fulfill that. It's hard to provide the exact code that causes it, but I think it's the interaction of the following two functions (this is the old code):

-- | Helper to handle failure in n handler in a consistent manner.
--
--   On failure a "badRequest400" status is returned with the error message
--   returned as a "FailureResponse". Only failures tagged as public, "FailurePublic"
--   form part of the error message. All the failures, both public and private, are logged as an
--   error.
--
--
handleFailure
  :: forall e em m a r. (MonadHandler m, MonadLogger m, ToJSON em, ToFailureMessage em, ToTypedContent r)
  => Text -- ^ The location used in the error message log
  -> (e -> em) -- ^ Convert the failure error types that have a "ToJSON" and "ToFailureMessage" types
  -> (a -> r) -- ^ Convert the resultant value of the handler to a "ToTypedContent"
  -> ExceptT [Failure e] m a -- ^ Run the handler wrapped in an ExceptT that can fail with "Failure e"
  -> m r
handleFailure loc_ printe_ mkResp_ act_ = do
  eresult <- runExceptT act_
  case eresult of
    Left e -> do
      logErrorNS loc_ (printErrors e)
      sendStatusJSON
        badRequest400
        (toJSON (toError . filter keepPublicFailure $ e))
    Right a -> pure (mkResp_ a)
  where
    printErrors = T.unlines . map (toFailureMessage . printe_ . extractFailure)
    toError :: [Failure e] -> FailureResponse em
    toError [] =
        FailureResponse
        {failureResponseError = "unknown error occurred"
        ,failureResponseAllErrors = []
        }
    toError es =
        FailureResponse
        {failureResponseError = printErrors es
        ,failureResponseAllErrors = map (printe_ . extractFailure) es
        }
    keepPublicFailure (FailurePrivate _) = False
    keepPublicFailure (FailurePublic _) = True

And

-- | Version of "constraintViolationToFailure" explicitly generating a list of failures
constraintViolationToFailure'
  :: (MonadBaseControl IO m, MonadCatch m, MonadError [Failure e] m)
  => (ed -> [Failure e]) -- ^ Convert the transaction abort reason e.g. "FailurePublic . asText" or "neverAborts"
  -> (ConstraintViolation -> [Failure e]) -- ^ Convert the constraint violation e.g. "FailurePublic . tshow"
  -> m (Either ed a) -- ^ The transaction that could fail or abort
  -> m a
constraintViolationToFailure' abortToFailure constraintToFailure m =
  catchJust
    constraintViolation
    (first abortToFailure <$> m)
    (pure . Left .  constraintToFailure) >>=
  either throwError pure

This is used as:

postLocationsR :: Foo -> Handler Value
postLocationsR _ =
  handleFailure "postLocationsR" asText (const $ toJSON Res.Success) $
  do ReqM.NewLocation {..} <- requireJsonBodyFail
     constraintViolationToFailure neverAborts (FailurePublic . tshow) $ runSerializableTransaction $
       void $
       insert ...

Note that constraintViolationToFailure uses MonadCatch, but I no longer have a MonadCatch instance for Hantdler. I can't use MonadUnliftIO though, because ExceptT isn't (and can't) be an instance of it. So right, now I'm stuck having to rewrite a lot of code. If you don't want these instances in yesod-core that's fine, we'll probably just add them as orphans - but it would certainly be nice to have them upstream.

Are you on the fence due to dependency concerns, or correctness concerns?

ocharles commented 6 years ago

I should note that we're in this situation as we need to update our package set for other reasons, but with 300+ modules doing a large refactor at the same time is unfortunately more work than we have time for at the moment. I appreciate that's not a great reason to add things to an upstream library (your inconvenience for our convenience), but I do think these instances are popular enough to be useful.

snoyberg commented 6 years ago

Are you on the fence due to dependency concerns, or correctness concerns?

Definitely correctness, exceptions is already a dependency of this library. Your use case actually demonstrates why I'm hesitant about adding these instances: I want users in general to get compilation errors when throwing ExceptT into the mix, as IME it more often than not causes problems. I think a good compromise solution here is to have an official orphans package that provides these instances, together with an explanation of why they could be a problem.

ocharles commented 6 years ago

Is ExceptT problematic in exceptions-0.10 though? I read the source for generalBracket for the MonadMask ExceptT instance, and I agree with what it's doing (it all seems reasonable to me). Do you think that 0.10 is still problematic?

snoyberg commented 6 years ago

Yes, it's inherent to ExceptT, not the implementation in exceptions. This is about my general advice against ExceptT over IO and confusion about where exceptions are thrown/caught.

ocharles commented 6 years ago

Is there anything I can read? I watched your "Everything You Don't Want To Know About Monad Transformer State" video yesterday (great talk!), but the story has changed since then. There is now afaik no discarding in generalBracket for ExceptT or StateT, so if there is still something problematic it'd be great to understand what that is.

snoyberg commented 6 years ago

There is definitely discarding in StateT, it's inherent to the transformer. For example:

try $ put newVal >> throwIO someExcVal

There's no change to the definition of try that can allow newVal to survive, it has to be handled with mutable variables. For ExceptT, the multiple error reporting mechanisms are inherent, and cannot be worked around at the exceptions library level.

ocharles commented 6 years ago

Oh right, though I agree with what is happening with StateT there, but I can see it could be subtle. However, I don't see an example of an ExceptT subtlety. The linked blog posts talk about things like ExceptT IO suggesting there is only one sort of exception at play, but exceptions-0.10 now seems to deal with that (e.g., things like finally do actually fire on any non-successful termination, not just an actual exception). Essentially, your points in https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell seem to be more about style rather than correctness - which is fine - but I'm trying to see if there is anything truly surprising.

Is there any other one liner that you think might be convincing? Let's leave out concurrency of this matter, and focus just on the space provided by exceptions (I agree with your concurrency examples that it becomes confusing here).

Sorry this is slightly off topic, and I know you probably feel like you've been over this a thousand times! I appreciate the discussion.

snoyberg commented 6 years ago

I doubt there's any one-liner I can provide that will be convincing. There's legitimate disagreement in the community about this topic. But I've seen enough broken code out there by people making assumptions about how code may behave that I stand strongly by this one. The basic idea is that, in many cases, people view a value of type ExceptT MyException IO Result as "it performs some IO, and then is guaranteed to return Either MyException Result." I've received bug reports about this kind of thing in the past. The assumption is simply false: IO can fail with any exception type, either synchronously or asynchronously.

I know some people are unconvinced by me on this, which is fine. But I remain strongly convinced that ExceptT over IO is an anti-pattern, and want to advocate against its usage. Notwithstanding the fact that:

ocharles commented 6 years ago

Ok, so you're on the fence here because you obviously have a ton of downstream users, and you can't really control what they do, and you'd rather err on the side of caution. That's fair enough. I'm probably in the disagree camp, but this has given me a lot of food for thought, and I'm less certain in my own view point now. I'll think on this.

Back to the topic at hand though, is there a disadvantage with having the instances in this library? Orphans are a mess, and I think if we were going to do that, I'd rather we just say "define the instances yourself" and consider this exceptional (ha!). All your exception handling is done with unliftio anyway, so the use of things wouldn't "leak" into Yesod code - right?

snoyberg commented 6 years ago

is there a disadvantage with having the instances in this library?

That's where I'm really on the fence. It doesn't make any existing code worse to add the instances. What it does do is make it easier to follow anti-patterns. Using the StateT example: if I added a MonadMask instance for HandlerFor to yesod-core, someone could inadvertently use try together with StateT SomeState Handler and experience state-loss behavior. As it stands now, that would be a compilation error. The case is definitely stronger for avoiding MonadBaseControl instances, where IMO totally broken libraries like lifted-base and lifted-async exist, which is why I remain on the fence on this one.

FWIW: prior art is here (https://github.com/commercialhaskell/rio/issues/38), where we ended up with a rio-orphans library.

ocharles commented 6 years ago

I agree that lifted-async is broken, I'm trying to rip that out of anything I use that depends on it now.

Maybe let's keep this open and see if others have thoughts? Happy to experiment with orphans in my own code and see how that works out.

ocharles commented 6 years ago

Thinking about this a little more, the reason we end up with ExceptT is because we need a "disposable" handler for MonadError, which we tend to prefer over untyped MonadThrow. However, if we know that we have MonadThrow and MonadCatch as a base, then we can satisfy MonadError via MonadThrow and MonadCatch:

newtype Thrown a = Thrown { unThrown :: a }

instance Show ( Thrown a ) where
  show _ = "<Thrown>"

instance ( Typeable a ) => Exception ( Thrown a )

newtype MapErrorT e m a = MapErrorT { unMapErrorT :: m a }
  deriving ( Functor, Applicative, Monad, MonadIO, MonadThrow, MonadCatch, MonadMask, MonadLogger )

instance MonadUnliftIO m => MonadUnliftIO (MapErrorT e m) where
  askUnliftIO = do
    UnliftIO f <- lift askUnliftIO
    return (UnliftIO (f . unMapErrorT))

instance MonadTrans ( MapErrorT e ) where
  lift = MapErrorT

instance MonadReader r m => MonadReader r ( MapErrorT e m ) where
  ask = lift ask
  local f (MapErrorT m) =
    MapErrorT (local f m)

instance MonadLog msg m => MonadLog msg (MapErrorT e m) where

instance ( Typeable e, MonadCatch m ) => MonadError e (MapErrorT e m) where
  throwError =
    MapErrorT . throwM . Thrown 

  catchError m f =
    MapErrorT ( try ( unMapErrorT m ) ) >>= either ( f . unThrown ) return

mapError :: ( MonadCatch m, MonadError e' m, Typeable e ) => (e -> e') -> MapErrorT e m a -> m a
mapError f = try . unMapErrorT >=> either ( throwError . f . unThrown ) return

With this, I have the ability to eliminate a MonadError constraint with MapErrorT. This also gives us mapError to "map" over MonadError. All of this is done via the underlying MonadCatch/MonadThrow instances.

What's even cooler is this still generalises to pure code! Just drop in CatchT as a handler for MonadCatch and MonadThrow. Of course if you also need MonadUnliftIO then you can't use the pure case, but this (for us) pushes MonadUnliftIO to code that needs to fork threads.

So, with the above I do still need MonadCatch and MonadThrow in order to use MonadError over HandlerFor, but it doesn't have the iffyness of ExceptT.

Sorry that's a bit rambly, maybe something there makes sense :)

timbess commented 2 years ago

This is a good discussion. Just my 2 cents, but IMO ExceptT MyErr IO a makes perfect sense if you think of ExceptT as a checked exception and IO as an unchecked exception. So for me, ExceptT is documentation of all the known ways it can fail, whereas async exceptions are things I'd expect to kill the program. I personally don't get the impression that ExceptT means there's no other way for it to fail, but more that these are domain errors that could be reasonably handled by a higher level function. I believe it's pretty clear that IO can fail at any time for any reason and blow up your app, so if ExceptT is wrapping it, we still inherits that behavior.

For example, servant has Handler that's a newtype over ExceptT ServerError IO a. So, by looking at this, I can tell that either:

  1. It will succeed with an a.
  2. Fail with some HTTP status error.
  3. Fail with some misc IO exception.

The nice thing about having 2 is that I can see at a glance the ways it can fail and easily add a handler that pattern matches and handles 404, 500, etc. in different ways. With an opaque IO, I have to dig through docs and try to see all the variety of ways it can fail manually, or just trigger all the different failure states manually and see what happens.

lf- commented 1 year ago

Hi! I'm hitting this today with some work code: we have some ExceptT Something (HandlerFor site) function, which I would like to use hs-opentelemetry instrumentation inside, but that is currently not possible without one of these two instances. I concur that ExceptT IO is a bad idea, but someone had the bad idea a long time ago.

There is no MonadUnliftIO (ExceptT m) instance, so I cannot use inSpan (which needs unliftio to catch exceptions thrown inside the span): https://github.com/fpco/unliftio/issues/68

Since there's no MonadMask (HandlerFor site) instance, I can't use inSpanM either, as introduced here: https://github.com/iand675/hs-opentelemetry/issues/20

parsonsmatt commented 1 year ago

I think the issues of allowing/promoting ExceptT _ IO _ and MonadThrow and MonadMask are orthogonal.

MonadThrow is more useful than a boilerplate alias for liftIO . throwIO. It also allows you to customize how the exception is thrown.

For example, consider annotated-exception:

instance MonadThrow App where
    throwM = throwWithCallStack

Or, consider a special exception wrapper type that indicates "this came from my code":

instance MonadThrow App where
   throwM = throwWithCallStack . wrapAppException

Or, consider how you can define MonadCatch to use safe-exceptions or unliftio, gaining async exception safety:

instance MonadCatch App where
    catch = UnliftIO.catch

The above case would also apply to using UnliftIO.bracket or similar when defining generalBracket, allowing you to have uninterruptible cleanup in finalizers.