[Haskell-cafe] Qualified import syntax badly designed (?)
wren ng thornton
wren at freegeek.org
Wed Jul 9 01:03:52 EDT 2008
Quoth skynare at gmail.com:
> Quoth Neil Mitchell <ndmitchell at gmail.com>:
> > [...]
> >
> > Both of these require two imports, yet feel like they should require
> > only one. It seems as though the import syntax more naturally promotes
> > security (preventing access to some functions), rather than
> > namespacing.
> >
> > I think a better design for namespacing might be:
> >
> > import Data.Map as M implicit (Map)
> > import Data.Map as M explicit (lookup)
> >
> > If this was the design, I'm not sure either qualified or hiding would
> > be necessary for namespacing. You'd get module names aligning up in
> > the same column after the import rather than being broken up with
> > qualified. You'd only need one import of a module for most purposes.
> > The hiding keyword might still be nice for lambdabot style
> > applications, but that is probably a secondary concern, and better
> > handled in other ways.
> >
> > Thoughts? Is this design flawed in some way? Does the existing design
> > have some compelling benefit I've overlooked?
>
> How about using + and - prefixes instead of implicit and explicit clause?
>
> \begin{code}
> module T where
>
> import Data.Map (Map, (\\))
> import qualified Data.Map as M hiding (lookup)
>
> f :: (Ord k) => Map k v -> k -> Map k v
> f m k = m \\ M.singleton k (m M.! k)
> \end{code}
>
> the following import command would mean the same:
> import qualified Data.Map as M (+Map, -lookup, +singleton, +(\\))
What I would like to see is the ability to do (1) module renaming, (2)
qualified import, (3) unqualified import, and (4) hiding all in a single
declaration with a regular syntax. For example:
import Data.Map as Map
unqualified (Map, (\\))
qualified (lookup, map, null)
hiding (filter)
To simplify this full generality for the common cases:
* At most one of the lists can be dropped, keeping the keyword, to mean
"everything else".
* Naturally if both the qualified and unqualified clauses have lists,
then everything else is assumed to be hidden and so the 'hiding' keyword
can be dropped too.
* Similarly, if any clause has an empty list, both the keyword and the
() can be dropped.
* A special case can be made when all three clauses are dropped so that,
if there's no 'as'-clause then everything is imported unqualified,
otherwise everything is imported qualified.
* Another special case to better mimic the current syntax is that if
neither 'qualified'- nor 'hiding'-clauses are present, then the
'unqualified' keyword can be dropped (retaining the list of imports).
As Neil mentioned, the most common idioms are to combine
unqualified/hiding or unqualified/qualified, but allowing all three
makes the syntax more consistent. And there are times when we would want
all three, such as when being very specific about expressing
dependencies: unqualified types and operators (for sanity), qualified
functions (for explicitness), hidden "dangerous"/known-unused functions
(for safety).
With the abbreviations above, this syntax is almost a proper superset of
the current syntax. The main incompatible difference is moving the
'qualified' keyword to make the syntax more consistent.
--
Live well,
~wren
More information about the Haskell-Cafe
mailing list