Qualified identifiers opinion

Isaac Dupree isaacdupree at charter.net
Sat Aug 18 07:00:10 EDT 2007


Christian Maeder wrote:
| 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.)

Okay, here's a thought experiment... one may follow along, and agree or 
not as one likes (I'm not sure how much I agree with it myself, though 
it might be an interesting way to structure a compiler)


 > {-# 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"

 > import A (foreign)
 > import B (mdo)

This turns up a problem already: explicitly naming things in an import 
or export list might not work unambiguously, because keywords are 
sometimes used to mean special things there. Going on... maybe we 
imported the whole modules.

According to standard Haskell import rules, there is no conflict until 
the ambiguous word is used.

Either "f" here works fine, because ":SpecialSyntax" in this module did 
not import "mdo":

 > f = mdo
 > f = B.mdo

Whereas the possibilities with "foreign"...

 > g = foreign --error, ambiguous!!!!
 > foreign import ccall ........ --error, ambiguous!!!!
 > g = A.foreign --okay, unambiguous
 > ":SpecialSyntax".foreign import ccall .... -- can't write in Haskell!

Now, if we want to avoid the understandably undesirable matter of 
imports interfering with keywords (after all, keywords can appear before 
the import list is finished, such as "module" "where" and "import"), we 
could tweak the import-conflict rules for this special case. In this 
module where "foreign" is imported from ":SpecialSyntax", the mere 
phrase "import A" could raise an error, as if all imported syntax were 
used (unqualified, as always) in the module.  Whereas, "import qualified 
A" would not.  (and what about "import A hiding ..."?)




By the way, we are lucky that pragmas have their own namespace {-# NAME 
arguments #-}.  But as I mentioned, we lack a namespace for extensions 
that have a semantic impact on the annotated code.  Certain 
preprocessors invent things like {-! !-} ... or add template-haskell 
syntax, or some arbitrary other keywords syntax like "proc...do"... or 
even steal large portions of existing comment syntax (Haddock, which 
isn't even a semantic impact on the code!)

BTW #2: The simpler and less variable the lexer is, the easier it is to 
scan for LANGUAGE pragmas.  That search doesn't need to deal with 
keywords at all. (although it may be popular not to use the usual lexer 
in order to search for those pragmas, I don't know)


Isaac


More information about the Haskell-prime mailing list