Am 20.05.2010 um 14:16 schrieb Tony Morris:

> I've compared and clearly the former is significantly superior :)
> 
> I'm rather interested if there are any sound suggestions to resolve the
> general issue of retrospective type-class extension.
> 

I would like to have something like

parent class Functor f <= Applicative f where
  fmap f x = pure f <*> x

Then one could write

instance Applicative MyApplicative deriving parent Functor where
  (<*>) = ...
  pure = ...

as an abbreviation for

instance Functor MyApplicative where
  fmap f x = pure f <*> x

This way, we do not only save some keystrokes, but now it is clear
that (fmap f x == pure f <*> x) is expected to hold for type
MyApplicative. One could also write

parent class Applicative a <= Monad a deriving parent Functor where
  (<*>) = ap
  pure = return
  fmap = liftM

overriding the default definition of Functor's fmap. Then

instance Monad MyMonad deriving parent Applicative where
  (>>=) = ...
  return = ...

would be an abbreviation for

instance Functor MyMonad where
  fmap = liftM

instance Applicative MyMonad where
  (<*>) = ap
  pure = return

Now the compiler can even conclude that (liftM f x == pure f <*> x) is expected 
to
hold for type MyMonad.

But there is an ambiguity if one also defines

parent class Functor f <= Monad f where
  fmap f x = trace "boo!" (liftM f x)

Then it might not be clear which definition of fmap should be used, because 
there are two
possible paths: (Monad => Applicative => Functor) and (Monad => Functor). But 
then the
programmer has to decide whether he writes 'deriving parent Applicative' or 
'deriving parent
Functor'. Thus, as long as every class or instance declaration contains at most 
one 'deriving
parent' statement, there will always be one unambiguous path, so that this will 
not become
a problem.

This extension would have three advantages:
- it is merely syntactic sugar, so that it can easily be implemented,
- it does not involve tricky resolution of methods or types, so that it is easy 
to comprehend, and
- it allows to encode knowledge about the laws class instances (should) follow.


> 
> Miguel Mitrofanov wrote:
>> That won't be a great idea; if I just want my monad to be declared as
>> one, I would have to write
>> 
>> instance Functor MyMonad where fmap = ...
>> instance Pointed MyMonad where pure = ...
>> instance Applicative MyMonad where (<*>) = ...
>> instance Monad MyMonad where join = ...
>> 
>> Compare this with
>> 
>> instance Monad MyMonad where
>>  return = ...
>>  (>>=) = ...
>> 
>> and take into account that (>>=) is usually easier to write than join.
>> 
>> Limestraƫl wrote:
>>> Then it would be:
>>> 
>>> class Functor f where
>>>    fmap :: (a -> b) -> f a -> f b
>>> 
>>> class (Functor f) => Pointed f where
>>>    pure :: a -> f a
>>> 
>>> class (Pointed f) => Applicative f where
>>>    (<*>) :: f (a -> b) -> f a -> f b
>>> 
>>> class (Applicative f) => Monad f where
>>>    join :: f (f a) -> f a
>>> 
>>> This would be a great idea, for the sake of logic, first (a monad
>>> which is not a functor doesn't make sense), and also to eliminate
>>> redudancy (fmap = liftM, ap = (<*>), etc.)
>>> 
>>> 2010/5/20 Tony Morris <tonymor...@gmail.com
>>> <mailto:tonymor...@gmail.com>>
>>> 
>>>    Ivan Miljenovic wrote:
>>>> On 20 May 2010 14:42, Tony Morris <tonymor...@gmail.com
>>>    <mailto:tonymor...@gmail.com>> wrote:
>>>> 
>>>>> We all know that "class (Functor f) => Monad f" is preferable
>>>    but its
>>>>> absence is a historical mistake. We've all probably tried once:
>>>>> 
>>>>> instance (Functor f) => Monad f where
>>>>> 
>>>> 
>>>> Do you mean the reverse of this (instance (Monad m) => Functor m
>>>    where) ?
>>>> 
>>>    Yes.
>>> 
>>>    --
>>>    Tony Morris
>>>    http://tmorris.net/

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to