Qualified import syntax badly designed (?)

Hi, It seems that the qualified import syntax is a bit awkward. At the moment, its common to see: import qualified Data.Map as M import Data.Map(Map) i.e. import a module, give it an alias (M), and put some things in the current namespace (Map). Another way some people sometimes do it is: import qualified Data.Map as M import Data.Map hiding (lookup) i.e. import a module, give it an alias (M), and exclude some things from the current namespace. 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? Thanks Neil

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, +(\\))
On 7/8/08, Neil Mitchell
Hi,
It seems that the qualified import syntax is a bit awkward. At the moment, its common to see:
import qualified Data.Map as M import Data.Map(Map)
i.e. import a module, give it an alias (M), and put some things in the current namespace (Map).
Another way some people sometimes do it is:
import qualified Data.Map as M import Data.Map hiding (lookup)
i.e. import a module, give it an alias (M), and exclude some things from the current namespace.
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?
Thanks
Neil _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Quoth skynare@gmail.com:
Quoth Neil Mitchell
: [...]
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

Hi
declaration with a regular syntax. For example:
import Data.Map as Map unqualified (Map, (\\)) qualified (lookup, map, null) hiding (filter)
I think I prefer this to my proposal, plus its closer to the current syntax. I think its also nearly equal to what Tom Davie came up with, given some keyword renaming. If we dropped the unqualified keyword, and just required unqualified things to come directly after, we get the full benefits of not introducing any keywords.
* 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.
That's not the current semantics. Currently 'as' means everything is imported unqualified and also qualified.
Why 'implicit' and 'explicit'? Do you mean something like 'include' and 'exclude'?
I want to refer to these things explicitly (with a module name), I want to refer to these things implicitly (without a module name). I have no particular attachment to the keywords - think of it as a discussion starter rather than a suggestion. Thanks Neil

Neil Mitchell wrote:
Hi
declaration with a regular syntax. For example:
import Data.Map as Map unqualified (Map, (\\)) qualified (lookup, map, null) hiding (filter)
I think I prefer this to my proposal, plus its closer to the current syntax. I think its also nearly equal to what Tom Davie came up with, given some keyword renaming. If we dropped the unqualified keyword, and just required unqualified things to come directly after, we get the full benefits of not introducing any keywords.
Just to say that I also like this design. A minor point would be; do we really need the parentheses and commas? or could we not just use indentation (I think this about module imports in general). Also I wouldn't mind 'as' for the names which are imported which would be a bit of a work around for the debate as to whether I should design my modules for qualified import or not. Suppose I make a 'NewList' module and use the default names then someone could do: import Data.NewList unqualified map as nlMap find as nlFind lookup as nlLookup or vice-versa. regards allan -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.

Hi
Just to say that I also like this design. A minor point would be; do we really need the parentheses and commas? or could we not just use indentation (I think this about module imports in general).
Yes, then you could just uses {a;b} to get the list which is actually a newline list. I think this would be even better for module declarations. For example, in the module I'm currently working on: module Hoogle.DataBase.TypeSearch.Graph( Graph, newGraph, GraphResult(..), ArgPos, Binding, graphSearch ) where I dislike the fact that ,'s come after every line but the last - it lacks consistency, and often requires 1 more line of diff when adding somethign (add comma to previous line, and add the line). I would rather write: module Hoogle.DataBase.TypeSearch.Graph{ Graph; newGraph GraphResult(..); ArgPos; Binding graphSearch } where However, I think the new syntax for modules, and the new type of declarations for modules, are separate issues.
Also I wouldn't mind 'as' for the names which are imported which would be a bit of a work around for the debate as to whether I should design my modules for qualified import or not. Suppose I make a 'NewList' module and use the default names then someone could do: import Data.NewList unqualified map as nlMap find as nlFind lookup as nlLookup
I believe old versions of Haskell had this, and it was considered too confusing. Consider: import Prelude unqualified (+) as (-) Also people reading the code will find it easier to know N = Data.NewList (one mapping), than three mappings as you have. Thanks Neil

Neil Mitchell wrote:
Hi
Just to say that I also like this design. A minor point would be; do we really need the parentheses and commas? or could we not just use indentation (I think this about module imports in general).
[snip general agreement]
However, I think the new syntax for modules, and the new type of declarations for modules, are separate issues.
Sure!
Also I wouldn't mind 'as' for the names which are imported which would be a bit of a work around for the debate as to whether I should design my modules for qualified import or not. Suppose I make a 'NewList' module and use the default names then someone could do: import Data.NewList unqualified map as nlMap find as nlFind lookup as nlLookup
I believe old versions of Haskell had this, and it was considered too confusing. Consider:
import Prelude unqualified (+) as (-)
Also people reading the code will find it easier to know N = Data.NewList (one mapping), than three mappings as you have.
Yes I generally agree there, I don't think 'as' for imported names is particularly important and if it's been tried before and found to be confusing well then that pretty much settles it for me. If I were particularly for it then I'd point out that: import Prelude unqualified (+) as (-) would only be written by someone with limited common sense or someone trying to break things (but I'm sure you could come up with a more realistic example). More importantly for me is the consistency you mentioned, for me it seems inconsistent that you can remap a module name but not an imported identifier. That said, your point about knowing one or three mappings is somewhat compelling and I'm now somewhat less in favour of 'as' for imported names. regards allan -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.

On Wed, 9 Jul 2008, Neil Mitchell wrote:
For example, in the module I'm currently working on:
module Hoogle.DataBase.TypeSearch.Graph( Graph, newGraph, GraphResult(..), ArgPos, Binding, graphSearch ) where
I dislike the fact that ,'s come after every line but the last - it lacks consistency, and often requires 1 more line of diff when adding somethign (add comma to previous line, and add the line). I would rather write:
Also in the current syntax it is allowed to add a comma in the last line.

On Wed, 2008-07-09 at 12:36 +0200, Henning Thielemann wrote:
On Wed, 9 Jul 2008, Neil Mitchell wrote:
For example, in the module I'm currently working on:
module Hoogle.DataBase.TypeSearch.Graph( Graph, newGraph, GraphResult(..), ArgPos, Binding, graphSearch ) where
I dislike the fact that ,'s come after every line but the last - it lacks consistency, and often requires 1 more line of diff when adding somethign (add comma to previous line, and add the line). I would rather write:
Also in the current syntax it is allowed to add a comma in the last line.
GHC rejects this. (Or is that just for import lists?) jcc

Neil Mitchell wrote:
Hi
declaration with a regular syntax. For example:
import Data.Map as Map unqualified (Map, (\\)) qualified (lookup, map, null) hiding (filter)
I think I prefer this to my proposal, plus its closer to the current syntax. I think its also nearly equal to what Tom Davie came up with, given some keyword renaming. If we dropped the unqualified keyword, and just required unqualified things to come directly after, we get the full benefits of not introducing any keywords.
We're still not introducing any keywords either way, fortunately :-). 'qualified', 'as' and 'hiding' are not keywords: the syntax after 'import' has no place for lowercase identifiers, so we can use as many new words as we want, here, as long as module names stay capitalized and import lists remain parenthesized (or, import lists could equally well be in layout after 'where', 'of', 'let' or 'do' if we adopt the layout syntax) -Isaac

On Wed, Jul 9, 2008 at 1:03 AM, wren ng thornton
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)
I've often thought it would be for Haskell to steal Agda's module
syntax. It does pretty much everything you want (plus some other stuff
we maybe don't need) and the various things it does fit together
logically.
--
Dave Menendez

David Menendez
I've often thought it would be for Haskell to steal Agda's module syntax. It does pretty much everything you want (plus some other stuff we maybe don't need) and the various things it does fit together logically.
What does that look like? I've been looking for some kind of documentation for ~20 minutes and I still can't find an example of an import. -- _jsn

On Wed, Jul 9, 2008 at 2:51 PM, Jason Dusek
David Menendez
wrote: I've often thought it would be for Haskell to steal Agda's module syntax. It does pretty much everything you want (plus some other stuff we maybe don't need) and the various things it does fit together logically.
What does that look like? I've been looking for some kind of documentation for ~20 minutes and I still can't find an example of an import.
There's a description on their wiki at
http://appserv.cs.chalmers.se/users/ulfn/wiki/agda.php?n=Docs.ModuleSystem.
There's a longer description in chapter 4 of Ulf Norell's thesis,
http://www.cs.chalmers.se/~ulfn/papers/thesis.pdf, which may be
slightly out of date.
Essentially, the import statement in Agda brings a module from another
file into scope as if it were a sub-module in the current file. It
also lets you rename the module, in case it conflicts with another
name. It does not bring any values or types into scope; they are
accessed by qualified names.
import Some.Module
import Some.Other.Module as SOM
A separate statement lets you bring names from any module into the
current scope. You can provide a list of names to include or exclude,
and a list of names to rename.
open SOM using (x,y)
open SOM renaming (x as alsoX, y as alsoY)
open SOM hiding (x,y)
You can combine renaming with using or hiding, but you can't use using
or hiding together. Note that hidden names are still accessible as
qualified names. That is, if you open SOM hiding x, you can still say
"SOM.x".
There's also a short-hand form that lets you import a module and open
it on the same line.
Aside from the syntax differences, Agda's module system features
nested modules and parameterized modules, both of which could be
pretty handy in Haskell.
Nested modules allow libraries which have many modules with similar
names to use qualified names.
open import Gtk using (module Button, module Window)
f = ... Button.name ... Window.name ...
Parameterized modules work sort of like implicit arguments. I suspect
that having them in Haskell could eliminate most of the call for
things like top-level IORefs.
--
Dave Menendez

David Menendez
Jason Dusek
wrote: David Menendez
wrote: I've often thought it would be for Haskell to steal Agda's module syntax.
What does that look like? I've been looking for some kind of documentation for ~20 minutes and I still can't find an example of an import.
There's a description on their wiki at http://appserv.cs.chalmers.se/users/ulfn/wiki/agda.php?n=Docs.ModuleSystem.
Thanks. That system is pretty neat -- I wish we had it. Without parameterized modules, we are reduced to a kind of warty singleton pattern -- or IORefs, as you mention. -- _jsn

On Tue, 8 Jul 2008, skynare@gmail.com wrote:
How about using + and - prefixes instead of implicit and explicit clause?
Hiding of identifiers is the wrong way round. It fails if new identifiers are added to a module interface: http://www.haskell.org/haskellwiki/Import_modules_properly For one-line imports, see: http://www.haskell.org/haskellwiki/Qualified_names

On Wed, 9 Jul 2008, Neil Mitchell wrote:
It seems that the qualified import syntax is a bit awkward. At the moment, its common to see:
import qualified Data.Map as M import Data.Map(Map)
i.e. import a module, give it an alias (M), and put some things in the current namespace (Map).
Another way some people sometimes do it is:
import qualified Data.Map as M import Data.Map hiding (lookup)
i.e. import a module, give it an alias (M), and exclude some things from the current namespace.
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)
Why 'implicit' and 'explicit'? Do you mean something like 'include' and 'exclude'?

I think a better design for namespacing might be:
import Data.Map as M implicit (Map) import Data.Map as M explicit (lookup)
Why 'implicit' and 'explicit'? Do you mean something like 'include' and 'exclude'?
To me at least, implicit and explicit make more sense. I don't want to exclude importing lookup, I want to make it so I have to explicitly tag lookup as being M.lookup. Similarly, I don't want to include Map (as opposed to all the other things I'm getting from Data.Map), I just want to make it so that when I say Map, I implicitly mean M.Map. Personally I'd extend this syntax (something Neil may have had in mind), so that import Data.Map as M (lookup, union) implicit (Map) gives me M.lookup, M.union and Map while import Data.Map as M hiding (union) explicit (lookup) gives me everything in Data.Map with no qualification except for union and lookup, plus it gives me M.lookup. Bob

On Wed, Jul 9, 2008 at 10:01 AM, Neil Mitchell
It seems that the qualified import syntax is a bit awkward. At the moment, its common to see:
import qualified Data.Map as M import Data.Map(Map)
i.e. import a module, give it an alias (M), and put some things in the current namespace (Map).
Incidentally, I sometimes find myself writing this: import Data.Map (Map) ; import qualified Data.Map as M It's not perfect, but at least it lines up with my other imports a little better. Stuart
participants (11)
-
allan
-
David Menendez
-
Henning Thielemann
-
Isaac Dupree
-
Jason Dusek
-
Jonathan Cast
-
Neil Mitchell
-
skynare@gmail.com
-
Stuart Cook
-
Thomas Davie
-
wren ng thornton