I used typeclasses because I want to have a "default version" of the run function.

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?

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.

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):

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}

import Control.Monad

class Reliable m s where

    type Req s :: *     -- the type for requests
    type Atp s :: *     -- the type for attempts
    type Ack s :: *     -- the type for acknowledgments
    type Res s :: *     -- the type for results (Success)
    type Fai s :: *     -- the type for failures

    getRequests :: Monad m => s                   -> m [Req s]
    mkAttempt   :: Monad m => s -> Req s          -> m (Maybe (Atp s))
    action      :: Monad m => s -> Atp s          -> m (Maybe (Ack s))
    getAcks     :: Monad m => s ->[Atp s]         -> m [Ack s]      
    mkResult    :: Monad m => s -> Req s -> Ack s -> m (Either (Fai s) (Res s))
    run         :: Monad m => s -> Req s          -> m (Res s)


data RemoteCall = RemoteCall

instance Reliable IO RemoteCall where

    type Req RemoteCall = Int
    type Atp RemoteCall = String
    type Ack RemoteCall = Bool
    type Res RemoteCall = String
    type Fai RemoteCall = Int

    getRequests = undefined  -- these can be specialized for each instance
    mkAttempt   = undefined
    action      = undefined
    getAcks     = undefined
    mkResult    = undefined

    run s req   = do        -- dummy version
                    mAtp <- mkAttempt s req
                    mAck <- action s (fromJust mAtp)
                    eRes <- mkResult s req (fromJust mAck)
                    return $ case eRes of
                        Left  f -> error "failure"
                        Right s -> s

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?


Thank you!


Dimitri



On 08/06/15 16:36, Rein Henrichs wrote:
This seems like a case where you only really need a record, not a typeclass.

On Mon, Jun 8, 2015 at 2:47 PM Dimitri DeFigueiredo <defigueiredo@ucdavis.edu> wrote:
Hello!

I am trying to tie together a group of functions that turn an unreliable
remote network call into a reliable one. For each different network
request I make, a specific group of these functions should always work
together, but their type signatures are quite different. My first
thought was to put them all in a typeclass:

import Control.Monad

class Reliable1 m req attempt ack failure result where
     getRequests1 :: Monad m =>               m [req]
     mkAttempt1   :: Monad m => req        -> m (Maybe attempt)
     action1      :: Monad m => attempt    -> m (Maybe ack)
     getAcks1     :: Monad m => [attempt]  -> m [ack]
     mkResult1    :: Monad m => req -> ack -> m (Either failure result)
     run1         :: Monad m => req        -> m result

That doesn't work because not all functions use all parameters. For
example, getAcks1 has no idea of what the final 'result' type parameter
is. This lead me to my second attempt. Defining a 'service' type with
the sole purpose of tying them all together. Here's my current attempt:

{-# LANGUAGE MultiParamTypeClasses #-}

import Control.Monad

class Reliable m service where
     getReqs     :: Monad m => service ->               m [req]
     mkAttempt   :: Monad m => service -> req        -> m (Maybe attempt)
     action      :: Monad m => service -> attempt    -> m (Maybe ack)
     getAcks     :: Monad m => service -> [attempt]  -> m [ack]
     mkResult    :: Monad m => service -> req -> ack -> m (Either
failure result)
     run         :: Monad m => service -> req        -> m result

data RemoteCall = RemoteCall

instance Reliable IO RemoteCall where
     getReqs     = undefined
     mkAttempt   = undefined
     action      = undefined
     getAcks     = undefined
     mkResult    = undefined
     run         = undefined

This works, but I have to explicitly pass the 'service' argument in
every call.
Can I avoid passing this parameter every time?
Question, is there a better way to do this?
I wanted to have a wrapper to make my remote calls reliable.

Thanks,

Dimitri



_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners