Reputation: 5294
I have a Servant app and an endpoint that creates a record in a database, then attempts to copy a file between S3 locations. If the copy fails, I want to roll back the transaction. I have this operator
{-# LANGUAGE TemplateHaskell #-}
import Control.Monad.Catch
import Control.Monad.Except
import Control.Monad.Logger
(<??)
:: (MonadError e m, MonadCatch m, MonadLogger m)
=> e
-> m a
-> m a
(<??) err a = a `catchAll` (\e -> $(logErrorSH) e >> throwError err)
infixr 0 <??
that catches all exceptions, logs the nature of the exception, and then throws (in my case, since my App
type has an instance of MonadError ServantErr
) a ServantErr
.
My handler is something like this:
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Monad
import Control.Monad.Catch
import Control.Monad.IO.Class
import qualified Network.AWS as AWS
import Servant
import App.Types
import App.Db
copy :: Copy -> App Text
copy (Copy user bucket srcKey tgtKey) = do
err400 <?? runDb (insertRecord $ User user bucket srcKey tgtKey)
catch (err500 <?? liftIO $ do
env <- AWS.newEnv AWS.Discover
void . AWS.runResourceT . AWS.runAWS env $ copyFiles bucket srcKey tgtKey
return "OK") (\(e :: ServantErr) -> rollback e user)
where rollback e u = runDb (deleteRecord u) >> throwError e
To test the logic, I moved my AWS credentials file, expecting that the inner AWS action would throw an InvalidFileError
, then (<??)
would convert it to a ServantErr
, then catch
would catch this ServantErr
and enact the rollback function. What happens instead is that the insert succeeds, the InvalidFileError
is logged, but then the rollback never occurs (i.e., the record still exists in the database after execution). This deleteRecord
function is used elsewhere successfully, so I can be sure it's not an issue with its definition.
Any idea what could be causing this?
Upvotes: 2
Views: 279
Reputation: 27766
If your App
type is ultimately an ExceptT
, the problem could be that the MonadError
and MonadCatch
instances for ExceptT
are mismatched:
MonadError
instance throws errors as the e
in ExceptT e
MonadCatch
intance catches exceptions in the underlying monad, not ExceptT e
errors. The instance definition for MonadCatch (ExceptT e m)
is:
-- | Catches exceptions from the base monad.
instance MonadCatch m => MonadCatch (ExceptT e m) where
catch (ExceptT m) f = ExceptT $ catch m (runExceptT . f)
ServantErr
has an Exception
instance, so it can be thrown as both.
Edit: The "exceptions" class MonadMask
provides the onError
function, that even for ExceptT
is quite well-behaved: it runs the cleanup action both in the case of ExceptT e
exceptions and regular exceptions:
Run an action only if an error is thrown in the main action. Unlike onException, this works with every kind of error, not just exceptions. For example, if f is an ExceptT computation which aborts with a Left, the computation onError f g will execute g, while onException f g will not.
It is a better option than catch
for handling the rollback.
Upvotes: 6