<div dir="ltr">Hi Vlatko,<div><br></div><div>It depends on what you want to happen. The easiest way is to use the runtime exception system and `try` to catch the type of exception you want to handle:<br><br><font face="monospace, monospace">tryApp :: (MonadCatch m) => m a -> m (Either AppException a)<br>tryApp = try</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">runDB :: (MonadIO m, MonadCatch m) => SqlPersistT m a -> AppM m (Either AppException a)<br>runDB query = do<br>  App{..} <- ask<br>  liftIO $ tryApp $ runPool pgConf query pgPool<br><br>f1 :: (MonadThrow m) => SqlPersistT m Bool<br>f1 = throwM (ExcTest "Exception!")</font></div><div><font face="monospace, monospace"><br>runF1 :: (MonadIO m, MonadCatch m) => AppM m (Either AppException Bool)</font></div><div><font face="monospace, monospace">runF1 = runDB f1</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="arial, helvetica, sans-serif">This approach preserves the transaction rollback feature of `persistent`. If you do not want to have that feature, then you can put `ExceptT` on the outside, like `ExceptT AppException (SqlPersistT m) a`, and this will give you short-circuiting (via the outer ExceptT layer).</font></div><div><br></div></div><div class="gmail_extra"><br clear="all"><div><div class="gmail_signature" data-smartmail="gmail_signature"><div dir="ltr"><div>Matt Parsons</div></div></div></div>
<br><div class="gmail_quote">On Mon, Jul 16, 2018 at 2:18 AM, Vlatko Basic <span dir="ltr"><<a href="mailto:vlatko.basic@gmail.com" target="_blank">vlatko.basic@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
  
    
    
  
  <div style="background-color:rgb(255,255,255);color:rgb(0,0,0)" text="#000000" bgcolor="#FFFFFF">
    Hi Matt,<br>
    <br>
    Thanks for taking time and giving so thorough explanation and a
    suggestion. Much appreciated. :-)<br>
    <br>
    I figured out some of this, except for the last, main part. I
    thought the problem was in not being able to instantiate MonadError
    AppException IO, not that ExceptT doesn't have MonadUnliftIO. <br>
    <br>
    I'm refactoring some db code and was just exploring possible
    short-circuiting ways in SqlPersistT with custom exception types,
    like get404. <br>
    Which approach would you suggest for that?<span class="HOEnZb"><font color="#888888"><br>
    <br>
    <br>
    <br>
    vlatko</font></span><div><div class="h5"><br>
    <br>
    <blockquote type="cite" style="border-left:2px solid #330033!important;border-right:2px solid #330033!important;padding:0px 15px 0px 15px;margin:8px 2px"><span class="m_3754725405212285428headerSpan" style="color:#000000">
        <div class="m_3754725405212285428moz-cite-prefix">-------- Original Message --------<br>
          Subject: Re: [Haskell-cafe] SqlPersistT action in MonadError
          issue<br>
          From: Matt <a class="m_3754725405212285428moz-txt-link-rfc2396E" href="mailto:parsonsmatt@gmail.com" target="_blank"><parsonsmatt@gmail.com></a><br>
          To: <a class="m_3754725405212285428moz-txt-link-abbreviated" href="mailto:vlatko.basic@gmail.com" target="_blank">vlatko.basic@gmail.com</a><br>
          Cc: haskell-cafe <a class="m_3754725405212285428moz-txt-link-rfc2396E" href="mailto:Haskell-cafe@haskell.org" target="_blank"><Haskell-cafe@haskell.org></a><br>
          Date: 14/07/18 20:09<br>
        </div>
        <br>
        <br>
      </span>
      
      <div dir="ltr">The type of `runPool` is given here: <a href="https://www.stackage.org/haddock/lts-12.0/persistent-2.8.2/Database-Persist-Class.html#v:runPool" target="_blank">https://www.stackage.<wbr>org/haddock/lts-12.0/<wbr>persistent-2.8.2/Database-<wbr>Persist-Class.html#v:runPool</a>
        <div><br>
        </div>
        <div>    <a class="m_3754725405212285428gmail-def" id="m_3754725405212285428gmail-v:runPool" style="margin:0px;padding:0px;text-decoration:none;font-weight:bold;background-color:rgb(255,255,0);color:rgb(0,0,0);font-family:monospace;font-size:14px;text-align:left">runPool</a><span style="color:rgb(0,0,0);font-family:monospace;font-size:14px;text-align:left;background-color:rgb(240,240,240);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><span> </span>::<span> </span></span><a href="https://www.stackage.org/haddock/lts-12.0/conduit-1.3.0.3/Conduit.html#t:MonadUnliftIO" title="Conduit" style="margin:0px;padding:0px;text-decoration:none;font-weight:bold;color:rgb(171,105,84);font-family:monospace;font-size:14px;text-align:left" target="_blank">MonadUnliftIO</a><span style="color:rgb(0,0,0);font-family:monospace;font-size:14px;text-align:left;background-color:rgb(240,240,240);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><span> </span>m
            => c -><span> </span></span><a href="https://www.stackage.org/haddock/lts-12.0/persistent-2.8.2/Database-Persist-Class.html#t:PersistConfigBackend" title="Database.Persist.Class" style="margin:0px;padding:0px;text-decoration:none;font-weight:bold;color:rgb(171,105,84);font-family:monospace;font-size:14px;text-align:left" target="_blank">PersistConfigBackend</a><span style="color:rgb(0,0,0);font-family:monospace;font-size:14px;text-align:left;background-color:rgb(240,240,240);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><span> </span>c
            m a -><span> </span></span><a href="https://www.stackage.org/haddock/lts-12.0/persistent-2.8.2/Database-Persist-Class.html#t:PersistConfigPool" title="Database.Persist.Class" style="margin:0px;padding:0px;text-decoration:none;font-weight:bold;color:rgb(171,105,84);font-family:monospace;font-size:14px;text-align:left" target="_blank">PersistConfigPool</a><span style="color:rgb(0,0,0);font-family:monospace;font-size:14px;text-align:left;background-color:rgb(240,240,240);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><span> </span>c
            -> m a</span></div>
        <div><span style="color:rgb(0,0,0);font-family:monospace;font-size:14px;text-align:left;background-color:rgb(240,240,240);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><br>
          </span></div>
        <div><span style="font-size:small;background-color:rgb(255,255,255);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline">The
            return type of `runPool`, then, is `m a`, for some `m`
            satisfying `MonadUnliftIO`.</span><br>
        </div>
        <div><span style="font-size:small;background-color:rgb(255,255,255);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><br>
          </span></div>
        <div><span style="font-size:small;background-color:rgb(255,255,255);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline">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`.</span></div>
        <div><span style="font-size:small;background-color:rgb(255,255,255);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><br>
          </span></div>
        <div><span style="font-size:small;background-color:rgb(255,255,255);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline">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`.</span></div>
        <div><span style="font-size:small;background-color:rgb(255,255,255);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline"><br>
          </span></div>
        <div><span style="font-size:small;background-color:rgb(255,255,255);text-decoration-style:initial;text-decoration-color:initial;float:none;display:inline">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.</span></div>
        <div><br>
        </div>
        <div>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:</div>
        <div><br>
        </div>
        <div><font face="monospace, monospace">pushException ::
            SqlPersistT (ExceptT e m) a -> SqlPersistT m (Either e a)</font></div>
        <div><font face="monospace, monospace">pushException =
            mapReaderT runExceptT</font></div>
        <div><br>
        </div>
        <div><br>
        </div>
        <div>Now, we can write:</div>
        <div><br>
        </div>
        <div>
          <div style="font-size:small;text-decoration-style:initial;text-decoration-color:initial"><font face="monospace, monospace">liftIO $ runPool pgConf
              (pushException f1) pgPool</font></div>
          <div style="font-size:small;text-decoration-style:initial;text-decoration-color:initial"><br>
          </div>
          <div style="font-size:small;text-decoration-style:initial;text-decoration-color:initial">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.</div>
          <div style="font-size:small;text-decoration-style:initial;text-decoration-color:initial"><br>
          </div>
          <div style="font-size:small;text-decoration-style:initial;text-decoration-color:initial">---</div>
          <div style="font-size:small;text-decoration-style:initial;text-decoration-color:initial"><br>
          </div>
          <div style="font-size:small;text-decoration-style:initial;text-decoration-color:initial">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.</div>
          <br>
        </div>
      </div>
      <div class="gmail_extra"><br clear="all">
        <div>
          <div class="m_3754725405212285428gmail_signature" data-smartmail="gmail_signature">
            <div dir="ltr">
              <div>Matt Parsons</div>
            </div>
          </div>
        </div>
        <br>
        <div class="gmail_quote">On Sat, Jul 14, 2018 at 10:22 AM,
          Vlatko Basic <span dir="ltr"><<a href="mailto:vlatko.basic@gmail.com" target="_blank">vlatko.basic@gmail.com</a>></span>
          wrote:<br>
          <blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
            <div style="background-color:rgb(255,255,255);color:rgb(0,0,0)" text="#000000" bgcolor="#FFFFFF">
              <p>Hello,</p>
              <p>I'm trying to use SqlPersistT funcs with MonadError,
                but am failing in writing the runDB correctly. <br>
              </p>
              <p>I tried several things, but always getting:</p>
              <p>    • Couldn't match type ‘IOException’ with
                ‘AppException’<br>
                        arising from a functional dependency between:<br>
                          constraint ‘MonadError AppException IO’
                arising from a use of ‘f1’<br>
                          instance ‘MonadError IOException IO’ at <no
                location info><br>
                    • In the second argument of ‘runPool’, namely ‘f1’<br>
                      In the second argument of ‘($)’, namely ‘runPool
                pgConf f1 pgPool’<br>
                      In a stmt of a 'do' block: liftIO $ runPool pgConf
                f1 pgPool</p>
              I understand there already is "instance MonadError
              IOException IO" and fundep says it can be only one for IO.
              <p>How to make it compile?</p>
              <br>
              <p>Best regards,</p>
              <p>vlatko</p>
              <p>    <br>
              </p>
              <p>Here is the minimal reproducible code:<br>
              </p>
              <font size="-1"><tt>module Test where</tt><tt><br>
                </tt><tt><br>
                </tt><tt>import Prelude</tt><tt><br>
                </tt><tt>import Control.Exception.Base</tt><tt><br>
                </tt><tt>import Control.Monad.Except</tt><tt><br>
                </tt><tt>import Control.Monad.Trans.Reader</tt><tt><br>
                </tt><tt>import Database.Persist.Postgresql</tt><tt><br>
                </tt><tt><br>
                </tt><tt>data AppException =</tt><tt><br>
                </tt><tt>    ExcText String</tt><tt><br>
                </tt><tt>  | ExcIO IOException</tt><tt><br>
                </tt><tt>  deriving (Show)</tt><tt><br>
                </tt><tt><br>
                </tt><tt>type AppM m = ExceptT AppException (ReaderT App
                  m)</tt><tt><br>
                </tt><tt>data App    = App { pgConf :: PostgresConf,
                  pgPool :: ConnectionPool}</tt><tt><br>
                </tt><tt><br>
                </tt><tt>runDB :: (MonadIO m, MonadError AppException m)
                  => AppM m Bool<br>
                </tt><tt>runDB = do</tt><tt><br>
                </tt><tt>  App{..} <- lift ask</tt><tt><br>
                </tt><tt>  liftIO $ runPool pgConf <b>f1</b> pgPool   
                  -- error</tt><tt><br>
                </tt><tt>  -- liftIO $ runPool pgConf <b>f2</b> pgPool 
                  -- OK</tt><tt><br>
                </tt><tt><br>
                </tt><tt><br>
                </tt><tt>f1 :: (MonadIO m, MonadError AppException m)
                  => SqlPersistT m Bool</tt><tt><br>
                </tt><tt>f1 = throwError $ ExcText "exception"</tt><tt><br>
                </tt><tt><br>
                </tt><tt>f2 :: MonadIO m => SqlPersistT m Bool</tt><tt><br>
                </tt><tt>f2 = return True</tt></font><br>
              <br>
            </div>
            <br>
            ______________________________<wbr>_________________<br>
            Haskell-Cafe mailing list<br>
            To (un)subscribe, modify options or view archives go to:<br>
            <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/haskell-caf<wbr>e</a><br>
            Only members subscribed via the mailman list are allowed to
            post.<br>
          </blockquote>
        </div>
        <br>
      </div>
      </blockquote>
    <br>
  </div></div></div>

</blockquote></div><br></div>