[Haskell-cafe] Rename When Import (was: Type Directed Name
Resolution)
Albert Y. C. Lai
trebla at vex.net
Wed Nov 10 14:51:11 EST 2010
A better solution to import-induced name clashes is Rename When Import.
You can already rename the module when importing. Let's rename the
imported names too.
Assume I want to import this module:
module SinisterlyNamedModule where
data Parsec = State { stdin :: () }
| Cont { runST :: (), fromList :: [()] }
as State{} a b = a
as Cont{} a b = b
State _ <*> y = State ()
x <*> State _ = Cont () []
_ <*> _ = Cont () [()]
on Cont{} y = y
on x y at State{} = x
infixr 5 <*>
infixl 3 on
infix 1 Cont
This sinister module clashes with everything we hold dear to our hearts,
left right and centre. (Yet somehow manages to avoid clashing with
Prelude!) I now import it with renaming, left right and centre.
The syntax
import SinisterlyNamedModule(
Parsec at GoodType(State at CaseOne(stdin at gfa),
Cont at CaseTwo(runST at gfb, fromList at gfc)
),
as at goodcase,
(<*>)@foo,
on@(###)
) as GoodModule
renames SinisterlyNamedModule to GoodModule, Parsec to GoodType, State
to CaseOne, stdin to gfa, Cont to CaseTwo, runST to gfb, fromList to
gfc, as to goodcase, <*> to foo, on to ###.
I use "@" instead of "as" because "as" is not a reserved word and could
be an identifier, and "@" is a reserved word already.
I am not sure what to do with type class names and type class method
names. Perhaps allow them to be renamed too. Perhaps don't allow them to
be renamed.
Rather than using Type Directed Name Resolution to perpetuate dictating
authoritarian names to users, let's use Rename When Import so users take
back control. One name doesn't fit all. Let users choose different names
to fit different uses and contexts.
More information about the Haskell-Cafe
mailing list