[Haskell-cafe] advice for dispatch question

John Lato jwlato at gmail.com
Mon Nov 2 19:17:04 EST 2009


Hello,

I've been thinking about a problem recently, and would like to know if
there are any recommendations for a solution.

I have two container-like type classes, defined as follows:

> import Control.Monad
>
> type family ElemOf c :: *
> type family MonadOf c :: * -> *
>
> class PureContainer c where
>   chead :: c -> ElemOf c
>
> class MonadicContainer c where
>   mhead :: c -> MonadOf c (ElemOf c)

now suppose I have two functions, like this:

> pureOp :: (PureContainer c, Monad m) => c -> m ()
> pureOp c = doSomethingWithElem $ chead c
>
> monadOp :: (Monad (MonadOf c), MonadicContainer c) => c -> MonadOf c ()
> monadOp c = mhead c >>= doSomethingWithElem
>
> -- assume this function does something
> doSomethingWithElem :: Monad m => a -> m ()
> doSomethingWithElem _ = return ()

the goal is to take the head from either a PureContainer or a
MonadicContainer and feed it to the doSomethingWithElem function,
which we can assume does something monadic.  What I would like to do
would be write one function that behaves like this quasi-Haskell:

combinedOp :: c -> m ()
combinedOp | PureContainer c = doSomethingWithElem $ chead c
combinedOp | MonadicContainer c = mhead c >>= doSomethingWithElem

I have many functions under consideration, and it would be nice to not
have to duplicate all of them.

So far I've thought of two possible solutions:

1.  create a newtype

> newtype M s (m :: * -> *) = M{ unM :: s}

then I can write

> type instance ElemOf (M c m) = ElemOf c
> type instance MonadOf (M c m) = m
>
> instance (Monad m, PureContainer c) => MonadicContainer (M c m) where
>   mhead = return . chead . unM

In this case, I would ignore the PureContainer case of combinedOp and
just stick every PureContainer of interest into the newtype as
necessary.

2.  Use a GADT with two constructors to special-case appropriately.  I
think this should work, but haven't tried it yet.  It seems more
complicated, and less transparent, than using a newtype as above.

Does anyone have any advice for this situation?  I'm defining
PureContainer instances anyway, so it seems silly to have to duplicate
everything for the monadic case.  Likewise the MonadicContainer
version is highly desirable for certain types, so I don't want to
forgo that either.

Thanks,
John


More information about the Haskell-Cafe mailing list