<html>
  <head>
    <meta content="text/html; charset=UTF-8" http-equiv="Content-Type">
  </head>
  <body style="background-color: rgb(255, 255, 255); color: rgb(0, 0,
    0);" bgcolor="#FFFFFF" text="#000000">
    Hi Adam,<br>
    <br>
    Thanks a lot. Spent almost a day on the problem. Tried every
    possible combination, except forall.<br>
    <br>
    I read again about forall and now it is much more clear when I see
    it as a solution to my own problem.<br>
    <br>
    vlatko<br>
    <br>
    <br>
    <blockquote style="border-left: 2px solid #330033 !important;
      border-right: 2px solid #330033 !important; padding: 0px 15px 0px
      15px; margin: 8px 2px;"
cite="mid:CAHfjoWm7zEnj2g=1u0uPhSRP8E9awEaH8P=uV8a5WkDjDq58_w@mail.gmail.com"
      type="cite"><!--[if !IE]><DIV style="border-left: 2px solid #330033; border-right: 2px solid #330033;  padding: 0px 15px; margin: 2px 0px;"><![endif]--><span
        style="color:#000000;" class="headerSpan">
        <div class="moz-cite-prefix">-------- Original Message --------<br>
          Subject: Re: [Haskell-cafe] How to pass a polymorphic function
          in a record?<br>
          From: adam vogt <a class="moz-txt-link-rfc2396E" href="mailto:vogt.adam@gmail.com"><vogt.adam@gmail.com></a><br>
          To: <a class="moz-txt-link-abbreviated" href="mailto:vlatko.basic@gmail.com">vlatko.basic@gmail.com</a><br>
          Cc: haskell-cafe <a class="moz-txt-link-rfc2396E" href="mailto:haskell-cafe@haskell.org"><haskell-cafe@haskell.org></a><br>
          Date: 28.01.2014 21:47<br>
        </div>
        <br>
        <br>
      </span>
      <div dir="ltr">Hi Vlatko,<br>
        <br>
        Did you consider:<br>
        <br>
        {-# LANGUAGE RankNTypes #-}<br>
        data ThingCfg m = ThingCfg {<br>
            thingDb  :: Text,<br>
            thingRun_ :: forall a. Text -> m a -> IO a }<br>
        <br>
        thingRun (ThingCfg db f) = f db<br>
        <br>
        Maybe the `m' above should be SqlPersistM, if all your other
        backends use that type.<br>
        <br>
        --<br>
        Adam<br>
      </div>
      <div class="gmail_extra"><br>
        <br>
        <div class="gmail_quote">On Tue, Jan 28, 2014 at 1:37 PM, Vlatko
          Basic <span dir="ltr"><<a moz-do-not-send="true"
              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">Hello
            Cafe,<br>
            <br>
            I'm playing with Persistent and have modules that I'd like
            to use on several backends. This is simplified situation.<br>
            <br>
            In shared module:<br>
            <br>
              sqliteRun, postgresRun :: Text -> Int ->
            (ConnectionPool -> IO a) -> IO a<br>
              sqliteRun          = withSqlitePool<br>
              postgresRun conStr = withPostgresqlPool (encodeUtf8
            conStr)<br>
            <br>
              sqlRun :: Text -> Int -> SqlPersistM a -> IO a<br>
              sqlRun conStr poolSize = postgresRun conStr poolSize .
            runSqlPersistMPool<br>
              --sqlRun conStr poolSize = sqliteRun conStr poolSize .
            runSqlPersistMPool<br>
                    <br>
            All works well if either 'sqlRun' above is
            commented/uncommented:<br>
            <br>
            <br>
            In one of modules:<br>
            <br>
              data ThingCfg = ThingCfg { thingDb :: Text }<br>
            <br>
              listThings :: ThingCfg -> IO [Thing]<br>
              listThings db = sqlRun (thingDb db) $ selectList ...<br>
                    <br>
              findThing :: ThingId -> ThingCfg -> IO (Maybe Thing)<br>
              findThing uid db = sqlRun (thingDb db) $ getBy ...<br>
            <br>
            <br>
            <br>
            On call site simply:<br>
              let tdb = ThingCfg "test"<br>
              ts <- listThings tdb<br>
            <br>
            <br>
            I would like to specify 'sqliteRun' or 'postgresRun'
            function as (some) parameter on the call site, but do not
            know how.<br>
            Something of imaginary solution:<br>
            <br>
              data ThingCfg = ThingCfg {<br>
                  thingDb  :: Text,<br>
                  thingRun :: SqlPersistM a -> IO a<br>
                }<br>
            <br>
            On call site:<br>
              let tdb = ThingCfg "test" sqliteRun<br>
              ts <- listThings tdb<br>
            <br>
            I want to keep it as an init param because there are other
            backends (class instances) that are not Persistent, so the
            use of 'sqlRun' on call site is not an option.<br>
            <br>
            <br>
            What would be the best/correct way(s) to achieve that?<br>
            <br>
            <br>
            Best regards,<br>
              Vlatko<br>
            _______________________________________________<br>
            Haskell-Cafe mailing list<br>
            <a moz-do-not-send="true"
              href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
            <a moz-do-not-send="true"
              href="http://www.haskell.org/mailman/listinfo/haskell-cafe"
              target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
          </blockquote>
        </div>
        <br>
      </div>
      <!--[if !IE]></DIV><![endif]--></blockquote>
    <br>
  </body>
</html>