Negation
John D. Earle
JohnDEarle at cox.net
Thu Feb 11 12:43:08 EST 2010
Possible Solution
There is a reason why lexical analysis follows the maximal munch rule
whereas a parser will follow the minimal munch rule which I won't discuss, a
fact that many of you may thank me for. Stated simply, the two operations,
lexical analysis and parsing, correspond to different paradigms. I have done
work in this area. If the compiler is at some step following the maximal
munch rule it is performing lexical analysis and not parsing. Herein, may
lie the problem. What this means is that the Haskell language needs to be
compiled in stages wherein there is at least one intermediate language that
in turn is the subject of lexical analysis followed by parsing. If the
Haskell language specification makes this clear, the problem may go away.
--------------------------------------------------
From: "S. Doaitse Swierstra" <doaitse at cs.uu.nl>
Sent: 09 Tuesday February 2010 1443
To: "Haskell Prime" <haskell-prime at haskell.org>
Subject: Re: Negation
> 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
More information about the Haskell-prime
mailing list