[Haskell-cafe] instance Monad m => Functor m

Hans Aberg haberg at math.su.se
Wed Apr 9 07:17:06 EDT 2008


On 9 Apr 2008, at 11:26, Jules Bean wrote:
>> Using 'hugs -98', I noticed it accepts:
>>   instance Monad m => Functor m where
>>     fmap f x = x >>= return.f
>> Has this been considered (say) as a part of the upcoming Haskell  
>> Prime?
>
> This forbids any Functors which are not monads. Unless you allow  
> overlapping instances...

I see it as a Haskell limitation of not being able to indicate the  
function names in the class definition head:

If one could write say
   class Monoid (a; unit, mult) where
     unit :: a
     mult :: a -> a -> a
then it is possible to say
   instance Monoid ([]; [], (++)) where
     -- 'unit' already defined
     -- definition of (++)

Similarly:
   class Functor (m; fmap) where
     fmap :: (a -> b) -> (m a -> m b)

   instance Monad m => Functor (m, mmap) where
     mmap f x = x >>= return.f

- For backwards compatibility, if the function names are not  
indicated, one gets the declaration names as default.

I don't know if it is possible to extend the syntax this way, but it  
would be closer to math usage. And one would avoid duplicate  
definitions just to indicate different operator names, like:
   class AdditiveMonoid a where
     o :: a
     (+) :: a -> a -> a
as it could be create using
   class Monoid (a; o, (+))

> ...(which of course would not be h98 any more!).

It does not work in 'hugs +98' mode; if I avoid the Prelude names by:
   class Munctor m where
     mmap :: (a -> b) -> (m a -> m b)

   instance Monad m => Munctor m where
     mmap f x = x >>= return.f
I get
   ERROR - Syntax error in instance head (constructor expected)

> Other solutions, such as class Functor m => Monad m are frequently  
> discussed.

The point is that Monads have a code lifting property, so the functor  
is already conatained in the current definition.

One might want to have away to override, so even if
   instance Monad m => Functor (m, mmap)
functor specialization can take place if one has a more efficeint  
definition. For example
   instance Functor ([], mmap) where
     mmap = map

   Hans




More information about the Haskell-Cafe mailing list