Negation
S. Doaitse Swierstra
doaitse at cs.uu.nl
Sun Feb 14 05:25:07 EST 2010
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 Launchbury<john at 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 at haskell.org
>>>> http://www.haskell.org/mailman/listinfo/haskell-prime
>>>
>>> _______________________________________________
>>> 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