The type of `runPool` is given here: https://www.stackage.org/haddock/lts-12.0/persistent-2.8.2/Database-Persist-Class.html#v:runPool

    runPool :: MonadUnliftIO m => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a

The return type of `runPool`, then, is `m a`, for some `m` satisfying `MonadUnliftIO`.

The type of `liftIO` is `liftIO :: (MonadIO m) => IO a -> m a`. This means that the first argument to `liftIO` must be an `IO a`.

When we say `liftIO (runPool ...)`, GHC tries to unify the `m a` from `runPool` and the `IO a` from `liftIO`. It is able to do this, as `IO` is an instance of `MonadUnliftIO`. Then, the concrete type of `runPool pgConf f1 pgPool` becomes `IO Bool`.

GHC now tries to unify the `m` in `f1 :: (MonadIO m, MonadError AppException m) => SqlPersistT m Bool` with `IO`. It tries to satisfy the constraints: `MonadIO` is easily satisfied, but `MonadError AppException m` triggers the problem you mention.

Because `ExceptT` does not have an instance for `MonadUnliftIO`, we cannot use it with the `m` in `SqlPersistT m Bool` directly. We can, instead, use `mapReaderT` to push the `Either` into the return type, like this:

pushException :: SqlPersistT (ExceptT e m) a -> SqlPersistT m (Either e a)
pushException = mapReaderT runExceptT


Now, we can write:

liftIO $ runPool pgConf (pushException f1) pgPool

This gives us an `IO (Either AppException Bool)`, which, after lifting, gives us `AppM IO (Either AppException Bool)`. You can then use `either throwError pure` to pull the `AppException` into the `ExceptT` again.

---

I would suggest that you reconsider this approach, however. The `persistent` library uses transactions and exceptions in a way that is *almost always* what you want, but can be surprising, and using `ExceptT` will break this system. Transactions are automatically rolled back on a `MonadCatch`-style exception, but they are not automatically rolled back on an `ExceptT`-style exception. Having a single `AppException` type that represents errors that can occur in database transactions *and* the rest of your application is also going to be a cause for unsafety and errors, as the type cannot possibly be precise enough to provide any safety.


Matt Parsons

On Sat, Jul 14, 2018 at 10:22 AM, Vlatko Basic <vlatko.basic@gmail.com> wrote:

Hello,

I'm trying to use SqlPersistT funcs with MonadError, but am failing in writing the runDB correctly.

I tried several things, but always getting:

    • Couldn't match type ‘IOException’ with ‘AppException’
        arising from a functional dependency between:
          constraint ‘MonadError AppException IO’ arising from a use of ‘f1’
          instance ‘MonadError IOException IO’ at <no location info>
    • In the second argument of ‘runPool’, namely ‘f1’
      In the second argument of ‘($)’, namely ‘runPool pgConf f1 pgPool’
      In a stmt of a 'do' block: liftIO $ runPool pgConf f1 pgPool

I understand there already is "instance MonadError IOException IO" and fundep says it can be only one for IO.

How to make it compile?


Best regards,

vlatko

   

Here is the minimal reproducible code:

module Test where

import Prelude
import Control.Exception.Base
import Control.Monad.Except
import Control.Monad.Trans.Reader
import Database.Persist.Postgresql

data AppException =
    ExcText String
  | ExcIO IOException
  deriving (Show)

type AppM m = ExceptT AppException (ReaderT App m)
data App    = App { pgConf :: PostgresConf, pgPool :: ConnectionPool}

runDB :: (MonadIO m, MonadError AppException m) => AppM m Bool
runDB = do
  App{..} <- lift ask
  liftIO $ runPool pgConf f1 pgPool    -- error
  -- liftIO $ runPool pgConf f2 pgPool  -- OK


f1 :: (MonadIO m, MonadError AppException m) => SqlPersistT m Bool
f1 = throwError $ ExcText "exception"

f2 :: MonadIO m => SqlPersistT m Bool
f2 = return True



_______________________________________________
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.