<html>
  <head>
    <meta content="text/html; charset=windows-1252"
      http-equiv="Content-Type">
  </head>
  <body text="#000000" bgcolor="#FFFFFF">
    I used typeclasses because I want to have a "default version" of the
    run function.<br>
    <br>
    I want that function to be able to call (specialized versions) of
    the other functions in the group. This is the only way *I know* to
    "factor out" common code in Haskell while still allowing the
    "factored out" code to call specialized versions of the other
    functions. In my view, this is very similar to inheritance and
    specialization is Object-Oriented Programming. Is there another way
    to do this?<br>
    <br>
    I don't see how I could do this with a record. If the run function
    were mostly the same for all types except for calls to specialized
    versions of the others. I think I would have to write a completely
    separate version of run for each instance. The example below shows
    what I mean.<br>
    <br>
    Also, my apologies, but my code was wrong. I now realize it did not
    capture what I need. I don't need the functions to be polymorphic
    for all types within a single instance. Within a single instance, I
    just need them to work for a few specific types. So, here's a better
    version (my current one):<br>
    <br>
    {-# LANGUAGE MultiParamTypeClasses #-}<br>
    {-# LANGUAGE TypeFamilies #-}<br>
    <br>
    import Control.Monad <br>
    <br>
    class Reliable m s where<br>
    <br>
        type Req s :: *     -- the type for requests<br>
        type Atp s :: *     -- the type for attempts<br>
        type Ack s :: *     -- the type for acknowledgments<br>
        type Res s :: *     -- the type for results (Success)<br>
        type Fai s :: *     -- the type for failures<br>
    <br>
        getRequests :: Monad m => s                   -> m [Req s]<br>
        mkAttempt   :: Monad m => s -> Req s          -> m
    (Maybe (Atp s))<br>
        action      :: Monad m => s -> Atp s          -> m
    (Maybe (Ack s)) <br>
        getAcks     :: Monad m => s ->[Atp s]         -> m [Ack
    s]       <br>
        mkResult    :: Monad m => s -> Req s -> Ack s -> m
    (Either (Fai s) (Res s))<br>
        run         :: Monad m => s -> Req s          -> m (Res
    s)<br>
    <br>
    <br>
    data RemoteCall = RemoteCall<br>
    <br>
    instance Reliable IO RemoteCall where<br>
    <br>
        type Req RemoteCall = Int<br>
        type Atp RemoteCall = String<br>
        type Ack RemoteCall = Bool<br>
        type Res RemoteCall = String<br>
        type Fai RemoteCall = Int<br>
    <br>
        getRequests = undefined  -- these can be specialized for each
    instance<br>
        mkAttempt   = undefined<br>
        action      = undefined<br>
        getAcks     = undefined<br>
        mkResult    = undefined<br>
    <br>
        run s req   = do        -- dummy version<br>
                        mAtp <- mkAttempt s req<br>
                        mAck <- action s (fromJust mAtp)<br>
                        eRes <- mkResult s req (fromJust mAck)<br>
                        return $ case eRes of<br>
                            Left  f -> error "failure"<br>
                            Right s -> s <br>
    <br>
    I don't know how I would write the 'run' function above only once if
    I were using records. It seems I would have to duplicate code, no?<br>
    <br>
    <br>
    Thank you!<br>
    <br>
    <br>
    Dimitri<br>
    <br>
    <br>
    <br>
    <div class="moz-cite-prefix">On 08/06/15 16:36, Rein Henrichs wrote:<br>
    </div>
    <blockquote
cite="mid:CAJp6G8zoJnW9fm56R9c=WJ6ivsJqPwNptPeiJGcDT601EseKCQ@mail.gmail.com"
      type="cite">
      <div dir="ltr">This seems like a case where you only really need a
        record, not a typeclass.<br>
      </div>
      <br>
      <div class="gmail_quote">
        <div dir="ltr">On Mon, Jun 8, 2015 at 2:47 PM Dimitri
          DeFigueiredo <<a moz-do-not-send="true"
            href="mailto:defigueiredo@ucdavis.edu">defigueiredo@ucdavis.edu</a>>

          wrote:<br>
        </div>
        <blockquote class="gmail_quote" style="margin:0 0 0
          .8ex;border-left:1px #ccc solid;padding-left:1ex">Hello!<br>
          <br>
          I am trying to tie together a group of functions that turn an
          unreliable<br>
          remote network call into a reliable one. For each different
          network<br>
          request I make, a specific group of these functions should
          always work<br>
          together, but their type signatures are quite different. My
          first<br>
          thought was to put them all in a typeclass:<br>
          <br>
          import Control.Monad<br>
          <br>
          class Reliable1 m req attempt ack failure result where<br>
               getRequests1 :: Monad m =>               m [req]<br>
               mkAttempt1   :: Monad m => req        -> m (Maybe
          attempt)<br>
               action1      :: Monad m => attempt    -> m (Maybe
          ack)<br>
               getAcks1     :: Monad m => [attempt]  -> m [ack]<br>
               mkResult1    :: Monad m => req -> ack -> m
          (Either failure result)<br>
               run1         :: Monad m => req        -> m result<br>
          <br>
          That doesn't work because not all functions use all
          parameters. For<br>
          example, getAcks1 has no idea of what the final 'result' type
          parameter<br>
          is. This lead me to my second attempt. Defining a 'service'
          type with<br>
          the sole purpose of tying them all together. Here's my current
          attempt:<br>
          <br>
          {-# LANGUAGE MultiParamTypeClasses #-}<br>
          <br>
          import Control.Monad<br>
          <br>
          class Reliable m service where<br>
               getReqs     :: Monad m => service ->             
           m [req]<br>
               mkAttempt   :: Monad m => service -> req       
          -> m (Maybe attempt)<br>
               action      :: Monad m => service -> attempt   
          -> m (Maybe ack)<br>
               getAcks     :: Monad m => service -> [attempt] 
          -> m [ack]<br>
               mkResult    :: Monad m => service -> req -> ack
          -> m (Either<br>
          failure result)<br>
               run         :: Monad m => service -> req       
          -> m result<br>
          <br>
          data RemoteCall = RemoteCall<br>
          <br>
          instance Reliable IO RemoteCall where<br>
               getReqs     = undefined<br>
               mkAttempt   = undefined<br>
               action      = undefined<br>
               getAcks     = undefined<br>
               mkResult    = undefined<br>
               run         = undefined<br>
          <br>
          This works, but I have to explicitly pass the 'service'
          argument in<br>
          every call.<br>
          Can I avoid passing this parameter every time?<br>
          Question, is there a better way to do this?<br>
          I wanted to have a wrapper to make my remote calls reliable.<br>
          <br>
          Thanks,<br>
          <br>
          Dimitri<br>
          <br>
          <br>
          <br>
          _______________________________________________<br>
          Beginners mailing list<br>
          <a moz-do-not-send="true" href="mailto:Beginners@haskell.org"
            target="_blank">Beginners@haskell.org</a><br>
          <a moz-do-not-send="true"
            href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners"
            target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners</a><br>
        </blockquote>
      </div>
      <br>
      <fieldset class="mimeAttachmentHeader"></fieldset>
      <br>
      <pre wrap="">_______________________________________________
Beginners mailing list
<a class="moz-txt-link-abbreviated" href="mailto:Beginners@haskell.org">Beginners@haskell.org</a>
<a class="moz-txt-link-freetext" href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners">http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners</a>
</pre>
    </blockquote>
    <br>
  </body>
</html>