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. 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)) We wish to define an instance for Monad (Iteratee el m). Since Functor is a superclass of Monad, we must define a functor instance: > instance Functor m => Functor (Iteratee el m) where > fmap f (IE_done a) = IE_done (f a) > fmap f (IE_cont e k) = IE_cont e (\s -> fmap docase (k s)) > where > docase (IE_done a,s) = (IE_done (f a), s) > docase (i, s) = (fmap f i, s) There are two ways to proceed with the Monad instance -- to be precise, there are two ways of defining bind. Method A: just define bind as usual > instance (Functor (Iteratee el m),Monad m) => Monad (Iteratee el m) where > return = IE_done > > IE_done a >>= f = f a > 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 (i >>= f, s) Although we must state the constraint (Functor (Iteratee el m)) to satisfy the super-class constraint, we have not made any use of the constraint. We defined bind without resorting to fmap. That seems like a waste. What makes it seem more like a waste is that the code for fmap and for bind is almost the same. We had to repeat essentially the same algorithm, analysing Iteratee and the continuation. Method B: define bind in terms of fmap Alas, just fmap is not sufficient to define bind. We need join: > joinIter :: Monad m => Iteratee el m (Iteratee el m a) -> Iteratee el m a > joinIter (IE_done i) = i > joinIter (IE_cont e k) = IE_cont e (\s -> k s >>= docase) > where > docase (IE_done (IE_cont Nothing k), s) = k s > docase (IE_done i, s) = return (i, s) > docase (i, s) = return (joinIter i, s) Only after defining join we can write > bind m f = joinIter $ fmap f m Again we see code duplication: the code for join resembles the code for fmap. The code for join follows the same pattern of analysing Iteratee and the continuation. In either way, Functor as a super-class of Monad leads to code duplication. That gives a bad feeling practically -- and theoretically. The experiment has led me wonder if a superclass constraint is the right way to state the relationship between Monads and Functors. 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. Alas, the instance ``instance Monad m => Functor m'' above has several drawbacks (for one, requiring overlapping instances everywhere). This makes me wonder if something is amiss. In the meanwhile, there is a practical work-around. Introduce a TemplateHaskell operation generating an instance such as > instance Monad (Iteratee el m) => Functor (Iteratee el m) where > fmap f m = m >>= (return . f) (the code for the method remains the same; only the type in the instance head varies). Alas, that requires undecidable instances. All the code before was Haskell98. _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime