Re: Negation

2010-02-09 Thread Atze Dijkstra


On  10 Feb, 2010, at 00:53 , Lennart Augustsson wrote:


Do you deal with this correctly as well:
 case () of _ -> 1==1==True


No, that is, in the same way as GHC & Hugs, by reporting an error. The  
report acknowledges that compilers may not deal with this correctly  
when it has the form ``let x=() in 1=1=True'' (or a if/\... ->  
prefix), but does not do so for your example. It is even a bit more  
complicated of the layout rule because


case () of _ -> 1==1
==True

is accepted.

I think the combination of layout rule, ambiguity disambiguated by a  
'extend as far as possible to the right' rule, fixity notation as  
syntax directives (but not separated as such), makes the language  
design at some points rather complex to manage implementationwise in a  
compiler. Like all we do our best to approach the definition. When  
possible I'd prefer changes in the language which simplify matters  
(like a simpler way of dealing with negate as proposed), at least with  
these syntactical issues.





On Tue, Feb 9, 2010 at 10:43 PM, 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  +  )

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


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



- Atze -

Atze Dijkstra, Department of Information and Computing Sciences. /|\
Utrecht University, PO Box 80089, 3508 TB Utrecht, Netherlands. / | \
Tel.: +31-30-2534118/1454 | WWW  : http://www.cs.uu.nl/~atze . /--|  \
Fax : +31-30-2513971  | Email: a...@cs.uu.nl  /   |___\



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


Re: Negation

2010-02-09 Thread Lennart Augustsson
Do you deal with this correctly as well:
  case () of _ -> 1==1==True


On Tue, Feb 9, 2010 at 10:43 PM, 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  +  )
>
> 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
>
___
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


Re: Negation

2010-02-09 Thread johndearle
My impression is that combinatory logic figures prominently in the design of 
Haskell and some of the constructs seem to be best understood as combinatorial 
logic with syntactic sugar. One could predict from this a number of things. One 
of such is the language would at some points seem counter intuitive, albeit 
rational. I am concerned that those who lose sight of this, or perhaps never 
understood this and don't care to, may lose touch with the language's intent. 
If it is an outcome of combinatorial logic it is likely correct. The problem 
may lie else where.

The example given "rationale" suggests that the problem centers on the language 
designers being in possession of a necessary condition for correctness, but not 
a sufficient condition. If this is the case, there are two courses of action 
that are available to you/us. Solve the problem, as in work out all the 
necessary conditions so that you are in possession of a sufficient condition or 
give up the attempt to solve the problem altogether, throw up your hands and 
admit you failed, proclaiming that the naive solution found was and is worse 
than the problem. It may even turn out that as you become familiar with the 
alleged solution, that it has charm, in that it brings you flowers and you 
discover that he isn't all that bad.

 Christian Maeder  wrote: 
> > | I imagine it would be something like deleting the production
> > | 
> > | lexp6->  - exp7
> 
> The rational for the current choice was the example:
> 
> f x = -x^2
> 
> > | and adding the production
> > | 
> > | exp10->  - fexp
> 
> But I would also recommend this change.
> 
> It would also make sense to allow "-" before "let", "if" and "case" or
> another "-" expression, but that's a matter of taste.
> 
> Cheers Christian
> ___
> 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 Christian Maeder
> | I imagine it would be something like deleting the production
> | 
> | lexp6->  - exp7

The rational for the current choice was the example:

f x = -x^2

> | and adding the production
> | 
> | exp10->  - fexp

But I would also recommend this change.

It would also make sense to allow "-" before "let", "if" and "case" or
another "-" expression, but that's a matter of taste.

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


Re: Negation

2010-02-09 Thread Lennart Augustsson
It's not true at all that Haskell was created by type theorists.
It is true that little attention was paid for how things are done in C. :)

On Tue, Feb 9, 2010 at 2:39 PM,   wrote:
>
> It needs to be appreciated that the Haskell language was created by type 
> theorists who were not necessarily concerned with how they do it in C.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Negation

2010-02-09 Thread johndearle
Monadic operators are atomic in that they form an atom. Binary operators do 
not. Perhaps I should have used the word unary instead of monadic, hmm. It is 
best sometimes to never turn back. What is done is done! There is an ambiguity. 
One is a partial order whereas the other is a total order. Despite the apparent 
clarity the question is are there mitigating factors?

I do not wish to reveal all the mysteries of the universe in one sitting (in 
other words I have no intention of discussing the precise mechanisms involved), 
but having multiple uses for a symbol complicates the grammar. Hyphen is badly 
overloaded. The rules as they are may serve to discourage certain patterns. OK, 
I'll spell it out. Ambiguity is not a one way street. In the usual course of 
the compiler, something might be unambiguous (with respect to the compiler). 
The compiler exhibits what I shall call direction bias. This is why it appears 
in a sense to be unambiguous. We usually explain this away by saying that 
though it is unambiguous, it is unclear. This is merely informal speech that 
results from a lack of understanding of the nature of the problem.

On occasion despite the direction bias of the machine in real world problems we 
often encounter this ambiguity that occurs in the opposite direction. 
Typically, we merely dismiss the ambiguity as not even being a legitimate 
expression of ambiguity once we realize that in the conventional direction it 
is unambiguous. We will conclude that we were confused when in fact we were 
not. Our confusion is our conclusion that we were confused.

So in a sense it is unambiguous and in another it is ambiguous in a manner that 
is context sensitive. For example, if you are trying to extend the grammar of 
the language you may have to account for the various ways in which hyphens are 
used. In other words you have to account for the ambiguities. This has been an 
area of research for me. As a practical matter it is often possible to account 
for them if you grok the language and how it was implemented, and have nothing 
better to do with your time than to work out all the possible implications of a 
proposed change to the language which is what all of you are doing. Since this 
sort of thing only crops up on occasion we dismiss it as unreal.

You/we could use tilde for minus sign much like Standard ML does. It was a 
brilliant stroke and it isn't heresy. It is conceivable that an alternative 
albeit inferior approach to achieve a similar outcome was taken that everyone 
is now stuck with, but there is more to the story.

Someone gave an example involving modular arithmetic. If negation were 
meaningless with respect to an operation that operation could be regarded as 
more atomic as in more primitive than negation. You essentially skip over the 
expression concluding that it can't apply because it cannot meaningfully apply. 
Negation is meaningful (though not wholly meaningful) with respect to modular 
arithmetic and so there is no reason for it to be regarded as more primitive 
than additive inverse "negation". There are no type distinctions. An integer is 
an integer is an integer though I could see how someone might think of modular 
arithmetic as the arithmetic of the finite and therefore smaller and something 
that fits inside of the infinite. The type of the result of modular arithmetic 
is not a pure integer. It has a more restrictive type even though the 
distinction is easily overlooked. The domain and codomain does not form the 
Cartesian product of integers. It is bounded by the modulus, thus a dependent 
type.

Can the degree to which a type is broad or narrow be used to signify the 
default order of evaluation, known as precedence? There is reason to believe 
so. Since one type is more restrictive than another on occasion the operation 
will be meaningful and on others meaningless. By way of analogy (and 
efficiency) more restrictive types should be evaluated first and therefore have 
a higher precedence compared to their less restrictive counterparts even if the 
type distinctions are invisible to the compiler.

It needs to be appreciated that the Haskell language was created by type 
theorists who were not necessarily concerned with how they do it in C.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Negation

2010-02-09 Thread Jon Fairbairn
"Sittampalam, Ganesh"

writes:

> Lennart Augustsson wrote:
>> Of course unary minus should bind tighter than any infix operator.
>> I remember suggesting this when the language was designed, but the
>> Haskell committee was very set against it (mostly Joe Fasel I think). 
>
> Are there archives of this discussion anywhere?

If it was on the fplangc mailing list, the archive exists
somewhere (Thomas Johnsson had it in the past). If it was at one
of the committee meetings, Thomas or Lennart had a tape recorder
running. I remember asking some time later what happened to this
and got a reply that contained the phrase "teknisk missöde",
which doesn't take much of a grasp of Swedish to guess the
meaning of.

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk


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


RE: Negation

2010-02-09 Thread Sittampalam, Ganesh
Lennart Augustsson wrote:
> Of course unary minus should bind tighter than any infix operator.
> I remember suggesting this when the language was designed, but the
> Haskell committee was very set against it (mostly Joe Fasel I think). 

Are there archives of this discussion anywhere?

Cheers,

Ganesh

=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime