Qualified identifiers opinion
Isaac Dupree
isaacdupree at charter.net
Wed Aug 15 18:48:09 EDT 2007
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
More information about the Haskell-prime
mailing list