
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