Re: In opposition of Functor as super-class of Monad

2012-10-24 Thread S. Doaitse Swierstra
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@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
 

Re: new keyword: infixlr?

2010-09-10 Thread S. Doaitse Swierstra

On 10 sep 2010, at 20:13, Ian Lynagh wrote:

 On Fri, Sep 10, 2010 at 07:51:10PM +0200, S. Doaitse Swierstra wrote:
 
 Currently Haskell has infix, infixl and infixr operators. I see a use for 
 infixlr as well. This indicates that the implemtation may assume the 
 operator to be associative, and thus has the freedom to balance an 
 expression containing several operator occurrences.
 
 Would it be restricted to use with operators with types that are (a - a
 - a) (or more specific)?

This is what I would normally expect from an infix operator. 

 
 Otherwise e.g.
   let (+:) = (:)
   infixlr :+
   in [] +: [] +: []
 could have type [[a]] or [[[a]]].
 
 The reason that I bring up this is that in a new combinator I have added to 
 my parser library (the || in Text.ParserCombinators.UU.Derived) internally 
 uses cartesian products, which are being constructed and updated. If the 
 compiler had the right to interpret  the expressions a || b ||c || d  
 as e.g. (a || b) || (c || d) then the updating time for would go down 
 from O(n) to O(log n). 
 
 How would the compiler work out which parsing to prefer? Or would it
 assume that infixlr expressions are best balanced?

Yes, that is the idea.


 
 When first reading the proposal, I thought the idea was to allow the
 compiler to more easily perform optimisations like
   a+b+c+2+3+d = a+b+c+5+d
 but I guess that wasn't something you were thinking about?

Indeed, but the behaviour would not be forbidden either. If you would expect 
this then I would probably also want to introduce comm for commutative 
operators, so a+2+b+c would get transformed into a+b+c+(2+4). The only suse for 
this is that after inlining  some further optimisations might take place, which 
would be hard for a programmer to achieve otherwise. My intention was however 
not to make things very complicated at this point.

Doaitse

 
 
 Thanks
 Ian
 
 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Negation

2010-02-14 Thread S. Doaitse Swierstra


On 14 feb 2010, at 09:32, Simon Marlow wrote:


On 14/02/10 02:21, Lennart Augustsson wrote:

I agree, I don't think this is a bug.  If the grammar actually says
that this is legal, then I think the grammar is wrong.


As far as I can tell Doitse is correct in that GHC does not  
implement the grammar, so it's either a bug in GHC or the grammar.   
To fix it in the grammar would no doubt involve quite a bit of  
refactoring, I can't immediately see how to do it easily.


This is indeed not easy, and probably one more situation where some  
extra text has to exclude this since I actually think it should not be  
accepted from a language design point of view. How would you explain  
that


weird :: Int - Int
weird = (if True then 3 else 5+)

is perfectly correct Haskell?

Doaitse





Cheers,
Simon



On Sun, Feb 14, 2010 at 1:48 AM, John Launchburyj...@galois.com   
wrote:
I don't think this is a bug. I do not expect to be able to unfold  
a definition without some syntactic issues. For example,


two = 1+1
four = 2 * two

but unfolding fails (four = 2 * 1 + 1). In general, we expect to  
have to parenthesize things when unfolding them.


John


On Feb 13, 2010, at 11:56 AM, Simon Marlow wrote:


On 09/02/10 21:43, S. Doaitse Swierstra wrote:
One we start discussing syntax again it might be a good occasion  
to

reformulate/make more precise a few points.

The following program is accepted by the Utrecht Haskell  
Compiler (here

we took great effort to follow the report closely ;-} instead of
spending our time on n+k patterns), but not by the GHC and Hugs.

module Main where

-- this is a (rather elaborate) definition of the number 1
one = let x=1 in x

-- this is a definition of the successor function using section  
notation

increment = ( one + )

-- but if we now unfold the definition of one we get a parser  
error in GHC

increment' = ( let x=1 in x + )


Now that *is* an interesting example.  I had no idea we had a bug  
in that area. Seems to me that it ought to be possible to fix it  
by refactoring the grammar, but I haven't tried yet.


Are there any more of these that you know about?

Cheers,
 Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Negation

2010-02-09 Thread S. Doaitse Swierstra
One we start discussing syntax again it might be a good occasion to  
reformulate/make more precise a few points.


The following program is accepted by the Utrecht Haskell Compiler  
(here we took great effort to follow the report closely ;-} instead of  
spending our time on n+k patterns), but not by the GHC and Hugs.


module Main where

-- this is a (rather elaborate) definition of the number 1
one = let x=1 in x

-- this is a definition of the successor function using section notation
increment = ( one + )

-- but if we now unfold the definition of one we get a parser error in  
GHC

increment' = ( let x=1 in x  +  )

The GHC and Hugs parsers are trying so hard to adhere to the meta rule  
that bodies of let-expressions
extend as far as possible when needed in order to avoid ambiguity,  
that they even apply that rule when there is no ambiguity;
here we have  only a single possible parse, i.e. interpreting the  
offending expression as ((let x = 1 in ) +).


Yes, Haskell is both a difficult language to parse and to describe  
precisely.


Doaitse


On 8 feb 2010, at 17:18, Simon Peyton-Jones wrote:


Folks

Which of these definitions are correct Haskell?

x1 = 4 + -5
x2 = -4 + 5
x3 = 4 - -5
x4 = -4 - 5
x5 = 4 * -5
x6 = -4 * 5

Ghc accepts x2, x4, x6 and rejects the others with a message like
Foo.hs:4:7:
  Precedence parsing error
  cannot mix `+' [infixl 6] and prefix `-' [infixl 6] in the  
same infix expression


Hugs accepts them all.

I believe that the language specifies that all should be rejected.  
http://haskell.org/onlinereport/syntax-iso.html


I think that Hugs is right here.  After all, there is no ambiguity  
in any of these expressions.  And an application-domain user found  
this behaviour very surprising.


I'm inclined to start a Haskell Prime ticket to fix this language  
definition bug.  But first, can anyone think of a reason *not* to  
allow all the above?


Simon


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


nomination for Haskell 2011

2009-12-23 Thread S. Doaitse Swierstra
Herewith I propose Atze Dijkstra as a member of the Haskell 2011  
committee.


Atze is the main architect/implementor of the Utrecht Haskell Compiler  
(see http://www.cs.uu.nl/wiki/UHC, and last year Haskell Symposium),  
and has as a result of that a very good insight in the implementation  
issues involved with new features/extensions/changes. He furthermore  
co-supervises Arie Middelkoop who is working on the Ruler system,  
which aims to be a tool for describing (the implementations of) type  
systems, and Jeroen Fokker who is working on a Grin-based whole- 
program analysis


The compiler itself is currently about 100.000 lines of Haskell. A  
second release is planned for the beginning of next year, which will  
contain a completely new garbage collector, a cabal based installation  
scheme, and the beginning of some global optimisations.


I think Atze primarily covers the following categories: Implementors,  
Academic users, Teachers.


If you have any questions I am more than willing to answer them,

Doaitse



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime