lexer was: Re: Qualified identifiers opinion
Christian Maeder
Christian.Maeder at dfki.de
Tue Aug 21 10:32:12 EDT 2007
Isaac Dupree wrote:
>> {-# LANGUAGE ForeignFunctionInterface #-}
>> module Foo where
>
> Suppose all modules have an implicit, unavoidable
>
>> import ":SpecialSyntax" (module, where, let, [], -- ...
>> , foreign --because that extension is enabled
>> )
>
> Now let's import some imaginary already-existing modules that use
> "keywords"
I think, it is nonsense to make an extension dependent lexer, because -
as said before - I don't want to change my old code when switching on an
extension.
The syntax of extensions should be simply illegal for code without that
extension.
Breaking old code just because a new keyword has been introduced for a
new extension is a smaller problem than trying to maintain (and call)
different lexers.
http://www.haskell.org/ghc/docs/6.6.1/html/users_guide/ghc-language-features.html#options-language
It would be nice, if the "Syntax stolen" bits could be streamlined for
haskell-prime. In particular "[e|", "[p|", "[d|", "[t|" are ugly -- a
keyword token for template haskell (-fth), three tokens (for
comprehensions) otherwise.
If that -fth syntax shall be kept, one should disallow any combination
"[<letter>|" without white space for comprehensions!
Cheers Christian
More information about the Glasgow-haskell-users
mailing list