In opposition of Functor as super-class of Monad

kahl at cas.mcmaster.ca kahl at cas.mcmaster.ca
Tue Jan 4 16:15:33 CET 2011


On Tue, Jan 04, 2011 at 02:24:21AM -0800, oleg at okmij.org wrote:
 > 
 > I'd like to argue in opposition of making Functor a super-class of
 > Monad. I would argue that superclass constraints are not the right
 > tool for expressing mathematical relationship such that all monads are
 > functors and applicatives.
 > 
 > Then argument is practical. It seems that making Functor a superclass
 > of Monad makes defining new monad instances more of a chore, leading
 > to code duplication. To me, code duplication is a sign that an
 > abstraction is missing or misused.

The argument about code duplication somehow seems to assume that
class member instances need to be defined as part of the instance
declaration. This is not the case, and in fact I am arguing in general
against putting any interesting code into instance declarations,
especially into declarations of instances with constraints
(since, in ML terminology, they are functors, and putting their
definition inside an instance declaration constrains their applicability).

In my opinion, the better approach is to define (generalised versions of)
the functions mentioned in the class interface,
and then just throw together the instances from those functions.
This also makes it easier to adapt to the ``class hierarchy du jour''.

The point for the situation here is that although we eventually need
definitions of all the functions declared as class members,
there is absolutely nothing that constrains the dependency relation
between the definitions of these functions to be conforming in any way
to the class hierarchy.

For a simpler example, assume that I have some arbitrary data type

> data T a = One a | Two a a

and assume that I am interested only in Ord instances, since I want to
use T with Data.Set, and I am not really interested in Eq instances.

Assume that the order will depend on that for |a|,
so I will define a function:

> compareT :: (a -> a -> Ordering) -> T a -> T a -> Ordering

Then I can thow together the necessary instances from that:

> instance Ord a => Ord (T a) where
>   compare = compareT compare
> 
> instance Ord a => Eq (T a) where
>   (==) = eqFromCompare compare

assuming I have (preferably from the exporter of Eq and Ord):

> eqFromCompare :: (a -> a -> Ordering) -> (a -> a -> Bool)
> eqFromCompare cmp x y = case cmp x y of
>   EQ -> True
>   _ -> False

The same approach works for Oleg's example:

 > For the sake of the argument, let us suppose that Functor is a
 > superclass of Monad. Let us see how to define a new Monad
 > instance. For the sake of a better illustration, I'll use a complex
 > monad. I just happen to have an example of that: Iteratee.
 > The data type Iteratee is defined as follows:

> type ErrMsg = String                    -- simplifying
> data Stream el = EOF (Maybe ErrMsg) | Chunk [el] deriving Show
>
> data Iteratee el m a = IE_done a
>                      | IE_cont (Maybe ErrMsg)
>                                (Stream el -> m (Iteratee el m a, Stream el))

 > [...]		               
 > 
 > It _almost_ makes me wish the constraint go the other way:
 > 
 > > instance Monad m => Functor m where
 > > 	fmap f m = m >>= (return . f)
 > 
 > That is, we need an instance rather than a superclass constraint, and
 > in the other direction. The instance constraint says that every monad
 > is a functor. Moreover,
 > 	\f m = m >>= (return . f)
 > 
 > is a _proof term_ that every monad is a functor. We can state it once
 > and for all, for all present and future monads.

I would expect that proof term to exported by the package exporting
Functor and Monad; let us define it here:

> fmapFromBind (>>=) f m = m >>= (return . f)

Now you can write, no matter which class is a superclass of which:

> bindIt return (>>=) (IE_done a) f = f a
> bindIt return (>>=) (IE_cont e k) f = IE_cont e (\s -> k s >>= docase)
>   where
>     docase (IE_done a, stream)   = case f a of
>                       IE_cont Nothing k -> k stream
>                       i                 -> return (i,stream)
>     docase (i, s)  = return (bindIt return (>>=) i f, s)
> 
> instance Monad m => Monad (Iteratee el m) where
>    return = IE_done
>    (>>=) = bindIt return (>>=)
> 
> instance Monad m => Functor (Iteratee el m) where
>   fmap = fmapFromBind (>>=)

Of course this assumes that you are not actually interested in an
instance of shape: instance (Functor ...) => Functor (Iteratee el m),
but this seems to be a plausible assumption.

Defining the functionality really has nothing to do with declaring an
instance of a type class, and it is normally better to keep the two
separated. And that does not lead to any real code duplication,
only extremely boring instance declarations.


Wolfram





More information about the Haskell-prime mailing list