
Hi Isaac, just to give you a reply at all, see below. I reply glasgow-haskell-users@haskell.org since I'm not subscribed to haskell-prime. And I don't want to subscribe, because I'm more interested that Haskell becomes more stable (and standard). So here is my opinion: 1. The lexer should recognize keywords. 2. I would not mind if Haskel98 rejected all keywords that are also rejected by extensions, so that the lexer is extension independent. (Starting with Haskell98, removing conflicting identifiers as soon as I switch on valuable extensions does not make sense.) 3. I'm against qualified identifiers, with the unqualified part being a keyword like "Foo.where". (The choice of qualification should be left to the user, usually one is not forced to used qualified names.) 4. However, "Foo.where" should always be rejected and not changed to "Foo.wher e"! (Longest matching, aka "maximal munch", must not consider keywords!) (see end of: http://www.haskell.org/onlinelibrary/lexemes.html#sect2.4) I would not mind if a name "F. " is plainly rejected. It only makes sense, when a data constructor is the first argument of the composition operator "(.)" Maybe "." and "$" as operators should require white spaces on both sides, since "$(" also indicates template haskell. Cheers Christian Isaac Dupree wrote:
Especially after writing a partial lexer for Haskell, I opine that this should be all legal:
module Foo where
--in case you didn't know, this is legal syntax: Foo.f = undefined
Foo.mdo = undefined Foo.where = undefined x Foo.! y = undefined x Foo... y = undefined --remember ".." is reserved id, e.g. [2..5]
{-# LANGUAGE RecursiveDo, BangPatterns #-} module Bar where import Foo hello !x = mdo { y <- Foo.mdo Foo... ({-Foo.-}f x y); return y }
{- Haskell 98 -} module Baz where import Foo goodbye x = x ! 12
(Foo.where) lexing as (Foo.wher e) or (Foo . where) does not make me happy. (being a lexer error is a little less bad...) Especially not when the set of keywords is flexible. I don't see any good reason to forbid declaring keywords as identifiers/operators, since it is completely unambiguous, removes an extension-dependence from the lexer and simplifies it (at least the mental lexer); Also I hear that the Haskell98 lexing is (Foo.wher e), which I'm sure no one relies on...
Well, that's my humble opinion on what should go into Haskell' on this issue.
Isaac