[Haskell-cafe] SqlPersistT action in MonadError issue

Vlatko Basic vlatko.basic at gmail.com
Sat Jul 14 16:22:39 UTC 2018


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

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180714/6d422dbf/attachment.html>


More information about the Haskell-Cafe mailing list