In opposition of Functor as super-class of Monad

Petr P petr.mvd at gmail.com
Wed Oct 24 12:42:45 CEST 2012


(Just to clarify, it's not my proposal, I just endorse it. Looking at
its history, it's been worked on by pigworker and simonpj.)

The uu-parser library looks quite complex, so before I dive into
exploring it and reading your paper, I'd say I believe that your
objection is already addressed in the proposal, namely in section "The
opt-out mechanism" and perhaps in section "The design of the opt-out
mechanism". To clarify, the proposal doesn't remove `return` in favor
of `pure` etc. We'd still keep all the functions names like we have
now and the ability to define them differently. You could always use
your own definitions for Applicative (Functor etc.) if you didn't want
the default ones resulting from Monad (return/ap for pure/<*>) for any
reason.

  Best regards,
  Petr Pudlak

2012/10/24 S. Doaitse Swierstra <doaitse at swierstra.net>:
> There are very good reasons for not following this road; indeed everything which is a Monad can also be made an instance of Applicative. But more often than not we want to have a more specific implementation. Because Applicative is less general, there is in general more that you can do with it.
>
> An analogue is the relation between regular grammars and context-free grammars; indeed, once we have the latter concept we might argue that we do not need the first one any more. But if we know that something is in the first category we can do all kins of nice things which we cannot do with conxet-free grammars, such as constructing a finite state machine for recognising sentences.
>
> You proposal would introduce overlapping instances is such cases where we want to give a ``better'' implementation in case we know we are dealing with the more restricted case.
>
> I have explained this phenomenon for the first time in:
>
>
> @inproceedings{SwieDupo96,
>         Author = {Swierstra, S. D. and Duponcheel, L.},
>         Booktitle = {Advanced Functional Programming},
>         Date-Added = {2009-01-04 17:21:54 +0100},
>         Date-Modified = {2009-01-04 17:21:54 +0100},
>         Editor = {Launchbury, John and Meijer, Erik and Sheard, Tim},
>         Pages = {184-207},
>         Publisher = {Springer-Verlag},
>         Series = {LNCS-Tutorial},
>         Title = {Deterministic, Error-Correcting Combinator Parsers},
>         Urlpdf = {http://www.cs.uu.nl/people/doaitse/Papers/1996/DetErrCorrComPars.pdf},
>         Volume = {1129},
>         Year = {1996}}
>
> If you look at the uu-parsinglib library you will see that the Applicative instance of the parsers used there is definitely more involved that what you can do with the monadic interface. Your proposal would ruin this library.
>
> Unless we have things like e.g. named instances, the possibility to choose between overlapping instances, etc. I think we should leave things the way they are; the only reason I see for having superclasses is to be able to use functions from those classes in the default implementations of functions in the new class, and to group functionality coming from several classes.
>
>  Doaitse
>
>
>
>
>
>
>
>
>
>
>
>
> On Oct 24, 2012, at 10:01 , Petr P <petr.mvd at gmail.com>
>  wrote:
>
>>  Hi,
>>
>> I was thinking lately about the well known problem that Monad is
>> neither Functor nor Applicative. As I understand, it is caused by some
>> historical issues. What I like about Haskell is that it allows to
>> describe very nicely what different objects actually are - something
>> that I find very important for programming. And this issue violates
>> this principle.
>>
>> This has been discussed here more than year ago in
>> http://www.haskell.org/pipermail/haskell-prime/2011-January/003312.html
>> :
>>
>> On 1/4/11 11:24, 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 main objections were that it would break existing code and that it
>> would lead to code duplication. The former is serious, the second can
>> be easily solved by standard Haskell, since one can define
>>
>> instance Applicative ... where
>>    pure   = return
>>    (<*>)  = ap
>> instance Functor ... where
>>    fmap   = liftM
>>
>> To address the first objection:
>> AFAIK nobody mentioned the "Default superclass instances" proposal:
>> http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
>> To give an example how it would work:
>>
>>    class Applicative f => Monad f where
>>      (>>=) :: f a -> (a -> f b) -> f b
>>      ...
>>      instance Applicative f where
>>        ff <*> fs = ff >>= \ f -> fs >>= \ s -> return (f s)
>>        ...
>>
>> This says that if somebody defines an instance of Monad it
>> automatically becomes an instance of Applicative as defined in the
>> nested "instance" block. So there is no need to define
>> Applicative/Functor explicitly, making existing code work.
>>
>> Implementing this proposal would allow making Monad to extend Functor
>> and Applicative without breaking existing code. Moreover, this would
>> simplify other things, for example it would be possible to define an
>> instance of Traversable and the instances for Functor and Foldable
>> would be defined implicitly using fmapDefault and foldMapDefault. I'm
>> sure there are many other cases where splitting type classes into a
>> more fine-grained hierarchy would be beneficial, and the main reason
>> against it is simply not to break compatibility with existing code.
>>
>> IMHO this would be worthwhile to consider for some future revision of Haskell.
>>
>>  Best regards,
>>  Petr Pudlak
>>
>> _______________________________________________
>> Haskell-prime mailing list
>> Haskell-prime at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-prime
>



More information about the Haskell-prime mailing list