The FunctorM library

Simon Marlow simonmar at microsoft.com
Wed Mar 23 04:49:43 EST 2005


On 20 March 2005 23:30, Thomas Jäger wrote:

> Aside from naming issues, there seem to be some problems with the way
> FunctorM is currently implemented.
> 
> First of all, `FunctorM` should be a superclass of `Functor' because
> there is an obvios implementation of fmap in terms of fmapM
>> import Data.FunctorM
>> import Control.Monad.Identity
>> 
>> fmap' :: FunctorM f => (a -> b) -> f a -> f b
>> fmap' f = runIdentity . fmapM (return . f)
> It is already annyoing enough that `Funtor' isn't a subclass of
> `Monad' although every monad must also be functor.
> 
> Now, FunctorM should be based on the simplest operations possible,
> which in this case is the distributive law and not a monadic version
> of fmap (which might be provided for efficiency reasons).
> 
>> class Functor f => FunctorM' f where
>>   dist' :: Monad m => f (m a) -> m (f a)
>>   fmapM' :: Monad m => (a -> m b) -> f a -> m (f b)
>> 
>>   dist' = fmapM' id
>>   fmapM' f = dist' . fmap f
>> 
>> -- for example
>> instance FunctorM' [] where
>>   dist' = sequence
>>   fmapM' = mapM

Does anyone else have any comments on the suggestions from Iavor and Thomas in this thread?  I'm happy to make changes, but only if there's a concensus.  The proposals so far seems to be

  1) add dist method
  2a) make Functor a superclass of FunctorM
  2b) make Functor a *sub*class of FunctorM
  2c) make Functor a subclass of Monad
  2d) make Functor a superclass of Monad
  3) rename FunctorM class to ForEach
  4) rename FunctorM module to Control.Monad.FunctorM(?)

(1) is easy and not controversial (but is 'dist' the best name?).

AFAICT, 2a, 2b, 2c, and 2d have all been suggested (eg. the quoted message above suggests 2a, 2b and 2c).  Perhaps some of the suggestions were typos, but at this point I'm a bit confused!

Cheers,
	Simon


More information about the Libraries mailing list