From libraries@haskell.org Mon Feb 26 17:59:30 2001 Date: Mon, 26 Feb 2001 17:59:30 +0000 From: Malcolm Wallace libraries@haskell.org Subject: Proposal: module namespaces.
This is an annoucement of a new mailing list, and a proposal for
three things:

  *  An extended mechanism for module namespaces in Haskell.
  *  A "standard" namespace for new libraries, common across all systems.
  *  A social process for adding new libraries to the "standard" set.

A formatted version of this proposal appears on the web at
        http://www.cs.york.ac.uk/fp/libraries/

The new mailing list is for the discussion of these proposals.
Please subscribe if you are interested.  Follow-ups set accordingly.

Mailing list details
--------------------
                      libraries@haskell.org

The purpose for this new list is to: 
  (a) discuss an extension to Haskell to provide a richer module namespace,
  (b) discuss how to partition this namespace and populate it with libraries,
  (c) discuss how to provide a consistent set of libraries for all compilers,
      and the setting up of a common library repository.

To subscribe:  http://haskell.org/mailman/listinfo/libraries/


Introduction
------------
Everyone agrees that Haskell needs good, useful, libraries: lots of
them, well-specified, well-implemented, well-documented.  A problem
is that the current "Standard Libraries" defined by the Haskell'98
Report number only about a dozen.  But there are actually many more
libraries out there: some are in GHC's hslibs collection, others are
linked from haskell.org, even more are used only by their original
author and have no public distribution.

What is more, there is no Haskell Committee.  There is no-one
to decide which candidate libraries are worthy to be added to the
"Standard" set.  This stifles the possible distribution of great
libraries, because no-one knows how to get /my/ library "accepted".

Furthermore, the existing libraries that people distribute from
their own websites often run into problems when used alongside other
people's libraries.  A library usually consists of several modules,
but often the constituent modules have simple names that can easily
clash with modules from another library package.  This leads people
to ad hoc solutions such as prefixing all their modules with a
cryptic identifier e.g.

        HsParse
        XmlParse
        HOGLParse
        THIHParse

Just counting the libraries currently available from GHC's hslibs, and
haskell.org's links, there are currently over 200 separate modules in
semi-"standard" use.  As more libraries are written, the possibility
of clashes can only increase.

Related to this problem, although not identical, is the difficulty
of finding a library that provides exactly the functionality you need
to help you write a specific application program.  How do you go
about searching through 200+ modules for interesting-looking datatypes
and signatures, starting only from the module names?


My View
-------
My view is that many of these problems are rooted in Haskell's
restriction to a flat module namespace.  If we can address that issue
adequately, then I believe that many of the difficulties surrounding
the provision of good libraries for Haskell will simply fall away.


Proposal 1
----------
Introduce nested namespaces for modules.  The key concept here is to
map the module namespace into a hierarchical directory-like structure.
I propose using the dot as a separator, analogous to Java's usage
for namespaces.

So for instance, the four example module names above using cryptic
prefixes could perhaps be more clearly named

    Haskell.Language.Parse
    Text.Xml.Parse
    Graphics.Drawing.HOpenGL.ConfigFile.Parse
    TypeSystem.Parse

Naming proceeds from the most general category on the left, through
more specific subdivisions towards the right.

For most compilers and interpreters, this extended module namespace
maps directly to a directory/file structure in which the modules
are stored.  Storing unrelated modules in separate directories (and
related modules in the same directory) is a useful and common practice
when engineering large systems.

(But note that, just as Haskell'98 does not *insist* that modules live
in files of the same name, this proposal does not insist on it either.
However, we expect most tools to use the close correspondance to
their advantage.)

There are several issues arising from the particular proposal here.

  * This is a surface change to the module naming convention.  It
    does not introduce nested /definition/ of modules.

  * The syntax I propose (a dot separator) is familiar from other
    languages such as Java, but could in principle be something else,
    for instance a prime ' or underscore _ or centred dot · or
    something different again.

  * Of the choices of separator, dot requires a change to the Haskell'98
    lexical syntax, allowing
            modid -> qconid
    where currently the syntax is
            modid ->  conid

  * The use of qualified imports becomes more verbose: for instance
            import qualified XmlParse
                      ... XmlParse.element f ...
    becomes
            import qualified Text.Xml.Parse
                      ... Text.Xml.Parse.element f ...
    However, I propose that every import have an implicit "as"
    clause to use as an abbreviation, so in
            import qualified Text.Xml.Parse   [ as Parse ]
    the clause "as Parse" would be implicit, unless overridden by the 
    programmer with her own "as" clause.  The implicit "as" clause
    always uses the final subdivision of the module name.  So for
    instance, either the fully-qualified or abbreviated-qualified names
            Text.Xml.Parse.element
            Parse.element
    would be accepted and have the same referent, but a partial
    qualification like
            Xml.Parse.element
    would not be accepted.

  * Another consequence of using the dot as the module namespace
    separator is that it steals one extremely rare construction from
    Haskell'98:
            A.B.C.D
    in Haskell'98 means the composition of constructor D from module C,
    with constructor B from module A:
            (.)  A.B  C.D
    No-one so far thinks this is any great loss, and if you really
    want to say the latter, you still can by simply inserting spaces:
            A.B . C.D

Further down this document, I give more motivation and a rationale for
this proposal of nested namespaces.  But first, two other proposals
which rest on the first one.


Proposal 2
----------
Adopt a standardised namespace layout to help those looking for or
writing libraries, and a "Std" namespace prefix for genuinely
standard libraries.  (These are two different things.)

The hslibs collection of modules is a great starting place for
finding common libraries that could become standards.  I propose
that we adopt a "standardised" namespace hierarchy, based on the
current hslibs layout, into which Haskell programmers can plug their
own libraries relatively easily (whether they intend to release them or
not).  The aim is to make it clear where to place a new module, and
where to search for a possible existing module.

For instance, in ASCII art, here is a small part of a suggested tree.

    + Data + Structures + Trees + AVL
    |      |            |       + RedBlack
    |      |            |
    |      |            + Queue + Bankers
    |      |                    + FIFO
    |      + Encoding + Binary
    |                 + MD5
    |
    + Graphics + UI + Gtk + Widget
    |          |    |     + Pane
    |          |    |     + Text
    |          |    | 
    |          |    + FranTk
    |          |
    |          + Drawing + HOpenGL + ....
    |          |         + Vector
    |          |
    |          + Format + Jpeg
    |                   + PPM
    + Haskell + ....
    |

A fuller proposed layout appears on the web at
    http://www.cs.york.ac.uk/fp/libraries/layout.html

In addition to a standardised hierarchy layout, I propose a truly
Standard-with-a-capital-S namespace.  A separate discussion is needed
on what exactly would consitute "Standard" quality, but by analogy
with Java where everything beginning "java." is sanctioned by Sun,
I propose that every module name beginning "Std." is in some sense
sanctioned by the whole Haskell community.

So for instance, an experimental, or not-quite-complete, library
could be called

    Text.Xml

but only a guaranteed-to-be-stable, complete, library could be called

    Std.Text.Xml

The implication of the Std. namespace is that all such "standard"
libraries will be distributed with all Haskell systems.  In other
words, you can rely on a standard library always being there, and
always having the same interface on all systems.


Proposal 3
----------
Develop a process by which candidate libraries can be proposed to
enter the Std namespace.

Since Haskell'98 is fixed, and there is no longer a Haskell Committee,
there is no official body capable of deciding new standards for
libraries.  However, we do have a Haskell community which will use
or not use libraries, depending on their quality.  So libraries will
become standards by a de-facto process, rather than de-jure.

Apart from the Haskell compiler implementers, we wanted a means to
encourage the whole community to be involved in recognising de facto
"standard" libraries.  The mailing list 'libraries@haskell.org'
is one contribution.  We hope this will work on the same model as
the FFI mailing list, which has been pretty successful at allowing a
community of designers and implementers to explore their FFI needs and
solidify a design that is common across at least three Haskell systems.

On top of this discussion however, some final decisions will have to
be made on which libraries achieve entry to the "Std." namespace.  The
Haskell implementers have collectively proposed a ruling troika, one
representing each of the three main Haskell systems (Hugs,ghc,nhc98).
These are Simon Marlow, representing ghc, and current keeper of the
hslibs collection;  Malcolm Wallace, representing nhc98; and Andy Gill,
representing Hugs users.

Some obvious criteria for entry to the "Std." namespace would be:

   * The interface is stable and unlikely to change significantly;
   * The library is written in pure Haskell'98.  This criterion
     is likely to be the most contentious, so perhaps a better
     idea would be that ...
   * ... an implementation exists for at least the three Haskell
     systems Hugs, ghc, and nhc98;
   * The library is already in current use, so bugs in its coding and
     design have been ironed out;
   * The Haskell community recognises it as solving a common task,
     or encapsulating a common programming idiom.

These suggested criteria need some discussion and improvement.

After the initial period of deciding what belongs in the "Std."
namespace, I would expect any further candidate libraries that
are proposed for standardisation to spend some time in another
part of the namespace hierarchy whilst they gain stability and
common acceptance, before being moved to "Std.".



Rationale and Motivation for Proposal 1 (nested namespaces)
-----------------------------------------------------------

Scenario 1
----------
Imagine you have just written a new library of, say, Pretty-printing
combinators.  You want to release it to the Haskell public.  So what
do you call it?

    module Pretty	-- already taken (several times)
    module UU_Pretty	-- also taken
    module PrettyLib	-- already exists as well

Ok, so lacking any further inspiration, you end up deciding to call it

    module MyPretty	-- !

Surely there must be a better solution.  Of course there is - namespaces.
Let's classify libraries that do similar jobs together:

    module Text.PrettyPrinter.Hughes	-- the original Hughes design
    module Text.PrettyPrinter.HughesPJ	-- later modified by Simon PJ
    module Text.PrettyPrinter.UU	-- the Utrecht design
    module Text.PrettyPrinter.Chitil	-- Olaf's new design

These are exactly the same Pretty libs as before, but named more
sensibly.  It is still clear that each is a pretty-printing library,
but it is also clear that they are different.

Incidentally, have you ever tried to write your own module called
Pretty?  You may have discovered with GHC (which has a Pretty already
in the hslibs collection), that you get strange errors.  This is
because sometimes the compiler can be confused into reading one
Pretty.hi interface file (i.e. yours), yet linking the other Pretty.o
object file (i.e. from hslibs), ending in a core dump.  With proper
module namespaces, this confusion should never happen again.

Scenario 2
----------
You are writing a complex library that has a couple of layers
of abstraction.  For some users, you want to expose just a small
high-level set of types and functions.  Other users will need
more detailed access to lower-level stuff.

With namespaces, you can use the directory-like structure to make these
kinds of access explicit.  For instance, imagine a socket library:

    module Network.Socket

It exports an /abstract/ type Socket for ordinary users - they only
need to know its name.  More advanced hackers however can play with
the details of the type, because you also have:

    module Network.Socket.Types

which exports the Socket type non-abstractly i.e. Socket(..).  And of
course this abstraction is easy for the library-writer to manage,
because the implementation of the more abstract layer simply imports
and re-exports a careful selection of the more detailed layers.

Don't forget that, in terms of the actual filesystem layout, it is
perfectly OK to have e.g.

    file  Network/Socket.hs
    dir   NetWork/Socket
    file  Network/Socket/Types.hs

Scenario 3
----------
You are managing a software engineering project.  Several people
are working more-or-less independently on different sections of the
program.  To avoid mistakes with files, you give each one a separate
directory to place their code in.  But in Haskell'98 this is not
enough to ensure that they invent module names that do not clash with
other developers' modules.  So you insist that everyone also uses a
prefix-naming scheme for each appropriate sub-task.

For instance, here is a sketch of the layout of the Galois Connection
team's entry in the ICFP 2000 programming contest:

    dir  CSG			-- constructive solid geometry
    file CSG/CSG.hs
    file CSG/CSGConstruct.hs
    file CSG/CSGGeometry.hs
    file CSG/CSGInterval.hs
    dir  Fran			-- Fran-style animation
    file Fran/FranLite.hs
    file Fran/FranCSG.hs
    dir  GML			-- interpreter for little language
    file GML/GMLData.hs
    file GML/GMLParse.hs
    file GML/GMLPrimitives.hs

So now the problem is that to actually build the software, you need
to write a Makefile that descends into these directories.  Or maybe
you use 'hmake' like so:

    hmake examples/chess.hs -ICSG -IFran -IGML -IRayTrace -package text

Note how many sub-directories you must remember to add to the
command line (this applies equally for compiler options in Makefiles).
Note also the inconsistency between compiling and linking /my/ modules,
against using and linking a "standard" hslibs module from package text.

Isn't there a simpler way?  Yes.  Namespaces.  Prefix naming is no
longer needed inside directories, because the directory name is /part/
of the module name:

    file CSG.hs			-- re-exports everything from the CSG dir
    dir  CSG
    file CSG/Construct.hs
    file CSG/Geometry.hs
    file CSG/Interval.hs
    dir  Fran
    file Fran/Lite.hs
    file Fran/CSG.hs		-- does not conflict with top-level CSG.hs
    dir  GML
    file GML/Data.hs
    file GML/Parse.hs
    file GML/Primitives.hs

And now, the commandline to 'hmake' (or compiler options in a Makefile)
becomes simply:

    hmake examples/chess.hs -I.

You only need to specify the root of the module tree (-I.), and all
modules in all subdirectories can be found via their full namespace
path as used in the source files.  Note also that, whereas previously
we needed to specify a package for whatever hslibs modules were
used, now the compiler/hmake already knows the root of the installed
hslibs tree and can use the same mechanism to find and link "standard"
modules as for user modules.

>From this example it should be clear that the use of module namespaces
is of benefit to ordinary programs that may never become public,
quite aside from any benefits we expect to derive in managing
publically-distributed library code.

What now?
---------
Ok, so that's my proposal.  The implementers of some of the main
Haskell systems have seen a presentation of these ideas, and seemed to
like them.  Namespaces are already implemented in nhc98 (v1.02) and
hmake (v2.02) if you want to play with them.  I expect some discussion
to refine this proposal on the 'libraries@haskell.org' list, to
which everyone interested is invited.

Once we have nailed down the precise design, we need to get matching
implementations in all systems.  I have rashly volunteered to implement
the lexical/parsing/module-search changes in any Haskell system that
no-one else volunteers for (probably ghc, Hugs, possibly hbc).

But after that we will still have many more decisions to take about
individual libraries, precise naming, build systems, and so on, not
to mention actually writing the libraries.  Get involved.  Contribute.

Regards,
    Malcolm



From joe@isun.informatik.uni-leipzig.de Tue Feb 27 09:15:21 2001 Date: Tue, 27 Feb 2001 10:15:21 +0100 (MET) From: Johannes Waldmann joe@isun.informatik.uni-leipzig.de Subject: yes please
Dear Malcolm, I fully aggree with rationale and motivation
for your module namespace proposals.

While teaching Haskell I noticed that the more I really did 
what I was preaching to the students, namely, 
writing re-useable code by factoring out common patterns,
I ran into module namespace problems.

So I will start using proposal-1 the day it will be implemented for hugs.

I can't think of any arguments that would speak against the proposal.
Are there any?

At some time in the future, the proposal needs a formal definition
of how the source/interface file for the imported module is actually found.
At the moment, it is "just like you would expect, 
and if you have questions, look in the Java definition"? 
Well that's OK for now, but a language standard should be self-contained.

Best regards,
-- 
-- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ --
-- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 --


From ketil@ii.uib.no Tue Feb 27 10:42:58 2001 Date: 27 Feb 2001 11:42:58 +0100 From: Ketil Malde ketil@ii.uib.no Subject: Proposal: module namespaces.
Malcolm Wallace <Malcolm.Wallace@cs.york.ac.uk> writes:

> Proposal 1
> ----------
> Introduce nested namespaces for modules.  The key concept here is to
> map the module namespace into a hierarchical directory-like structure.
>   * The use of qualified imports becomes more verbose: for instance
        [...]
>     instance, either the fully-qualified or abbreviated-qualified names
>             Text.Xml.Parse.element
>             Parse.element
>     would be accepted and have the same referent, but a partial
>     qualification like
>             Xml.Parse.element
>     would not be accepted.

Why not?

Perhaps one could have a warning/error if there are multiple "Parse"
modules? 

>   * Another consequence of using the dot as the module namespace
>     separator is that it steals one extremely rare construction from
>     Haskell'98:
        [...]
>     No-one so far thinks this is any great loss, and if you really
>     want to say the latter, you still can by simply inserting spaces:
>             A.B . C.D

Personally, I'm not overly enthusiastic about using (.) for function
composition - but I guess e.g the degrees sign was ruled out since
it's not in (7bit) ASCII - and I think it should require spaces
anyway, in order to differentiate it from its other uses.

> Proposal 2
> ----------
> Adopt a standardised namespace layout to help those looking for or
> writing libraries, and a "Std" namespace prefix for genuinely
> standard libraries.  (These are two different things.)

Sounds good!

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants


From simonmar@microsoft.com Tue Feb 27 10:47:21 2001 Date: Tue, 27 Feb 2001 10:47:21 -0000 From: Simon Marlow simonmar@microsoft.com Subject: Hierarchy suggestions
Firstly, I'd like to say this proposal is great.  We're in dire need of
extending the module namespace, and it's important that we do it in a
community-directed way.

Proposals 1 & 3: no problem.

Proposal 2: I think we should spend a lot of effort designing the layout
of the module hierarchy, at least the standard parts, to make it as
"future proof" as possible.  We really don't want to be reorganising
things later.

1) Std.

I have a feeling that the "Std." prefix is going to be annoying,
especially when libraries move from the base hierarchy to the Std
hierarchy.  It doesn't fit well with the idea that the hierarchy should
be as static as possible. =20

A portable application will only use libraries from the Std hierarchy,
so we should make this the default.  Non-standard libraries should get
the prefix, if any.

An alternative is to simply sanction each library individually, as the
interface is fixed and a portable, well-tested implementation exists.
Non-sanctioned libraries aren't necessarily provided by all of the main
implementations, and their interfaces may change (or even differ across
implementations).

2) Haskell->Plus

At some point in the future, Haskell will no doubt include the FFI, at
which point the Haskell->Plus->FFI hierarchy won't make sense any more,
and we'll have to break lots of existing code to move the library
somewhere sensible.

I suggest just calling it "Foreign", and putting it near the top of the
hierarchy somewhere.  Similarly for Concurrent, Exceptions, etc.


I have a fairly complete hierarchy sketched out, but I'm going to revise
it based on your ideas and send it out later.

Cheers,
	Simon


From joe@isun.informatik.uni-leipzig.de Tue Feb 27 10:58:04 2001 Date: Tue, 27 Feb 2001 11:58:04 +0100 (MET) From: Johannes Waldmann joe@isun.informatik.uni-leipzig.de Subject: Hierarchy suggestions
on module prefixes (= directory names).

perhaps there could be renaming declarations 
not only for modules, but also for prefixes.


say you have modules Foo.Frobs and Bar.Frobs, then you could

import Foo as X
import X.Frobs 


there would normally be an implicit "import Standard",
but you could override with "import Experimental as Standard" 


of course this could cause more problems than it solves.
-- 
-- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ --
-- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 --


From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 12:02:51 2001 Date: Tue, 27 Feb 2001 12:02:51 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: Proposal: module namespaces.
Ketil Malde writes:

> >     instance, either the fully-qualified or abbreviated-qualified names
> >             Text.Xml.Parse.element
> >             Parse.element
> >     would be accepted and have the same referent, but a partial
> >     qualification like
> >             Xml.Parse.element
> >     would not be accepted.
> 
> Why not?

I suppose it would be possible to have an implicit

      import A.B.C.D.E as E
      import A.B.C.D.E as D.E
      import A.B.C.D.E as C.D.E
      import A.B.C.D.E as B.C.D.E

To me, this seems like it introduces extra complexity with little
benefit for ease of use.  Wouldn't it be confusing to use C.D.E at
some places in a program, and D.E at others?  It isn't necessarily
obvious that they refer to the same entity.  After all, what if
your project has a module hierarchy like:

    A/B/C/D/E
    B/C/D/E
    Z/B/C/D/E
    R/S/T/D/E

?  To which of these paths might D.E refer?  No, I think that
restricting the implicit 'as' declaration to the simplest convenient
case (just the last component) is the best compromise to improve
readability, without introducing too many potential pitfalls.

And of course, you can always give an explicit 'as' clause if you wish.

> Perhaps one could have a warning/error if there are multiple "Parse"
> modules? 

This is kind-of what currently happens in Haskell'98.  You can rename
two imports to the same qualifier:

    import A as M
    import B as M

Provided that function f appears in only one of A or B, the qualified
name M.f is resolved correctly.  If function g is defined in both, then
M.g is ambiguous and the compiler gives an error - but only if you
actually mention M.g.  It is okay for A and B to have overlapping
definitions provided you don't try to use one of them.

> Personally, I'm not overly enthusiastic about using (.) for function
> composition - but I guess e.g the degrees sign was ruled out since
> it's not in (7bit) ASCII - and I think it should require spaces
> anyway, in order to differentiate it from its other uses.

I have been thinking about defining centred dot   in nhc98's Prelude
as a synonym for the composition operator.  Perhaps other Haskell
systems might be prepared to do the same?  (On my system I can type
a centred dot easily with the sequence Compose-dot-dot.)

Regards,
    Malcolm


From sk@mathematik.uni-ulm.de Tue Feb 27 12:52:06 2001 Date: Tue, 27 Feb 2001 13:52:06 +0100 From: Stefan Karrmann sk@mathematik.uni-ulm.de Subject: Proposal: module namespaces.
Malcolm Wallace schrieb folgendes am Mon, Feb 26, 2001 at 05:59:30PM +0000:
> Proposal 2
> ----------
> but only a guaranteed-to-be-stable, complete, library could be called
> 
>     Std.Text.Xml
> 
> The implication of the Std. namespace is that all such "standard"
> libraries will be distributed with all Haskell systems.  In other
> words, you can rely on a standard library always being there, and
> always having the same interface on all systems.

What's about version changes? How can anybody garantee that a library is stable?
Some functions or instances may become obsolete or even disappear. Other
may be needed in later versions of the library.

Regards,
-- 
Stefan Karrmann


From sk@mathematik.uni-ulm.de Tue Feb 27 12:52:06 2001 Date: Tue, 27 Feb 2001 13:52:06 +0100 From: Stefan Karrmann sk@mathematik.uni-ulm.de Subject: Proposal: module namespaces.
Malcolm Wallace schrieb folgendes am Mon, Feb 26, 2001 at 05:59:30PM +0000:
> Proposal 2
> ----------
> but only a guaranteed-to-be-stable, complete, library could be called
> 
>     Std.Text.Xml
> 
> The implication of the Std. namespace is that all such "standard"
> libraries will be distributed with all Haskell systems.  In other
> words, you can rely on a standard library always being there, and
> always having the same interface on all systems.

What's about version changes? How can anybody garantee that a library is stable?
Some functions or instances may become obsolete or even disappear. Other
may be needed in later versions of the library.

Regards,
-- 
Stefan Karrmann


From franka@cs.uu.nl Tue Feb 27 13:01:40 2001 Date: Tue, 27 Feb 2001 14:01:40 +0100 From: Frank Atanassow franka@cs.uu.nl Subject: Proposal: module namespaces.
I have two nitpicking comments.

Malcolm Wallace wrote (on 26-02-01 17:59 +0000):
>   * The use of qualified imports becomes more verbose: for instance
>             import qualified XmlParse
>                       ... XmlParse.element f ...
>     becomes
>             import qualified Text.Xml.Parse
>                       ... Text.Xml.Parse.element f ...
>     However, I propose that every import have an implicit "as"
>     clause to use as an abbreviation, so in
>             import qualified Text.Xml.Parse   [ as Parse ]
>     the clause "as Parse" would be implicit, unless overridden by the 
>     programmer with her own "as" clause.  The implicit "as" clause
>     always uses the final subdivision of the module name.  So for
>     instance, either the fully-qualified or abbreviated-qualified names
>             Text.Xml.Parse.element
>             Parse.element
>     would be accepted and have the same referent, but a partial
>     qualification like
>             Xml.Parse.element
>     would not be accepted.

I don't like the implicit "as". The reason for having a tree structure for
names is that leaves are likely to collide. So I might use both
Text.ParserCombinators.UU and Text.PrettyPrinter.UU. In this case I might want
to use the declarations:

  import qualified Text.ParserCombinators.UU as PC
  import qualified Text.PrettyPrinter.UU as PP

Since a person is likely to use several packages in the same subtree quite
often, and in our goal of a "library-rich world" we expect a plethora of
implementations from disparate sources, I wonder whether the default "as" is
useful enough in practice. As an example, in cases where sibling modules
actually have the same interface and you want to write a client module which
can use either implementation interchangeably, you would always use an
explicit "as" anyway, since you want to write, say, "Tree.map" rather than
"AVL.map" or "RedBlack.map".

Besides, it is only a few more characters to make it explicit, and I think it
is better to avoid implicit behavior when possible.

Well, I don't care too much.

I care more about:

> A fuller proposed layout appears on the web at
>     http://www.cs.york.ac.uk/fp/libraries/layout.html

I wish we could agree on capitalization of acronyms. On one hand, we have:

  Gtk, Jpeg, Html, Xml

but on the other:

  AVL, ODBC, FIFO, MD5, UI, PPM, FFI, IO, UU, PP, DSP, FFT, FIR, URL, CGI

Personally, I prefer the first group being normalized to uppercase rather
than vice versa, since "JPEG" and "HTML" look right, but "Url" and "Odbc" look
terribly wrong. (Unless you are Dutch, in which case maybe "Ui" looks good but
is still misleading. :)

Other miscellanea:

  * I think the top-level "Interface" is better named "Console", to contrast
    with "Graphics".

  * I would prefer short names to long. So: "Text.Parse" rather than
    "Text.ParserCombinators", "Data.Struct" rather than "Data.Structures",
    "Graphics.Draw" rather than "Graphics.Drawing", etc. Generally, the
    ancestors of a short name should give enough context to disambiguate it.

  * I would move "Format" out of "Graphics" and into "Data.Encoding". (But
    maybe "Encoding" is intended to be a collection of things of `universal'
    encodings, which clearly "Jpeg", for example, is not.)

  * Change "Data.Structures.Trees" and "...Graphs" from plural to
    singular. Same for "Data.Encoding.Bits". But not "Data" to "Datum"! :)

  * Maybe change "Data.Structures" and "Data.Encoding" to one name each,
    "DataStruct" and "DataEncoding" (or "Encoding" or "Codec"). The reason is
    that it's not clear to me why they belong in the same subtree except for
    the fact that in English both terms start with "Data". In other words, we
    should try to group things semantically rather than lexically.

-- 
Frank Atanassow, Information & Computing Sciences, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-3261 Fax +31 (030) 251-379


From Christian.Brolin@carmen.se Tue Feb 27 13:19:30 2001 Date: Tue, 27 Feb 2001 14:19:30 +0100 From: Christian Brolin Christian.Brolin@carmen.se Subject: Proposal: module namespaces.
Malcolm Wallace wrote:
> 
>     I propose that every import have an implicit "as"
>     clause to use as an abbreviation, so in
>             import qualified Text.Xml.Parse   [ as Parse ]
>     the clause "as Parse" would be implicit, unless overridden by the
>     programmer with her own "as" clause.  The implicit "as" clause
>     always uses the final subdivision of the module name.

What about, e.g.
  import qualified Text.Xml.Parse
  import qualified Text.Yml.Parse
?

-- 
Christian Brolin


From Christian.Brolin@carmen.se Tue Feb 27 13:20:22 2001 Date: Tue, 27 Feb 2001 14:20:22 +0100 From: Christian Brolin Christian.Brolin@carmen.se Subject: Proposal: module namespaces.
Malcolm Wallace wrote:
> 
> Proposal 1
> ----------
> Introduce nested namespaces for modules.  The key concept here is to
> map the module namespace into a hierarchical directory-like structure.
> I propose using the dot as a separator, analogous to Java's usage
> for namespaces.

I haven't commented on this if I thought it was a bad idea:)

What about the module declaration? Should it be:
  module Text.Xml.Parser where ...
or just
  module Parser where ...  -- located in Text/Xml/Parser.hs?

I prefer the latter one since I think it is wrong to specify the address
of the module in the module itself. It would be even better if the
module declaration wasn't needed at all. I don't know what it is needed
for.

I would also like to import modules using relative addresses, e.g. the
file:
  My/Small/Test/Xml/Parser.hs
contains:
  import .Lexer  -- Relative path to the module: My.Small.Test.Xml.Lexer
  import ..Data  -- Relative path to the module:
My.Small.Test.Xml.Parser.Data
  import Text.ParserCombinators.HuttonMeijer  -- Absolute address

When the world realize that this is the XML parser, they won't accept
the name and I refuse to change my implementation. The only thing that
is needed to rename (an unused) module hierarchy is to move it. 

import Std.Module
import .Sibling
import .Sibling.Child
import ..Child
import ..Child.GrandChild
import ...Syntax.Error  -- This isn't allowed

-- 
Christian Brolin


From ashley@semantic.org Tue Feb 27 13:33:26 2001 Date: Tue, 27 Feb 2001 05:33:26 -0800 From: Ashley Yakeley ashley@semantic.org Subject: Proposal: module namespaces.
At 2001-02-26 09:59, Malcolm Wallace wrote:

>Proposal 2
>----------
>Adopt a standardised namespace layout to help those looking for or
>writing libraries, 

I'm a big fan of the Java reversed DNS style. Whatever, I think it's 
important that anyone with a domain name should be able to obtain a 
unique namespace without any further bureaucracy.

In fact, whatever you decide it's likely to happen anyway, since people 
will decide that for instance "Com.Microsoft.Research.MyModule" is 
unlikely to clash with anyone outside the appropriate domains and 
subdivisions.

I'm assuming that module name components have enforced capitalisation, 
like all other Haskell identifiers.

>and a "Std" namespace prefix for genuinely
>standard libraries.  (These are two different things.)

Eeesh, let's hope ICANN doesn't register a 'std' TLD. I would prefer 
"Standard" for this reason and also because the abbreviation seems pretty 
pointless.

>In addition to a standardised hierarchy layout, I propose a truly
>Standard-with-a-capital-S namespace.  A separate discussion is needed
>on what exactly would consitute "Standard" quality, but by analogy
>with Java where everything beginning "java." is sanctioned by Sun,
>I propose that every module name beginning "Std." is in some sense
>sanctioned by the whole Haskell community.

Do you have any kind of guarantees of copyright openness in mind? In 
Java, everything under java.* is supposed to be owned by Sun.

Will it be standard practice for versions of Standard be included with 
Haskell compilers?

Could the Prelude make use of Standard?

Could Standard become an alternative to the Prelude?

If answers to these last three are all "no", an alternative would be to 
put it under "Org.Haskell.Standard".


-- 
Ashley Yakeley, Seattle WA



From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 15:35:31 2001 Date: Tue, 27 Feb 2001 15:35:31 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: Proposal: module namespaces.
> > The implication of the Std. namespace is that all such "standard"
> > libraries will be distributed with all Haskell systems.  In other
> > words, you can rely on a standard library always being there, and
> > always having the same interface on all systems.
> 
> What's about version changes? How can anybody garantee that a library is
> stable?  Some functions or instances may become obsolete or even disappear.
> Other may be needed in later versions of the library.

We can't provide absolute guarantees of course.  But this is no
different from the situation with standard libraries in other languages
- witness the difficulties with libc versions etc.  I think the best
we can do realistically is to aim for maximum stability.

In some cases, it may be sensible for a new version of a standard
library to adopt a new name, simply to make things clear.  We should
probably decide this on a case-by-case basis if/when the problem
arises.

Regards,
    Malcolm


From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:03:26 2001 Date: Tue, 27 Feb 2001 16:03:26 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: Hierarchy suggestions
> Proposal 2: I think we should spend a lot of effort designing the layout
> of the module hierarchy, at least the standard parts, to make it as
> "future proof" as possible.  We really don't want to be reorganising
> things later.

I absolutely agree.  Let's try to get the naming correct (and
extensible) right from the beginning.

> 1) Std.
> I have a feeling that the "Std." prefix is going to be annoying,
> especially when libraries move from the base hierarchy to the Std
> hierarchy.

I actually had the same feeling in some ways.  The notion of a
"privileged" Std. hierarchy was not originally part of my proposal,
but it seemed to be quite important to some of the implementers at
the Cambridge meeting where I first presented the namespaces idea.

I think many people would value a clear signal about whether a library
is truly portable or not.  Making that fact a part of the module name
is about as clear and unmistakable as you can get.

> A portable application will only use libraries from the Std hierarchy,
> so we should make this the default.  Non-standard libraries should get
> the prefix, if any.

A "NonStd." prefix perhaps?  The trouble is that it would be very
hard to police.  Anybody can write a library with any name, and it
will immediately look standard unless they take the trouble to follow
this convention.  In some ways that completely negates the meaning
of standard.  "Assume everything is a standard, unless it explicitly
says it isn't!"

> An alternative is to simply sanction each library individually, as the
> interface is fixed and a portable, well-tested implementation exists.
> Non-sanctioned libraries aren't necessarily provided by all of the main
> implementations, and their interfaces may change (or even differ across
> implementations).

This was my original idea.  But I was swayed towards proposing
a distinguished Std. namespace, mainly because of the
clarity/documentation argument.  How do I know whether a library is
portable or not?  "Well it seems to work in GHC, so it must be okay..."
It's amazing how many people think some language feature is standard
Haskell'98 just because ghc implements it!

People don't seem to complain about having to write "java." at the
beginning of all their Java imports.

> 2) Haskell->Plus
> At some point in the future, Haskell will no doubt include the FFI, at
> which point the Haskell->Plus->FFI hierarchy won't make sense any more,
> and we'll have to break lots of existing code to move the library
> somewhere sensible.

The Haskell.Plus. namespace is a cute (IMO) way to make it clear that
these libraries use extensions to pure Haskell'98.  Perhaps if we
called the namespace Haskell98.Plus. then it would be even clearer
that these things are not Haskell'98, and never will be.  When a
future version of Haskell comes along, perhaps it won't even be called
Haskell, so we will adopt a LanguageFormerlyKnownAsHaskell. hierarchy.
(Or more likely Haskell200x. I suppose)

> I suggest just calling it "Foreign", and putting it near the top of the
> hierarchy somewhere.  Similarly for Concurrent, Exceptions, etc.

Whatever, I think the name should make it clear that these libraries
require compiler/language extensions, that's the main point.

> I have a fairly complete hierarchy sketched out, but I'm going to revise
> it based on your ideas and send it out later.

Looking forward to it.  I'll place it on the web next to my current
layout proposal if you like, for comparison.  Then we should start
discussing individual branches of the hierarchy, and try to come up
with a consensus for each part, recording our progress on the web also.
(I suggest at that stage we build a new layout tree from scratch,
separate from both layout proposals, and based on agreement here on
the list).

Regards,
    Malcolm


From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:47:26 2001 Date: Tue, 27 Feb 2001 16:47:26 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: Proposal: module namespaces.
Christian writes:
> >     I propose that every import have an implicit "as"
> >     clause to use as an abbreviation,
>
> What about, e.g.
>   import qualified Text.Xml.Parse
>   import qualified Text.Yml.Parse
> ?

Just like right now in Haskell'98 with overlapping module renaming.
If a function name f is found in only one of the two libraries, Parse.f
is unambiguous.  If it occurs in both, Parse.f is ambiguous and gives
an error, but only if Parse.f is mentioned in the importing module.
The fully qualified name is unambiguous, and if you really want to be
clear, do your own explicit renaming.

Regards,
    Malcolm


From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:42:16 2001 Date: Tue, 27 Feb 2001 16:42:16 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: Proposal: module namespaces.
Frank writes:
> I wish we could agree on capitalization of acronyms. On one hand, we have:
>     Gtk, Jpeg, Html, Xml
> but on the other:
>     AVL, ODBC, FIFO, MD5, UI, PPM, FFI, IO, UU, PP, DSP, FFT, FIR, URL, CGI

Hmm, yes.  Actually, my preferred solution would be to use acronyms
only when they are extremely well known, and otherwise to spell things
out in full.  So
      Gtk, Jpeg, Html, Xml, Fifo, UI, Ppm, IO, URL, CGI
but
      ObjectDataBase, Foreign, Utrecht, PrettyPrint, SignalProcessing,
      FourierTransform, GroeltzmanFilter ...

But these things are inevitably a matter of taste.  Some people detest
the MixedUpperAndLower style.

>   I think the top-level "Interface" is better named "Console", to contrast
>   with "Graphics".

Cool.  I like it.

>   I would prefer short names to long. So: "Text.Parse" rather than
>   "Text.ParserCombinators", "Data.Struct" rather than "Data.Structures",
>   "Graphics.Draw" rather than "Graphics.Drawing", etc. Generally, the
>   ancestors of a short name should give enough context to disambiguate it.

In terms of software engineering, I think fully descriptive names
are better than abbreviations.  On the other hand, no-one likes names
that are long just for the sake of completeness.

  * Text.Parse could be ambiguous - does it contain combinator
    libraries, or support libraries for Happy?  Or maybe: Text.Parser
    - does it indeed parse text according to some syntax/grammar,
    or does it just contain functions that help you to parse text?
    Text.ParserCombinators is at least clear.

  * Graphics.Draw might indeed be better than Graphics.Drawing

  * Data.Struct - I don't like it - it sounds like C!

>   I would move "Format" out of "Graphics" and into "Data.Encoding". (But
>   maybe "Encoding" is intended to be a collection of things of `universal'
>   encodings, which clearly "Jpeg", for example, is not.)

Indeed, we do need to guard against overlapping categories.  I don't
know about this particular case - Graphics.Format seems more natural to
me.  As you say, it contains datatype-specific codecs, not universal ones.

>   Change "Data.Structures.Trees" and "...Graphs" from plural to
>   singular. Same for "Data.Encoding.Bits". But not "Data" to "Datum"! :)

Like Data.Structure.Tree etc?  Yes, looks ok.

Data.Encoding.Bits is a special case.  There are two current bit
libraries, one called Bit (in nhc98), the other called Bits (in ghc).
They even have different interfaces.  Sadly, inconsistencies like this
have grown up over the years.  But I think we can turn the situation
into a more positive one by permitting the distribution of competing
libraries - just like for pretty-printers, we can extend the namespace
to have both:

    Data.Encoding.Bit.Glasgow
    Data.Encoding.Bit.York

Mechanism, not policy.

>   Maybe change "Data.Structures" and "Data.Encoding" to one name each,
>   "DataStruct" and "DataEncoding" (or "Encoding" or "Codec"). The reason is
>   that it's not clear to me why they belong in the same subtree except for
>   the fact that in English both terms start with "Data". In other words, we
>   should try to group things semantically rather than lexically.

I quite like the name Codec.  MD5 is not a codec as such - more of
a checksum really.  For me, data structures and data codecs belong
semantically in the same subtree - it isn't just a lexical grouping.

Thanks for your suggestions!
Regards,
    Malcolm


From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:59:42 2001 Date: Tue, 27 Feb 2001 16:59:42 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: Proposal: module namespaces.
Christian writes:
> What about the module declaration? Should it be:
>   module Text.Xml.Parser where ...
> or just
>   module Parser where ...  -- located in Text/Xml/Parser.hs?

The former.  The reason is that a compiler needs to generate a unique
linker symbol for each defined function.  If the full module name is
not encoded in the source file, you will need to add a commandline
option to the compiler, which is the wrong way to go in my opinion.

Why is  e.g. Parser.f  not sufficient as a unique symbol for
Text.Xml.Parser.f?  Well, what if you also have Text.Html.Parser.f?
You really need the full thing.

> I would also like to import modules using relative addresses, e.g. the
> file:
>   My/Small/Test/Xml/Parser.hs
> contains:
>   import .Lexer  -- Relative path to the module: My.Small.Test.Xml.Lexer
>   import ..Data  -- Relative path to the module: My.Small.Test.Xml.Parser.Data
>   import Text.ParserCombinators.HuttonMeijer  -- Absolute address

I'm sorry, I don't entirely follow what the differing numbers of
initial dots mean.

> When the world realize that this is the XML parser, they won't accept
> the name and I refuse to change my implementation. The only thing that
> is needed to rename (an unused) module hierarchy is to move it. 

If you refuse to change your implementation, someone else will change
it for you!  You can't have closed standards.

Regards,
    Malcolm


From dpt@math.harvard.edu Tue Feb 27 17:09:41 2001 Date: Tue, 27 Feb 2001 12:09:41 -0500 From: Dylan Thurston dpt@math.harvard.edu Subject: Proposal: module namespaces.
On Tue, Feb 27, 2001 at 04:42:16PM +0000, Malcolm Wallace wrote:
> Frank writes:
> >   I would prefer short names to long. So: "Text.Parse" rather than
> >   "Text.ParserCombinators", ...
> ... 
>   * Text.Parse could be ambiguous - does it contain combinator
>     libraries, or support libraries for Happy?  Or maybe: Text.Parser
>     - does it indeed parse text according to some syntax/grammar,
>     or does it just contain functions that help you to parse text?
>     Text.ParserCombinators is at least clear.

Surely all these belong in the same subtree "Text.Parse" anyway.

--Dylan Thurston


From dpt@math.harvard.edu Tue Feb 27 17:14:58 2001 Date: Tue, 27 Feb 2001 12:14:58 -0500 From: Dylan Thurston dpt@math.harvard.edu Subject: Module versions
On Tue, Feb 27, 2001 at 03:35:31PM +0000, Malcolm Wallace wrote:
> > > The implication of the Std. namespace is that all such "standard"
> > > libraries will be distributed with all Haskell systems.  In other
> > > words, you can rely on a standard library always being there, and
> > > always having the same interface on all systems.
> > 
> > What's about version changes? How can anybody garantee that a library is
> > stable?  Some functions or instances may become obsolete or even disappear.
> > Other may be needed in later versions of the library.
> 
> We can't provide absolute guarantees of course.  But this is no
> different from the situation with standard libraries in other languages
> - witness the difficulties with libc versions etc.  I think the best
> we can do realistically is to aim for maximum stability.

But note that there is a well-defined "soname" mechanism in the Unix
world to deal with this issue.  This usually works on the object level
rather than the source level; it is usually hard to compile against an
old version of the library (without renaming the library to include a
version number).

Probably we don't need to worry about this now.

Best,
	Dylan Thurston


From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 17:30:59 2001 Date: Tue, 27 Feb 2001 17:30:59 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: Proposal: module namespaces.
Ashley writes:
> In fact, whatever you decide it's likely to happen anyway, since people 
> will decide that for instance "Com.Microsoft.Research.MyModule" is 
> unlikely to clash with anyone outside the appropriate domains and 
> subdivisions.

Yes, we expect companies to develop their own hierarchies if they
so wish.  I don't know whether the domain prefixes Com. Net. Org.
and country codes Us. Uk. Fr. etc are strictly necessary - as I
understand it, Java is moving to allow "vendor." as a synonym for
"com.vendor."

> I'm assuming that module name components have enforced capitalisation, 
> like all other Haskell identifiers.

A namespace is a dot-separated sequence of conids, therefore yes,
there is enforced capitalisation.

> Eeesh, let's hope ICANN doesn't register a 'std' TLD. I would prefer 
> "Standard" for this reason and also because the abbreviation seems pretty 
> pointless.

If Std. is going to be the common case, people will complain about
having to type the extra five characters.  Normally I would say spell
it out in full is the best rule.  Here, I'm prepared to compromise
a little.

> Do you have any kind of guarantees of copyright openness in mind? In 
> Java, everything under java.* is supposed to be owned by Sun.

All standard libraries will be copyright to their authors, but must
be released under an open source licence.  (For instance Hugs at the
very least will require the source.)  Ideally, I think they should
all have the same licence.  We need to decide which.  LGPL?  BSD?
Any opinions?

> Will it be standard practice for versions of Standard be included with 
> Haskell compilers?

This is the intention.

> Could the Prelude make use of Standard?
> Could Standard become an alternative to the Prelude?

In principle yes.  One notable omission from my hierarchy layout
proposal is the current Haskell'98 standard libraries.  Should they
remain at the toplevel?  Or should they become

    Standard.Prelude
    Standard.IO
    Standard.List
    Standard.Monad

etc.?

Regards,
    Malcolm


From chak@cse.unsw.edu.au Tue Feb 27 23:23:17 2001 Date: Wed, 28 Feb 2001 10:23:17 +1100 From: Manuel M. T. Chakravarty chak@cse.unsw.edu.au Subject: Hierarchy suggestions
Malcolm Wallace <Malcolm.Wallace@cs.york.ac.uk> wrote,

> > 1) Std.
> > I have a feeling that the "Std." prefix is going to be annoying,
> > especially when libraries move from the base hierarchy to the Std
> > hierarchy.
> 
> I actually had the same feeling in some ways.  The notion of a
> "privileged" Std. hierarchy was not originally part of my proposal,
> but it seemed to be quite important to some of the implementers at
> the Cambridge meeting where I first presented the namespaces idea.

I also don't have a good feeling about Std.  

> I think many people would value a clear signal about whether a library
> is truly portable or not.  Making that fact a part of the module name
> is about as clear and unmistakable as you can get.

I can understand the concerns that have surfaced at the
meeting, but I am not sure that a prefix is the right way to
assert the standardness of a library.

> > A portable application will only use libraries from the Std hierarchy,
> > so we should make this the default.  Non-standard libraries should get
> > the prefix, if any.
> 
> A "NonStd." prefix perhaps?  The trouble is that it would be very
> hard to police.  Anybody can write a library with any name, and it
> will immediately look standard unless they take the trouble to follow
> this convention.  In some ways that completely negates the meaning
> of standard.  "Assume everything is a standard, unless it explicitly
> says it isn't!"

And it wouldn't solve the problem with having to change the
name of the library at a point, where by definition, it is
heavily used (because only then we take it as a standard
library).

> > An alternative is to simply sanction each library individually, as the
> > interface is fixed and a portable, well-tested implementation exists.
> > Non-sanctioned libraries aren't necessarily provided by all of the main
> > implementations, and their interfaces may change (or even differ across
> > implementations).
> 
> This was my original idea.  But I was swayed towards proposing
> a distinguished Std. namespace, mainly because of the
> clarity/documentation argument.  How do I know whether a library is
> portable or not?  "Well it seems to work in GHC, so it must be okay..."
> It's amazing how many people think some language feature is standard
> Haskell'98 just because ghc implements it!

There must be an official list of standard libraries.  Just
as we know have the Library Report that provides the
official list of standard libraries.

Cheers,
Manuel


From chak@cse.unsw.edu.au Tue Feb 27 23:56:48 2001 Date: Wed, 28 Feb 2001 10:56:48 +1100 From: Manuel M. T. Chakravarty chak@cse.unsw.edu.au Subject: Proposal: module namespaces.
Malcolm Wallace <Malcolm.Wallace@cs.york.ac.uk> wrote,

> Ashley writes:
> > Do you have any kind of guarantees of copyright openness in mind? In 
> > Java, everything under java.* is supposed to be owned by Sun.
> 
> All standard libraries will be copyright to their authors, but must
> be released under an open source licence.  (For instance Hugs at the
> very least will require the source.)  Ideally, I think they should
> all have the same licence.  We need to decide which.  LGPL?  BSD?
> Any opinions?

This depends a bit on what actually we mean by standard.  In
fact, I don't think that there can be only one standard.
There reason is the varying complexity of libraries and the
fact that some rely on other non-haskell libraries.

For example, the current modules in the Library Report are
really standard libraries in the sense that their interface
is set in stone and there is as far as technically possible
freely available code with absolutely no strings attached.

However, this is not going to work for large libraries like
HOpenGL or Gtk+HS.  Their interface will never be stable
simply because they have to track the changes in the
corresponding C library (and because they are so big that we
will always find mistakes in their interface).  Moreover, it
doesn't make much sense to require, e.g., that Gtk+HS comes
with a license that is less restrictive than LGPL, because
GTK+ is LGPL and we can't change this.

BTW, this is another reason that I think, Std. doesn't make
sense.  It's too inflexible.

> > Will it be standard practice for versions of Standard be included with 
> > Haskell compilers?
> 
> This is the intention.

Which immediately leads us to protability issues with
libraries that are not fully implemented in Haskell, but
rely on some external code.

Cheers,
Manuel


From chak@cse.unsw.edu.au Wed Feb 28 00:01:29 2001 Date: Wed, 28 Feb 2001 11:01:29 +1100 From: Manuel M. T. Chakravarty chak@cse.unsw.edu.au Subject: Module versions
Dylan Thurston <dpt@math.harvard.edu> wrote,

> On Tue, Feb 27, 2001 at 03:35:31PM +0000, Malcolm Wallace wrote:
> > > > The implication of the Std. namespace is that all such "standard"
> > > > libraries will be distributed with all Haskell systems.  In other
> > > > words, you can rely on a standard library always being there, and
> > > > always having the same interface on all systems.
> > > 
> > > What's about version changes? How can anybody garantee that a library is
> > > stable?  Some functions or instances may become obsolete or even disappear.
> > > Other may be needed in later versions of the library.
> > 
> > We can't provide absolute guarantees of course.  But this is no
> > different from the situation with standard libraries in other languages
> > - witness the difficulties with libc versions etc.  I think the best
> > we can do realistically is to aim for maximum stability.
> 
> But note that there is a well-defined "soname" mechanism in the Unix
> world to deal with this issue.  This usually works on the object level
> rather than the source level; it is usually hard to compile against an
> old version of the library (without renaming the library to include a
> version number).

Like with soname, we could have optional version numbers at
the end of each name, which defaults to the latest version
if no version is given. 

Manuel


From Christian.Brolin@carmen.se Wed Feb 28 08:49:25 2001 Date: Wed, 28 Feb 2001 09:49:25 +0100 From: Christian Brolin Christian.Brolin@carmen.se Subject: Proposal: module namespaces.
Malcolm Wallace wrote:
> 
> Christian writes:
> > What about the module declaration? Should it be:
> >   module Text.Xml.Parser where ...
> > or just
> >   module Parser where ...  -- located in Text/Xml/Parser.hs?
> 
> The former.  The reason is that a compiler needs to generate a unique
> linker symbol for each defined function.  If the full module name is
> not encoded in the source file, you will need to add a commandline
> option to the compiler, which is the wrong way to go in my opinion.

What?? The compiler knows the full name of the module without the module
clause. If it didn't do that, it can't find the modules to compile! Does
the compiler opens every file on the Internet to check whether it is the
file to compile? How does the compiler find the file to compile in the
first place? What should the command line option you mentioned do?

> Why is  e.g. Parser.f  not sufficient as a unique symbol for
> Text.Xml.Parser.f?  Well, what if you also have Text.Html.Parser.f?
> You really need the full thing.

Of course, see above.

> > I would also like to import modules using relative addresses, e.g. the
> > file:
> >   My/Small/Test/Xml/Parser.hs
> > contains:
> >   import .Lexer  -- Relative path to the module: My.Small.Test.Xml.Lexer
> >   import ..Data  -- Relative path to the module: My.Small.Test.Xml.Parser.Data
> >   import Text.ParserCombinators.HuttonMeijer  -- Absolute address
> 
> I'm sorry, I don't entirely follow what the differing numbers of
> initial dots mean.

They are used to specify relative addresses to other modules. Relative
addresses is a very important concept, but You missed it in your
proposal. 

The dots was just my suggestion of a syntax for relative addresses. 
One dot: Relative to the parent of this module.
Two dots: Relative to this module.

E.g.
module A.B.C.D1 where
import A.B.C.D1.E1
import A.B.C.D1.E1.F
import A.B.C.D1.E2
import A.B.C.D2
import X.Y.Z

would be the same as (delete 'A.B.C'):
module A.B.C.D1 where
import .D1.E1
import .D1.E1.F
import .D1.E2
import .D2
import X.Y.Z

would be the same as (delete 'D1'):
module A.B.C.D1 where
import ..E1
import ..E1.F
import ..E2
import .D2
import X.Y.Z

Move the package of modules (A.B.C.*) to (Std.AAA.BBB.CCC.*) and rename
D1 to DDD:
module Std.AAA.BBB.CCC.DDD where
import ..E1
import ..E1.F
import ..E2
import .D2
import X.Y.Z

The only thing that needs to be changed is the module clause. Which of
course would be unnecessary if the module clause was dropped.

> > When the world realize that this is the XML parser, they won't accept
> > the name and I refuse to change my implementation. The only thing that
> > is needed to rename (an unused) module hierarchy is to move it.
> 
> If you refuse to change your implementation, someone else will change
> it for you!  You can't have closed standards.

It is not necessary to modify the modules if the module system supports
relative addresses!!! The steering wheel of my car is positioned
relative to my car, so it is NOT necessary to change that position when
I move the car.

-- 
Christian Brolin


From joe@isun.informatik.uni-leipzig.de Wed Feb 28 10:17:22 2001 Date: Wed, 28 Feb 2001 11:17:22 +0100 (MET) From: Johannes Waldmann joe@isun.informatik.uni-leipzig.de Subject: module namespaces
I think the namespace proposal wants to be strictly upward compatible,
therefore it's perhaps not the right time to discuss this ...
but still I think the question "why should the source text of a module
contain its name?" wants an answer.


Even if we stick to module headers, I don't really like the idea of
`module Fully.Qualified.Name where ..'

The proposal mentions the analogy to Java.
My knowledge of that is minimal, but in Java,
they have `package Foo.Bar.Frobs' (full name required)
and `class Frobble' (only last name there).
So, a Haskell module corresponds to what?


I understand the argument "the compiler needs to generate unique names
in the object files" but this is a matter of implementation,
about which the programmer (at least theoretically) should not care.

I think the underlying design decision here is:
how far should the user of a set of modules expect 
that he can move their source/interface/object files around,
and still  compile them/link against them  correctly.
The present proposal seems to imply: not at all.
This is a conservative answer. It is easy to implement, 
and guarantees some consistency. Is it too restrictive? 

But assume this policy is adopted. Then I am not allowed 
to move (precompiled) modules around physically.
That's why I want some means of renaming them (during importing),
and as I wrote earlier, not only for single modules (`import Foo as Bar')
but also for complete hierarchies (`import Leipzig.Standard as Standard')

A potential problem is that the root of some hierarchy 
perhaps is just a directory (that contains subdirs and modules) 
but not itself a module. One would need to write a dummy module
that just (qualified-)imports and re-exports all submodules.
But this had to be extended whenever a submodule is added.
This doesn't feel right. (On the other hand, the libFoo.a file
had to be rebuilt anyway on such an occasion.)


This leads to another question - during the linking stage: 
when should the compilation manager look for a single object file, 
and when should it expect an archive?


Anyway I think even the most restricitve form of hierarchical module names
would be very helpful. I certainly would start using it.
-- 
-- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ --
-- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 --


From simonmar@microsoft.com Wed Feb 28 10:32:16 2001 Date: Wed, 28 Feb 2001 02:32:16 -0800 From: Simon Marlow simonmar@microsoft.com Subject: Proposal: module namespaces.
[ leaving out haskell@haskell.org from the recipient list ]

> Malcolm Wallace wrote:
> > 
> > Christian writes:
> > > What about the module declaration? Should it be:
> > >   module Text.Xml.Parser where ...
> > > or just
> > >   module Parser where ...  -- located in Text/Xml/Parser.hs?
> > 
> > The former.  The reason is that a compiler needs to 
> generate a unique
> > linker symbol for each defined function.  If the full module name is
> > not encoded in the source file, you will need to add a commandline
> > option to the compiler, which is the wrong way to go in my opinion.
> 
> What?? The compiler knows the full name of the module without 
> the module
> clause. If it didn't do that, it can't find the modules to 
> compile! Does
> the compiler opens every file on the Internet to check 
> whether it is the
> file to compile? How does the compiler find the file to compile in the
> first place? What should the command line option you mentioned do?

The compiler finds the file because you tell it what the filename is.
That's the way it works now, and if I understand correctly Malcolm isn't
suggesting we change that (and I agree).

There are really two issues here:

  * how do you find a module to compile in the first place (not an
    issue for interpreters, only for batch compilers).  Just run
    the compiler giving it the filename.

  * when you import a module, how does the compiler find the interface
    (or source, in the case of an interpreter) for the target.
  
    My feeling is that this happens with a small extension to the 
    current scheme: at the moment, the compilers all have a list of
    search paths in which to find interfaces/sources.  The change
    is that to find a module A.B.C you search in D/A/B/ (for each D
    in the search path) rather than just D.

GHC's package mechanism will actually work pretty much unchanged with
this scheme, I believe.

Cheers,
	Simon


From mk167280@students.mimuw.edu.pl Wed Feb 28 10:37:31 2001 Date: Wed, 28 Feb 2001 11:37:31 +0100 (CET) From: Marcin 'Qrczak' Kowalczyk mk167280@students.mimuw.edu.pl Subject: Proposal: module namespaces.
On Wed, 28 Feb 2001, Christian Brolin wrote:

> What?? The compiler knows the full name of the module without the module
> clause.

It does not. File A/B/C/D.hs can be module A.B.C.D, or module B.C.D which
happened to be placed in a directory A, or C.D etc. It's ambiguous.

I'm not saying that I want to have to write full paths, but I see no other
choice.

> The dots was just my suggestion of a syntax for relative addresses. 
> One dot: Relative to the parent of this module.
> Two dots: Relative to this module.

It's confusing. If at all, it should be the opposite, analogous
to . and .. directories. But it doesn't look clear either.

-- 
Marcin 'Qrczak' Kowalczyk




From mk167280@students.mimuw.edu.pl Wed Feb 28 10:41:12 2001 Date: Wed, 28 Feb 2001 11:41:12 +0100 (CET) From: Marcin 'Qrczak' Kowalczyk mk167280@students.mimuw.edu.pl Subject: Proposal: module namespaces.
On Wed, 28 Feb 2001, Simon Marlow wrote:

> GHC's package mechanism will actually work pretty much unchanged with
> this scheme, I believe.

I hope that module name clashes across packages will not be fatal. That's
why it should probably be somewhat unified with the package system, not
built on top of it.

I would prefer to be able to just write a full module path in the import
clause, including the package name, instead of being forced to put
appropriate -package options in the makefile.

-- 
Marcin 'Qrczak' Kowalczyk



From simonmar@microsoft.com Wed Feb 28 10:42:38 2001 Date: Wed, 28 Feb 2001 02:42:38 -0800 From: Simon Marlow simonmar@microsoft.com Subject: module namespaces
Johannes Waldmann writes:
> This leads to another question - during the linking stage: 
> when should the compilation manager look for a single object file, 
> and when should it expect an archive?
 
I'll explain briefly how GHC would handle this.

GHC has a concept of a "package", which is basically a compiled unit
consisting of libraries and interfaces (not necessarily Haskell).  For
each package, the compiler has a specification telling it what the
interface search path for this package is, what the libraries are called
(and where they live), and what other packages this one depends on.

In the hierarchical module scheme, the only thing that changes is that
the search paths are now all "roots" of the hierarchical namespace (see
my previous message).

Cheers,
	Simon


From Christian.Brolin@carmen.se Wed Feb 28 10:44:58 2001 Date: Wed, 28 Feb 2001 11:44:58 +0100 From: Christian Brolin Christian.Brolin@carmen.se Subject: Proposal: module namespaces.
Marcin 'Qrczak' Kowalczyk wrote:
> 
> On Wed, 28 Feb 2001, Christian Brolin wrote:
> 
> > What?? The compiler knows the full name of the module without the module
> > clause.
> 
> It does not. File A/B/C/D.hs can be module A.B.C.D, or module B.C.D which
> happened to be placed in a directory A, or C.D etc. It's ambiguous.

Only if you give the compiler include pathes to both ~ and ~/A, where ~
is the directory containing your A.

> I'm not saying that I want to have to write full paths, but I see no other
> choice.
> 
> > The dots was just my suggestion of a syntax for relative addresses.
> > One dot: Relative to the parent of this module.
> > Two dots: Relative to this module.
> 
> It's confusing. If at all, it should be the opposite, analogous
> to . and .. directories. But it doesn't look clear either.

I just want to left out the redundant information, and . and .. are what
remain.
import .D2 -- import [A.B.C].D2
import ..E -- import [A.B.C].[D].E

-- 
Christian Brolin


From simonmar@microsoft.com Wed Feb 28 10:45:57 2001 Date: Wed, 28 Feb 2001 02:45:57 -0800 From: Simon Marlow simonmar@microsoft.com Subject: Proposal: module namespaces.
> On Wed, 28 Feb 2001, Simon Marlow wrote:
> 
> > GHC's package mechanism will actually work pretty much 
> unchanged with
> > this scheme, I believe.
> 
> I hope that module name clashes across packages will not be 
> fatal.

eek!  I thought the reason for having a richer module namespace was so
that we didn't have to allow module shadowing.

> That's
> why it should probably be somewhat unified with the package 
> system, not
> built on top of it.
> 
> I would prefer to be able to just write a full module path in 
> the import
> clause, including the package name, instead of being forced to put
> appropriate -package options in the makefile.

This may be possible too.

Cheers,
	Simon


From simonmar@microsoft.com Wed Feb 28 11:40:06 2001 Date: Wed, 28 Feb 2001 11:40:06 -0000 From: Simon Marlow simonmar@microsoft.com Subject: Alternative hierarchy proposal.
Here's my attempt at a library hierarchy.  No ASCII art - I've just
used indentation to indicate nesting.  I've merged my initial sketch
with Malcolm's proposal, so some of the subtrees are identical, but
I've changed names here and there (eg. Interface --> Console,
Encoding --> Codec or Digest).

The leaves are all real modules, some of which already exist in some
form in hslibs.  The non-leaf nodes may also be imported as Haskell
modules: more about this later.

Note: I haven't addressed the issue of what parts of the tree should
be "standard" or not - I've just populated the tree.  I've placed most
of the tree under "Haskell.".  This is roughly equivalent to Malcolm's
"Std.", except that my requirements for entry into Haskell are much
slacker :-)

I'm assuming there is a separate mechanism for deciding which
libraries are standard, and a mechansim by which a library
specification can be evolved into a standard.

I've included the Haskell 98 standard libraries, placed in their
correct places in the tree.  No doubt the interfaces to these
libraries, and even their existence in the new scheme, is now up for
debate.

The prelude is Haskell.Prelude, and is probably just a re-export
of various other parts of the tree.  In practice the implementation
will be system-specific.

I've noticed that the tree gets fairly deep in places
("Haskell.Lang.Foreign.Marshal.Array" ??) so a modification to the
language extension to allow shortening of names might be in order,
something like Java's "import java.lang.*".

System specific libraries live in GHC.*, NHC.*, Hugs.* etc.

One problem with this scheme which I haven't quite resolved, is what
happens when you import a non-leaf node.  I've identified four
possible meanings, each of which is useful in certain cases:

    (a) bring into scope everything below that node
        (might be nice for eg. Foreign, Foreign.Ptr etc.)
    (b) bring into scope some things below the node
        (eg. Foreign exports everything except C.*)
    (b) get a default module of some description
        (eg. Pretty vs. Pretty.HughesPJ)
    (c) import a unique module
        (eg. Array vs. Array.IArray)

Note that no special compiler support is required for importing a
non-leaf node, and all of the above schemes can co-exist.

Ok, here we go.  I've marked optional libraries with (opt), the rest
are assumed to have portable implementations, or be implementable in a
portable way, for any Haskell compiler with FFI support.

Cheers,
	Simon

------------------------------------------------------------------------
--
Haskell

   Prelude			-- Haskell98 Prelude
				-- mostly just re-exports other parts of
the tree.

   Lang			-- "language support"
       Foreign
	   Ptr		-- should be in Data???
	   StablePtr	-- should be in System.GC???
	   ForeignPtr	-- should be in System.GC???
	   Storable
	   Marshal
		Alloc
		Array
		Errors
		Utils
	   C
	      Types
	      Errors
	      Strings =20

       Array		-- Haskell 98 Array library
	   IArray		-- (opt) GHC's overloaded arr libs
	   MArray		-- (opt)
	   IOArray		-- mutable arrays in the IO/ST monads
	   STArray

       Monad		-- Haskell 98 Monad library
         ST
	   LazyST

	   Either		-- monad libraries
	   State
	   etc.

       Exception		-- (opt)
       Generics		-- (opt)
       Memo			-- (opt)
       Unique
       ShowFunctions	-- sounds more impressive than it is
       Dynamic	=09

   System
       IO			-- H98 + IOExts - IOArray - IORef
	   Directory
	   Select

       GC
         Weak		-- (opt)
	   StableName	-- (opt)

      Console
         GetOpt
         Readline

       Time	        	-- H98 + extensions
       Locale
       CPUTime

       -- split H98 "System" (too generic) into:
       Exit
       Environment (Args, Prog, Env ...)

   Numeric
	DSP
	    FFT
	    FIR
	    Noise
	    Oscillator
	Gaussian

   Source			-- hslibs/hssource
	AbsSyn
	Lexer
	Parser
	Pretty

   Concurrent		-- as hslibs/concurrent
        CVar		-- (some of these could also go in "Data").
	Chan
	MVar
	Merge
	QSem
	QSemN
	SampleVar
	Semaphore

   Parallel			-- as hslibs/concurrent/Parallel
	Strategies

   Net			-- won't need to be optional (will use FFI only)
	Socket		-- redesign (merge w/ SocketPrim)
	BSD			-- remove??
	URI
	CGI			-- one in hslibs is ok?

   Text
	Regex			-- previously RegexString
	   PackedString 	-- previously Regex (remove?)
	Pretty		-- default (HughesPJ?)
	   HughesPJ
	   Wadler
	   ...
	HTML			-- HTML combinator lib
	XML
	   Combinators
	   Parse
	   Pretty
	   Types
	Parse			-- no default
	   Parsec
	   Hutton_Meijer=20
	   ...

   Posix			-- redesigned, use FFI only

   Database
      SQL
      ODBC
  =20
   Debug
      Observe
      Quickcheck
      Trace

   Graphics
      UI
      Drawing
      Format		-- perhaps should be under Data.Encoding

   Data
      Bits
      Char			-- H98
      Complex		-- H98
      Either		-- H98
      Int
      Maybe			-- H98
      List			-- H98
      PackedString
      Ratio			-- H98
      Word

      IORef
      STRef

      Binary		-- Haskell binary I/O

      Digest
	  MD5
	  ...		-- others (CRC ?)

      Codec
	  Bzip2
	  Gzip
          MPEG		-- or perhaps Audio/Graphics.Format.MPEG?

      Structures
	  Trees
		AVL
		RedBlack
		BTree
	  Queue
		Bankers
		FIFO
	  Collection
	  Graphs
	  FiniteMap
	  Set
	  Edison		-- (opt, uses multi-param type classes)

GHC
      Primitives
      UnboxedTypes
      ...

-------------------------------------


From joe@isun.informatik.uni-leipzig.de Wed Feb 28 11:59:23 2001 Date: Wed, 28 Feb 2001 12:59:23 +0100 (MET) From: Johannes Waldmann joe@isun.informatik.uni-leipzig.de Subject: module namespaces
> GHC has a concept of a "package", which is basically a compiled unit
> consisting of libraries and interfaces (not necessarily Haskell).  

OK, so this would correspond (roughly) to Java packages,
while Haskell modules correspond to Java classes?

Note that in Java, you can import a class (`import Foo.Bar') 
or a package (`import Foo.*'), and that's a syntactic difference
built into the language.

Do we need the same thing for Haskell?  
Then the compiler/linker would know:
import a package: link with libPack.a; 
import a module: link with Module.o


> For each package, the compiler has a specification telling it 
                    ^^^^^^^^^^^^^^^^
So you'd have to change the compiler (driver script) 
if you want to add a package? Yes I know how this works with ghc now,
but I thought the new namespace proposal could somehow give
a more uniform solution.
-- 
-- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ --
-- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 --


From joe@isun.informatik.uni-leipzig.de Wed Feb 28 12:17:10 2001 Date: Wed, 28 Feb 2001 13:17:10 +0100 (MET) From: Johannes Waldmann joe@isun.informatik.uni-leipzig.de Subject: Alternative hierarchy proposal.
Please mind the "style warning"
http://haskell.org/pipermail/haskell/2001-February/000473.html

> 	   MArray		-- (opt)
> 	   IOArray		-- mutable arrays in the IO/ST monads

MArray looks cryptic. Why not Array.Mutable, and similar.
There are a few more places where this applies.

Of course this is rather irrelevant to the layout discussion now.
But perhaps not, since it's the question of introducing
small sub-modules, or using name prefixes.
-- 
-- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ --
-- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 --


From simonmar@microsoft.com Wed Feb 28 12:12:50 2001 Date: Wed, 28 Feb 2001 12:12:50 -0000 From: Simon Marlow simonmar@microsoft.com Subject: module namespaces
> > For each package, the compiler has a specification telling it=20
>                     ^^^^^^^^^^^^^^^^
> So you'd have to change the compiler (driver script)=20
> if you want to add a package? Yes I know how this works with ghc now,
> but I thought the new namespace proposal could somehow give
> a more uniform solution.

At the moment, or rather in the forthcoming GHC 5.00, the package
specifications are in a configuration file which GHC reads.  GHC has
command line options for installing new packages and deleting existing
ones (actually just installing/deleting the package spec, not the
package itself).

Cheers,
	Simon


From simonmar@microsoft.com Wed Feb 28 14:33:14 2001 Date: Wed, 28 Feb 2001 06:33:14 -0800 From: Simon Marlow simonmar@microsoft.com Subject: Alternative hierarchy proposal.
> Please mind the "style warning"
> http://haskell.org/pipermail/haskell/2001-February/000473.html
> 
> > 	   MArray		-- (opt)
> > 	   IOArray		-- mutable arrays in the IO/ST monads
> 
> MArray looks cryptic. Why not Array.Mutable, and similar.
> There are a few more places where this applies.
> 
> Of course this is rather irrelevant to the layout discussion now.
> But perhaps not, since it's the question of introducing
> small sub-modules, or using name prefixes.

Good point.  However, this scheme is following another style guideline,
which is that the module name follows the type name, when the module
defines a type.  Perhaps the MArray type should also be renamed to
Mutable (i.e. Haskell.Lang.Array.Mutable qualified), but this doesn't
look as nice.

Cheers,
	Simon



From joe@isun.informatik.uni-leipzig.de Wed Feb 28 18:16:47 2001 Date: Wed, 28 Feb 2001 19:16:47 +0100 (MET) From: Johannes Waldmann joe@isun.informatik.uni-leipzig.de Subject: Alternative hierarchy proposal.
> Good point.  However, this scheme is following another style guideline,
> which is that the module name follows the type name, when the module
> defines a type. 

Yes this is a good principle, and it should be kept.

> Perhaps the MArray type should also be renamed 

That was my intention.

> to Mutable (i.e. Haskell.Lang.Array.Mutable qualified), but this doesn't
> look as nice.

So what about ...Mutable.Array, then? The type name would be `Array'. 

What we're in fact trying to do here, roughly,
is to give different implementations of one interface.
Well, it's not exactly the same, but still these are Arrays.

The Edison user guide gives a good discussion of similar design decisions.

Regards,
-- 
-- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ --
-- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 --


From libraries@haskell.org Mon Feb 26 17:59:30 2001 From: libraries@haskell.org (Malcolm Wallace) Date: Mon, 26 Feb 2001 17:59:30 +0000 Subject: Proposal: module namespaces. Message-ID: <2VsAAIKZmjoiBAEA@cs.york.ac.uk> This is an annoucement of a new mailing list, and a proposal for three things: * An extended mechanism for module namespaces in Haskell. * A "standard" namespace for new libraries, common across all systems. * A social process for adding new libraries to the "standard" set. A formatted version of this proposal appears on the web at http://www.cs.york.ac.uk/fp/libraries/ The new mailing list is for the discussion of these proposals. Please subscribe if you are interested. Follow-ups set accordingly. Mailing list details -------------------- libraries@haskell.org The purpose for this new list is to: (a) discuss an extension to Haskell to provide a richer module namespace, (b) discuss how to partition this namespace and populate it with libraries, (c) discuss how to provide a consistent set of libraries for all compilers, and the setting up of a common library repository. To subscribe: http://haskell.org/mailman/listinfo/libraries/ Introduction ------------ Everyone agrees that Haskell needs good, useful, libraries: lots of them, well-specified, well-implemented, well-documented. A problem is that the current "Standard Libraries" defined by the Haskell'98 Report number only about a dozen. But there are actually many more libraries out there: some are in GHC's hslibs collection, others are linked from haskell.org, even more are used only by their original author and have no public distribution. What is more, there is no Haskell Committee. There is no-one to decide which candidate libraries are worthy to be added to the "Standard" set. This stifles the possible distribution of great libraries, because no-one knows how to get /my/ library "accepted". Furthermore, the existing libraries that people distribute from their own websites often run into problems when used alongside other people's libraries. A library usually consists of several modules, but often the constituent modules have simple names that can easily clash with modules from another library package. This leads people to ad hoc solutions such as prefixing all their modules with a cryptic identifier e.g. HsParse XmlParse HOGLParse THIHParse Just counting the libraries currently available from GHC's hslibs, and haskell.org's links, there are currently over 200 separate modules in semi-"standard" use. As more libraries are written, the possibility of clashes can only increase. Related to this problem, although not identical, is the difficulty of finding a library that provides exactly the functionality you need to help you write a specific application program. How do you go about searching through 200+ modules for interesting-looking datatypes and signatures, starting only from the module names? My View ------- My view is that many of these problems are rooted in Haskell's restriction to a flat module namespace. If we can address that issue adequately, then I believe that many of the difficulties surrounding the provision of good libraries for Haskell will simply fall away. Proposal 1 ---------- Introduce nested namespaces for modules. The key concept here is to map the module namespace into a hierarchical directory-like structure. I propose using the dot as a separator, analogous to Java's usage for namespaces. So for instance, the four example module names above using cryptic prefixes could perhaps be more clearly named Haskell.Language.Parse Text.Xml.Parse Graphics.Drawing.HOpenGL.ConfigFile.Parse TypeSystem.Parse Naming proceeds from the most general category on the left, through more specific subdivisions towards the right. For most compilers and interpreters, this extended module namespace maps directly to a directory/file structure in which the modules are stored. Storing unrelated modules in separate directories (and related modules in the same directory) is a useful and common practice when engineering large systems. (But note that, just as Haskell'98 does not *insist* that modules live in files of the same name, this proposal does not insist on it either. However, we expect most tools to use the close correspondance to their advantage.) There are several issues arising from the particular proposal here. * This is a surface change to the module naming convention. It does not introduce nested /definition/ of modules. * The syntax I propose (a dot separator) is familiar from other languages such as Java, but could in principle be something else, for instance a prime ' or underscore _ or centred dot · or something different again. * Of the choices of separator, dot requires a change to the Haskell'98 lexical syntax, allowing modid -> qconid where currently the syntax is modid -> conid * The use of qualified imports becomes more verbose: for instance import qualified XmlParse ... XmlParse.element f ... becomes import qualified Text.Xml.Parse ... Text.Xml.Parse.element f ... However, I propose that every import have an implicit "as" clause to use as an abbreviation, so in import qualified Text.Xml.Parse [ as Parse ] the clause "as Parse" would be implicit, unless overridden by the programmer with her own "as" clause. The implicit "as" clause always uses the final subdivision of the module name. So for instance, either the fully-qualified or abbreviated-qualified names Text.Xml.Parse.element Parse.element would be accepted and have the same referent, but a partial qualification like Xml.Parse.element would not be accepted. * Another consequence of using the dot as the module namespace separator is that it steals one extremely rare construction from Haskell'98: A.B.C.D in Haskell'98 means the composition of constructor D from module C, with constructor B from module A: (.) A.B C.D No-one so far thinks this is any great loss, and if you really want to say the latter, you still can by simply inserting spaces: A.B . C.D Further down this document, I give more motivation and a rationale for this proposal of nested namespaces. But first, two other proposals which rest on the first one. Proposal 2 ---------- Adopt a standardised namespace layout to help those looking for or writing libraries, and a "Std" namespace prefix for genuinely standard libraries. (These are two different things.) The hslibs collection of modules is a great starting place for finding common libraries that could become standards. I propose that we adopt a "standardised" namespace hierarchy, based on the current hslibs layout, into which Haskell programmers can plug their own libraries relatively easily (whether they intend to release them or not). The aim is to make it clear where to place a new module, and where to search for a possible existing module. For instance, in ASCII art, here is a small part of a suggested tree. + Data + Structures + Trees + AVL | | | + RedBlack | | | | | + Queue + Bankers | | + FIFO | + Encoding + Binary | + MD5 | + Graphics + UI + Gtk + Widget | | | + Pane | | | + Text | | | | | + FranTk | | | + Drawing + HOpenGL + .... | | + Vector | | | + Format + Jpeg | + PPM + Haskell + .... | A fuller proposed layout appears on the web at http://www.cs.york.ac.uk/fp/libraries/layout.html In addition to a standardised hierarchy layout, I propose a truly Standard-with-a-capital-S namespace. A separate discussion is needed on what exactly would consitute "Standard" quality, but by analogy with Java where everything beginning "java." is sanctioned by Sun, I propose that every module name beginning "Std." is in some sense sanctioned by the whole Haskell community. So for instance, an experimental, or not-quite-complete, library could be called Text.Xml but only a guaranteed-to-be-stable, complete, library could be called Std.Text.Xml The implication of the Std. namespace is that all such "standard" libraries will be distributed with all Haskell systems. In other words, you can rely on a standard library always being there, and always having the same interface on all systems. Proposal 3 ---------- Develop a process by which candidate libraries can be proposed to enter the Std namespace. Since Haskell'98 is fixed, and there is no longer a Haskell Committee, there is no official body capable of deciding new standards for libraries. However, we do have a Haskell community which will use or not use libraries, depending on their quality. So libraries will become standards by a de-facto process, rather than de-jure. Apart from the Haskell compiler implementers, we wanted a means to encourage the whole community to be involved in recognising de facto "standard" libraries. The mailing list 'libraries@haskell.org' is one contribution. We hope this will work on the same model as the FFI mailing list, which has been pretty successful at allowing a community of designers and implementers to explore their FFI needs and solidify a design that is common across at least three Haskell systems. On top of this discussion however, some final decisions will have to be made on which libraries achieve entry to the "Std." namespace. The Haskell implementers have collectively proposed a ruling troika, one representing each of the three main Haskell systems (Hugs,ghc,nhc98). These are Simon Marlow, representing ghc, and current keeper of the hslibs collection; Malcolm Wallace, representing nhc98; and Andy Gill, representing Hugs users. Some obvious criteria for entry to the "Std." namespace would be: * The interface is stable and unlikely to change significantly; * The library is written in pure Haskell'98. This criterion is likely to be the most contentious, so perhaps a better idea would be that ... * ... an implementation exists for at least the three Haskell systems Hugs, ghc, and nhc98; * The library is already in current use, so bugs in its coding and design have been ironed out; * The Haskell community recognises it as solving a common task, or encapsulating a common programming idiom. These suggested criteria need some discussion and improvement. After the initial period of deciding what belongs in the "Std." namespace, I would expect any further candidate libraries that are proposed for standardisation to spend some time in another part of the namespace hierarchy whilst they gain stability and common acceptance, before being moved to "Std.". Rationale and Motivation for Proposal 1 (nested namespaces) ----------------------------------------------------------- Scenario 1 ---------- Imagine you have just written a new library of, say, Pretty-printing combinators. You want to release it to the Haskell public. So what do you call it? module Pretty -- already taken (several times) module UU_Pretty -- also taken module PrettyLib -- already exists as well Ok, so lacking any further inspiration, you end up deciding to call it module MyPretty -- ! Surely there must be a better solution. Of course there is - namespaces. Let's classify libraries that do similar jobs together: module Text.PrettyPrinter.Hughes -- the original Hughes design module Text.PrettyPrinter.HughesPJ -- later modified by Simon PJ module Text.PrettyPrinter.UU -- the Utrecht design module Text.PrettyPrinter.Chitil -- Olaf's new design These are exactly the same Pretty libs as before, but named more sensibly. It is still clear that each is a pretty-printing library, but it is also clear that they are different. Incidentally, have you ever tried to write your own module called Pretty? You may have discovered with GHC (which has a Pretty already in the hslibs collection), that you get strange errors. This is because sometimes the compiler can be confused into reading one Pretty.hi interface file (i.e. yours), yet linking the other Pretty.o object file (i.e. from hslibs), ending in a core dump. With proper module namespaces, this confusion should never happen again. Scenario 2 ---------- You are writing a complex library that has a couple of layers of abstraction. For some users, you want to expose just a small high-level set of types and functions. Other users will need more detailed access to lower-level stuff. With namespaces, you can use the directory-like structure to make these kinds of access explicit. For instance, imagine a socket library: module Network.Socket It exports an /abstract/ type Socket for ordinary users - they only need to know its name. More advanced hackers however can play with the details of the type, because you also have: module Network.Socket.Types which exports the Socket type non-abstractly i.e. Socket(..). And of course this abstraction is easy for the library-writer to manage, because the implementation of the more abstract layer simply imports and re-exports a careful selection of the more detailed layers. Don't forget that, in terms of the actual filesystem layout, it is perfectly OK to have e.g. file Network/Socket.hs dir NetWork/Socket file Network/Socket/Types.hs Scenario 3 ---------- You are managing a software engineering project. Several people are working more-or-less independently on different sections of the program. To avoid mistakes with files, you give each one a separate directory to place their code in. But in Haskell'98 this is not enough to ensure that they invent module names that do not clash with other developers' modules. So you insist that everyone also uses a prefix-naming scheme for each appropriate sub-task. For instance, here is a sketch of the layout of the Galois Connection team's entry in the ICFP 2000 programming contest: dir CSG -- constructive solid geometry file CSG/CSG.hs file CSG/CSGConstruct.hs file CSG/CSGGeometry.hs file CSG/CSGInterval.hs dir Fran -- Fran-style animation file Fran/FranLite.hs file Fran/FranCSG.hs dir GML -- interpreter for little language file GML/GMLData.hs file GML/GMLParse.hs file GML/GMLPrimitives.hs So now the problem is that to actually build the software, you need to write a Makefile that descends into these directories. Or maybe you use 'hmake' like so: hmake examples/chess.hs -ICSG -IFran -IGML -IRayTrace -package text Note how many sub-directories you must remember to add to the command line (this applies equally for compiler options in Makefiles). Note also the inconsistency between compiling and linking /my/ modules, against using and linking a "standard" hslibs module from package text. Isn't there a simpler way? Yes. Namespaces. Prefix naming is no longer needed inside directories, because the directory name is /part/ of the module name: file CSG.hs -- re-exports everything from the CSG dir dir CSG file CSG/Construct.hs file CSG/Geometry.hs file CSG/Interval.hs dir Fran file Fran/Lite.hs file Fran/CSG.hs -- does not conflict with top-level CSG.hs dir GML file GML/Data.hs file GML/Parse.hs file GML/Primitives.hs And now, the commandline to 'hmake' (or compiler options in a Makefile) becomes simply: hmake examples/chess.hs -I. You only need to specify the root of the module tree (-I.), and all modules in all subdirectories can be found via their full namespace path as used in the source files. Note also that, whereas previously we needed to specify a package for whatever hslibs modules were used, now the compiler/hmake already knows the root of the installed hslibs tree and can use the same mechanism to find and link "standard" modules as for user modules. From this example it should be clear that the use of module namespaces is of benefit to ordinary programs that may never become public, quite aside from any benefits we expect to derive in managing publically-distributed library code. What now? --------- Ok, so that's my proposal. The implementers of some of the main Haskell systems have seen a presentation of these ideas, and seemed to like them. Namespaces are already implemented in nhc98 (v1.02) and hmake (v2.02) if you want to play with them. I expect some discussion to refine this proposal on the 'libraries@haskell.org' list, to which everyone interested is invited. Once we have nailed down the precise design, we need to get matching implementations in all systems. I have rashly volunteered to implement the lexical/parsing/module-search changes in any Haskell system that no-one else volunteers for (probably ghc, Hugs, possibly hbc). But after that we will still have many more decisions to take about individual libraries, precise naming, build systems, and so on, not to mention actually writing the libraries. Get involved. Contribute. Regards, Malcolm From joe@isun.informatik.uni-leipzig.de Tue Feb 27 09:15:21 2001 From: joe@isun.informatik.uni-leipzig.de (Johannes Waldmann) Date: Tue, 27 Feb 2001 10:15:21 +0100 (MET) Subject: yes please Message-ID: <200102270915.KAA16179@isun11.informatik.uni-leipzig.de> Dear Malcolm, I fully aggree with rationale and motivation for your module namespace proposals. While teaching Haskell I noticed that the more I really did what I was preaching to the students, namely, writing re-useable code by factoring out common patterns, I ran into module namespace problems. So I will start using proposal-1 the day it will be implemented for hugs. I can't think of any arguments that would speak against the proposal. Are there any? At some time in the future, the proposal needs a formal definition of how the source/interface file for the imported module is actually found. At the moment, it is "just like you would expect, and if you have questions, look in the Java definition"? Well that's OK for now, but a language standard should be self-contained. Best regards, -- -- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ -- -- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 -- From ketil@ii.uib.no Tue Feb 27 10:42:58 2001 From: ketil@ii.uib.no (Ketil Malde) Date: 27 Feb 2001 11:42:58 +0100 Subject: Proposal: module namespaces. In-Reply-To: Malcolm Wallace's message of "Mon, 26 Feb 2001 17:59:30 +0000" References: <2VsAAIKZmjoiBAEA@cs.york.ac.uk> Message-ID: Malcolm Wallace writes: > Proposal 1 > ---------- > Introduce nested namespaces for modules. The key concept here is to > map the module namespace into a hierarchical directory-like structure. > * The use of qualified imports becomes more verbose: for instance [...] > instance, either the fully-qualified or abbreviated-qualified names > Text.Xml.Parse.element > Parse.element > would be accepted and have the same referent, but a partial > qualification like > Xml.Parse.element > would not be accepted. Why not? Perhaps one could have a warning/error if there are multiple "Parse" modules? > * Another consequence of using the dot as the module namespace > separator is that it steals one extremely rare construction from > Haskell'98: [...] > No-one so far thinks this is any great loss, and if you really > want to say the latter, you still can by simply inserting spaces: > A.B . C.D Personally, I'm not overly enthusiastic about using (.) for function composition - but I guess e.g the degrees sign was ruled out since it's not in (7bit) ASCII - and I think it should require spaces anyway, in order to differentiate it from its other uses. > Proposal 2 > ---------- > Adopt a standardised namespace layout to help those looking for or > writing libraries, and a "Std" namespace prefix for genuinely > standard libraries. (These are two different things.) Sounds good! -kzm -- If I haven't seen further, it is by standing in the footprints of giants From simonmar@microsoft.com Tue Feb 27 10:47:21 2001 From: simonmar@microsoft.com (Simon Marlow) Date: Tue, 27 Feb 2001 10:47:21 -0000 Subject: Hierarchy suggestions Message-ID: <9584A4A864BD8548932F2F88EB30D1C61157EF@TVP-MSG-01.europe.corp.microsoft.com> Firstly, I'd like to say this proposal is great. We're in dire need of extending the module namespace, and it's important that we do it in a community-directed way. Proposals 1 & 3: no problem. Proposal 2: I think we should spend a lot of effort designing the layout of the module hierarchy, at least the standard parts, to make it as "future proof" as possible. We really don't want to be reorganising things later. 1) Std. I have a feeling that the "Std." prefix is going to be annoying, especially when libraries move from the base hierarchy to the Std hierarchy. It doesn't fit well with the idea that the hierarchy should be as static as possible. =20 A portable application will only use libraries from the Std hierarchy, so we should make this the default. Non-standard libraries should get the prefix, if any. An alternative is to simply sanction each library individually, as the interface is fixed and a portable, well-tested implementation exists. Non-sanctioned libraries aren't necessarily provided by all of the main implementations, and their interfaces may change (or even differ across implementations). 2) Haskell->Plus At some point in the future, Haskell will no doubt include the FFI, at which point the Haskell->Plus->FFI hierarchy won't make sense any more, and we'll have to break lots of existing code to move the library somewhere sensible. I suggest just calling it "Foreign", and putting it near the top of the hierarchy somewhere. Similarly for Concurrent, Exceptions, etc. I have a fairly complete hierarchy sketched out, but I'm going to revise it based on your ideas and send it out later. Cheers, Simon From joe@isun.informatik.uni-leipzig.de Tue Feb 27 10:58:04 2001 From: joe@isun.informatik.uni-leipzig.de (Johannes Waldmann) Date: Tue, 27 Feb 2001 11:58:04 +0100 (MET) Subject: Hierarchy suggestions In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C61157EF@TVP-MSG-01.europe.corp.microsoft.com> from Simon Marlow at "Feb 27, 2001 10:47:21 am" Message-ID: <200102271058.LAA16264@isun11.informatik.uni-leipzig.de> on module prefixes (= directory names). perhaps there could be renaming declarations not only for modules, but also for prefixes. say you have modules Foo.Frobs and Bar.Frobs, then you could import Foo as X import X.Frobs there would normally be an implicit "import Standard", but you could override with "import Experimental as Standard" of course this could cause more problems than it solves. -- -- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ -- -- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 -- From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 12:02:51 2001 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 27 Feb 2001 12:02:51 +0000 Subject: Proposal: module namespaces. In-Reply-To: Message-ID: Ketil Malde writes: > > instance, either the fully-qualified or abbreviated-qualified names > > Text.Xml.Parse.element > > Parse.element > > would be accepted and have the same referent, but a partial > > qualification like > > Xml.Parse.element > > would not be accepted. > > Why not? I suppose it would be possible to have an implicit import A.B.C.D.E as E import A.B.C.D.E as D.E import A.B.C.D.E as C.D.E import A.B.C.D.E as B.C.D.E To me, this seems like it introduces extra complexity with little benefit for ease of use. Wouldn't it be confusing to use C.D.E at some places in a program, and D.E at others? It isn't necessarily obvious that they refer to the same entity. After all, what if your project has a module hierarchy like: A/B/C/D/E B/C/D/E Z/B/C/D/E R/S/T/D/E ? To which of these paths might D.E refer? No, I think that restricting the implicit 'as' declaration to the simplest convenient case (just the last component) is the best compromise to improve readability, without introducing too many potential pitfalls. And of course, you can always give an explicit 'as' clause if you wish. > Perhaps one could have a warning/error if there are multiple "Parse" > modules? This is kind-of what currently happens in Haskell'98. You can rename two imports to the same qualifier: import A as M import B as M Provided that function f appears in only one of A or B, the qualified name M.f is resolved correctly. If function g is defined in both, then M.g is ambiguous and the compiler gives an error - but only if you actually mention M.g. It is okay for A and B to have overlapping definitions provided you don't try to use one of them. > Personally, I'm not overly enthusiastic about using (.) for function > composition - but I guess e.g the degrees sign was ruled out since > it's not in (7bit) ASCII - and I think it should require spaces > anyway, in order to differentiate it from its other uses. I have been thinking about defining centred dot in nhc98's Prelude as a synonym for the composition operator. Perhaps other Haskell systems might be prepared to do the same? (On my system I can type a centred dot easily with the sequence Compose-dot-dot.) Regards, Malcolm From sk@mathematik.uni-ulm.de Tue Feb 27 12:52:06 2001 From: sk@mathematik.uni-ulm.de (Stefan Karrmann) Date: Tue, 27 Feb 2001 13:52:06 +0100 Subject: Proposal: module namespaces. In-Reply-To: <2VsAAIKZmjoiBAEA@cs.york.ac.uk>; from Malcolm.Wallace@cs.york.ac.uk on Mon, Feb 26, 2001 at 05:59:30PM +0000 References: <2VsAAIKZmjoiBAEA@cs.york.ac.uk> Message-ID: <20010227135206.C20080@theseus.mathematik.uni-ulm.de> Malcolm Wallace schrieb folgendes am Mon, Feb 26, 2001 at 05:59:30PM +0000: > Proposal 2 > ---------- > but only a guaranteed-to-be-stable, complete, library could be called > > Std.Text.Xml > > The implication of the Std. namespace is that all such "standard" > libraries will be distributed with all Haskell systems. In other > words, you can rely on a standard library always being there, and > always having the same interface on all systems. What's about version changes? How can anybody garantee that a library is stable? Some functions or instances may become obsolete or even disappear. Other may be needed in later versions of the library. Regards, -- Stefan Karrmann From sk@mathematik.uni-ulm.de Tue Feb 27 12:52:06 2001 From: sk@mathematik.uni-ulm.de (Stefan Karrmann) Date: Tue, 27 Feb 2001 13:52:06 +0100 Subject: Proposal: module namespaces. In-Reply-To: <2VsAAIKZmjoiBAEA@cs.york.ac.uk>; from Malcolm.Wallace@cs.york.ac.uk on Mon, Feb 26, 2001 at 05:59:30PM +0000 References: <2VsAAIKZmjoiBAEA@cs.york.ac.uk> Message-ID: <20010227135206.C20080@theseus.mathematik.uni-ulm.de> Malcolm Wallace schrieb folgendes am Mon, Feb 26, 2001 at 05:59:30PM +0000: > Proposal 2 > ---------- > but only a guaranteed-to-be-stable, complete, library could be called > > Std.Text.Xml > > The implication of the Std. namespace is that all such "standard" > libraries will be distributed with all Haskell systems. In other > words, you can rely on a standard library always being there, and > always having the same interface on all systems. What's about version changes? How can anybody garantee that a library is stable? Some functions or instances may become obsolete or even disappear. Other may be needed in later versions of the library. Regards, -- Stefan Karrmann From franka@cs.uu.nl Tue Feb 27 13:01:40 2001 From: franka@cs.uu.nl (Frank Atanassow) Date: Tue, 27 Feb 2001 14:01:40 +0100 Subject: Proposal: module namespaces. In-Reply-To: <2VsAAIKZmjoiBAEA@cs.york.ac.uk>; from Malcolm.Wallace@cs.york.ac.uk on Mon, Feb 26, 2001 at 05:59:30PM +0000 References: <2VsAAIKZmjoiBAEA@cs.york.ac.uk> Message-ID: <20010227140140.B24331@cs.uu.nl> I have two nitpicking comments. Malcolm Wallace wrote (on 26-02-01 17:59 +0000): > * The use of qualified imports becomes more verbose: for instance > import qualified XmlParse > ... XmlParse.element f ... > becomes > import qualified Text.Xml.Parse > ... Text.Xml.Parse.element f ... > However, I propose that every import have an implicit "as" > clause to use as an abbreviation, so in > import qualified Text.Xml.Parse [ as Parse ] > the clause "as Parse" would be implicit, unless overridden by the > programmer with her own "as" clause. The implicit "as" clause > always uses the final subdivision of the module name. So for > instance, either the fully-qualified or abbreviated-qualified names > Text.Xml.Parse.element > Parse.element > would be accepted and have the same referent, but a partial > qualification like > Xml.Parse.element > would not be accepted. I don't like the implicit "as". The reason for having a tree structure for names is that leaves are likely to collide. So I might use both Text.ParserCombinators.UU and Text.PrettyPrinter.UU. In this case I might want to use the declarations: import qualified Text.ParserCombinators.UU as PC import qualified Text.PrettyPrinter.UU as PP Since a person is likely to use several packages in the same subtree quite often, and in our goal of a "library-rich world" we expect a plethora of implementations from disparate sources, I wonder whether the default "as" is useful enough in practice. As an example, in cases where sibling modules actually have the same interface and you want to write a client module which can use either implementation interchangeably, you would always use an explicit "as" anyway, since you want to write, say, "Tree.map" rather than "AVL.map" or "RedBlack.map". Besides, it is only a few more characters to make it explicit, and I think it is better to avoid implicit behavior when possible. Well, I don't care too much. I care more about: > A fuller proposed layout appears on the web at > http://www.cs.york.ac.uk/fp/libraries/layout.html I wish we could agree on capitalization of acronyms. On one hand, we have: Gtk, Jpeg, Html, Xml but on the other: AVL, ODBC, FIFO, MD5, UI, PPM, FFI, IO, UU, PP, DSP, FFT, FIR, URL, CGI Personally, I prefer the first group being normalized to uppercase rather than vice versa, since "JPEG" and "HTML" look right, but "Url" and "Odbc" look terribly wrong. (Unless you are Dutch, in which case maybe "Ui" looks good but is still misleading. :) Other miscellanea: * I think the top-level "Interface" is better named "Console", to contrast with "Graphics". * I would prefer short names to long. So: "Text.Parse" rather than "Text.ParserCombinators", "Data.Struct" rather than "Data.Structures", "Graphics.Draw" rather than "Graphics.Drawing", etc. Generally, the ancestors of a short name should give enough context to disambiguate it. * I would move "Format" out of "Graphics" and into "Data.Encoding". (But maybe "Encoding" is intended to be a collection of things of `universal' encodings, which clearly "Jpeg", for example, is not.) * Change "Data.Structures.Trees" and "...Graphs" from plural to singular. Same for "Data.Encoding.Bits". But not "Data" to "Datum"! :) * Maybe change "Data.Structures" and "Data.Encoding" to one name each, "DataStruct" and "DataEncoding" (or "Encoding" or "Codec"). The reason is that it's not clear to me why they belong in the same subtree except for the fact that in English both terms start with "Data". In other words, we should try to group things semantically rather than lexically. -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379 From Christian.Brolin@carmen.se Tue Feb 27 13:19:30 2001 From: Christian.Brolin@carmen.se (Christian Brolin) Date: Tue, 27 Feb 2001 14:19:30 +0100 Subject: Proposal: module namespaces. References: <2VsAAIKZmjoiBAEA@cs.york.ac.uk> Message-ID: <3A9BA962.CB5DAE4@carmen.se> Malcolm Wallace wrote: > > I propose that every import have an implicit "as" > clause to use as an abbreviation, so in > import qualified Text.Xml.Parse [ as Parse ] > the clause "as Parse" would be implicit, unless overridden by the > programmer with her own "as" clause. The implicit "as" clause > always uses the final subdivision of the module name. What about, e.g. import qualified Text.Xml.Parse import qualified Text.Yml.Parse ? -- Christian Brolin From Christian.Brolin@carmen.se Tue Feb 27 13:20:22 2001 From: Christian.Brolin@carmen.se (Christian Brolin) Date: Tue, 27 Feb 2001 14:20:22 +0100 Subject: Proposal: module namespaces. References: <2VsAAIKZmjoiBAEA@cs.york.ac.uk> Message-ID: <3A9BA996.AA110851@carmen.se> Malcolm Wallace wrote: > > Proposal 1 > ---------- > Introduce nested namespaces for modules. The key concept here is to > map the module namespace into a hierarchical directory-like structure. > I propose using the dot as a separator, analogous to Java's usage > for namespaces. I haven't commented on this if I thought it was a bad idea:) What about the module declaration? Should it be: module Text.Xml.Parser where ... or just module Parser where ... -- located in Text/Xml/Parser.hs? I prefer the latter one since I think it is wrong to specify the address of the module in the module itself. It would be even better if the module declaration wasn't needed at all. I don't know what it is needed for. I would also like to import modules using relative addresses, e.g. the file: My/Small/Test/Xml/Parser.hs contains: import .Lexer -- Relative path to the module: My.Small.Test.Xml.Lexer import ..Data -- Relative path to the module: My.Small.Test.Xml.Parser.Data import Text.ParserCombinators.HuttonMeijer -- Absolute address When the world realize that this is the XML parser, they won't accept the name and I refuse to change my implementation. The only thing that is needed to rename (an unused) module hierarchy is to move it. import Std.Module import .Sibling import .Sibling.Child import ..Child import ..Child.GrandChild import ...Syntax.Error -- This isn't allowed -- Christian Brolin From ashley@semantic.org Tue Feb 27 13:33:26 2001 From: ashley@semantic.org (Ashley Yakeley) Date: Tue, 27 Feb 2001 05:33:26 -0800 Subject: Proposal: module namespaces. Message-ID: <200102271333.FAA25861@mail4.halcyon.com> At 2001-02-26 09:59, Malcolm Wallace wrote: >Proposal 2 >---------- >Adopt a standardised namespace layout to help those looking for or >writing libraries, I'm a big fan of the Java reversed DNS style. Whatever, I think it's important that anyone with a domain name should be able to obtain a unique namespace without any further bureaucracy. In fact, whatever you decide it's likely to happen anyway, since people will decide that for instance "Com.Microsoft.Research.MyModule" is unlikely to clash with anyone outside the appropriate domains and subdivisions. I'm assuming that module name components have enforced capitalisation, like all other Haskell identifiers. >and a "Std" namespace prefix for genuinely >standard libraries. (These are two different things.) Eeesh, let's hope ICANN doesn't register a 'std' TLD. I would prefer "Standard" for this reason and also because the abbreviation seems pretty pointless. >In addition to a standardised hierarchy layout, I propose a truly >Standard-with-a-capital-S namespace. A separate discussion is needed >on what exactly would consitute "Standard" quality, but by analogy >with Java where everything beginning "java." is sanctioned by Sun, >I propose that every module name beginning "Std." is in some sense >sanctioned by the whole Haskell community. Do you have any kind of guarantees of copyright openness in mind? In Java, everything under java.* is supposed to be owned by Sun. Will it be standard practice for versions of Standard be included with Haskell compilers? Could the Prelude make use of Standard? Could Standard become an alternative to the Prelude? If answers to these last three are all "no", an alternative would be to put it under "Org.Haskell.Standard". -- Ashley Yakeley, Seattle WA From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 15:35:31 2001 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 27 Feb 2001 15:35:31 +0000 Subject: Proposal: module namespaces. In-Reply-To: <20010227135206.C20080@theseus.mathematik.uni-ulm.de> Message-ID: > > The implication of the Std. namespace is that all such "standard" > > libraries will be distributed with all Haskell systems. In other > > words, you can rely on a standard library always being there, and > > always having the same interface on all systems. > > What's about version changes? How can anybody garantee that a library is > stable? Some functions or instances may become obsolete or even disappear. > Other may be needed in later versions of the library. We can't provide absolute guarantees of course. But this is no different from the situation with standard libraries in other languages - witness the difficulties with libc versions etc. I think the best we can do realistically is to aim for maximum stability. In some cases, it may be sensible for a new version of a standard library to adopt a new name, simply to make things clear. We should probably decide this on a case-by-case basis if/when the problem arises. Regards, Malcolm From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:03:26 2001 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 27 Feb 2001 16:03:26 +0000 Subject: Hierarchy suggestions In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C61157EF@TVP-MSG-01.europe.corp.microsoft.com> Message-ID: > Proposal 2: I think we should spend a lot of effort designing the layout > of the module hierarchy, at least the standard parts, to make it as > "future proof" as possible. We really don't want to be reorganising > things later. I absolutely agree. Let's try to get the naming correct (and extensible) right from the beginning. > 1) Std. > I have a feeling that the "Std." prefix is going to be annoying, > especially when libraries move from the base hierarchy to the Std > hierarchy. I actually had the same feeling in some ways. The notion of a "privileged" Std. hierarchy was not originally part of my proposal, but it seemed to be quite important to some of the implementers at the Cambridge meeting where I first presented the namespaces idea. I think many people would value a clear signal about whether a library is truly portable or not. Making that fact a part of the module name is about as clear and unmistakable as you can get. > A portable application will only use libraries from the Std hierarchy, > so we should make this the default. Non-standard libraries should get > the prefix, if any. A "NonStd." prefix perhaps? The trouble is that it would be very hard to police. Anybody can write a library with any name, and it will immediately look standard unless they take the trouble to follow this convention. In some ways that completely negates the meaning of standard. "Assume everything is a standard, unless it explicitly says it isn't!" > An alternative is to simply sanction each library individually, as the > interface is fixed and a portable, well-tested implementation exists. > Non-sanctioned libraries aren't necessarily provided by all of the main > implementations, and their interfaces may change (or even differ across > implementations). This was my original idea. But I was swayed towards proposing a distinguished Std. namespace, mainly because of the clarity/documentation argument. How do I know whether a library is portable or not? "Well it seems to work in GHC, so it must be okay..." It's amazing how many people think some language feature is standard Haskell'98 just because ghc implements it! People don't seem to complain about having to write "java." at the beginning of all their Java imports. > 2) Haskell->Plus > At some point in the future, Haskell will no doubt include the FFI, at > which point the Haskell->Plus->FFI hierarchy won't make sense any more, > and we'll have to break lots of existing code to move the library > somewhere sensible. The Haskell.Plus. namespace is a cute (IMO) way to make it clear that these libraries use extensions to pure Haskell'98. Perhaps if we called the namespace Haskell98.Plus. then it would be even clearer that these things are not Haskell'98, and never will be. When a future version of Haskell comes along, perhaps it won't even be called Haskell, so we will adopt a LanguageFormerlyKnownAsHaskell. hierarchy. (Or more likely Haskell200x. I suppose) > I suggest just calling it "Foreign", and putting it near the top of the > hierarchy somewhere. Similarly for Concurrent, Exceptions, etc. Whatever, I think the name should make it clear that these libraries require compiler/language extensions, that's the main point. > I have a fairly complete hierarchy sketched out, but I'm going to revise > it based on your ideas and send it out later. Looking forward to it. I'll place it on the web next to my current layout proposal if you like, for comparison. Then we should start discussing individual branches of the hierarchy, and try to come up with a consensus for each part, recording our progress on the web also. (I suggest at that stage we build a new layout tree from scratch, separate from both layout proposals, and based on agreement here on the list). Regards, Malcolm From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:47:26 2001 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 27 Feb 2001 16:47:26 +0000 Subject: Proposal: module namespaces. In-Reply-To: <3A9BA962.CB5DAE4@carmen.se> Message-ID: Christian writes: > > I propose that every import have an implicit "as" > > clause to use as an abbreviation, > > What about, e.g. > import qualified Text.Xml.Parse > import qualified Text.Yml.Parse > ? Just like right now in Haskell'98 with overlapping module renaming. If a function name f is found in only one of the two libraries, Parse.f is unambiguous. If it occurs in both, Parse.f is ambiguous and gives an error, but only if Parse.f is mentioned in the importing module. The fully qualified name is unambiguous, and if you really want to be clear, do your own explicit renaming. Regards, Malcolm From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:42:16 2001 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 27 Feb 2001 16:42:16 +0000 Subject: Proposal: module namespaces. In-Reply-To: <20010227140140.B24331@cs.uu.nl> Message-ID: Frank writes: > I wish we could agree on capitalization of acronyms. On one hand, we have: > Gtk, Jpeg, Html, Xml > but on the other: > AVL, ODBC, FIFO, MD5, UI, PPM, FFI, IO, UU, PP, DSP, FFT, FIR, URL, CGI Hmm, yes. Actually, my preferred solution would be to use acronyms only when they are extremely well known, and otherwise to spell things out in full. So Gtk, Jpeg, Html, Xml, Fifo, UI, Ppm, IO, URL, CGI but ObjectDataBase, Foreign, Utrecht, PrettyPrint, SignalProcessing, FourierTransform, GroeltzmanFilter ... But these things are inevitably a matter of taste. Some people detest the MixedUpperAndLower style. > I think the top-level "Interface" is better named "Console", to contrast > with "Graphics". Cool. I like it. > I would prefer short names to long. So: "Text.Parse" rather than > "Text.ParserCombinators", "Data.Struct" rather than "Data.Structures", > "Graphics.Draw" rather than "Graphics.Drawing", etc. Generally, the > ancestors of a short name should give enough context to disambiguate it. In terms of software engineering, I think fully descriptive names are better than abbreviations. On the other hand, no-one likes names that are long just for the sake of completeness. * Text.Parse could be ambiguous - does it contain combinator libraries, or support libraries for Happy? Or maybe: Text.Parser - does it indeed parse text according to some syntax/grammar, or does it just contain functions that help you to parse text? Text.ParserCombinators is at least clear. * Graphics.Draw might indeed be better than Graphics.Drawing * Data.Struct - I don't like it - it sounds like C! > I would move "Format" out of "Graphics" and into "Data.Encoding". (But > maybe "Encoding" is intended to be a collection of things of `universal' > encodings, which clearly "Jpeg", for example, is not.) Indeed, we do need to guard against overlapping categories. I don't know about this particular case - Graphics.Format seems more natural to me. As you say, it contains datatype-specific codecs, not universal ones. > Change "Data.Structures.Trees" and "...Graphs" from plural to > singular. Same for "Data.Encoding.Bits". But not "Data" to "Datum"! :) Like Data.Structure.Tree etc? Yes, looks ok. Data.Encoding.Bits is a special case. There are two current bit libraries, one called Bit (in nhc98), the other called Bits (in ghc). They even have different interfaces. Sadly, inconsistencies like this have grown up over the years. But I think we can turn the situation into a more positive one by permitting the distribution of competing libraries - just like for pretty-printers, we can extend the namespace to have both: Data.Encoding.Bit.Glasgow Data.Encoding.Bit.York Mechanism, not policy. > Maybe change "Data.Structures" and "Data.Encoding" to one name each, > "DataStruct" and "DataEncoding" (or "Encoding" or "Codec"). The reason is > that it's not clear to me why they belong in the same subtree except for > the fact that in English both terms start with "Data". In other words, we > should try to group things semantically rather than lexically. I quite like the name Codec. MD5 is not a codec as such - more of a checksum really. For me, data structures and data codecs belong semantically in the same subtree - it isn't just a lexical grouping. Thanks for your suggestions! Regards, Malcolm From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 16:59:42 2001 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 27 Feb 2001 16:59:42 +0000 Subject: Proposal: module namespaces. In-Reply-To: <3A9BA996.AA110851@carmen.se> Message-ID: Christian writes: > What about the module declaration? Should it be: > module Text.Xml.Parser where ... > or just > module Parser where ... -- located in Text/Xml/Parser.hs? The former. The reason is that a compiler needs to generate a unique linker symbol for each defined function. If the full module name is not encoded in the source file, you will need to add a commandline option to the compiler, which is the wrong way to go in my opinion. Why is e.g. Parser.f not sufficient as a unique symbol for Text.Xml.Parser.f? Well, what if you also have Text.Html.Parser.f? You really need the full thing. > I would also like to import modules using relative addresses, e.g. the > file: > My/Small/Test/Xml/Parser.hs > contains: > import .Lexer -- Relative path to the module: My.Small.Test.Xml.Lexer > import ..Data -- Relative path to the module: My.Small.Test.Xml.Parser.Data > import Text.ParserCombinators.HuttonMeijer -- Absolute address I'm sorry, I don't entirely follow what the differing numbers of initial dots mean. > When the world realize that this is the XML parser, they won't accept > the name and I refuse to change my implementation. The only thing that > is needed to rename (an unused) module hierarchy is to move it. If you refuse to change your implementation, someone else will change it for you! You can't have closed standards. Regards, Malcolm From dpt@math.harvard.edu Tue Feb 27 17:09:41 2001 From: dpt@math.harvard.edu (Dylan Thurston) Date: Tue, 27 Feb 2001 12:09:41 -0500 Subject: Proposal: module namespaces. In-Reply-To: ; from Malcolm.Wallace@cs.york.ac.uk on Tue, Feb 27, 2001 at 04:42:16PM +0000 References: <20010227140140.B24331@cs.uu.nl> Message-ID: <20010227120941.A18256@math.harvard.edu> On Tue, Feb 27, 2001 at 04:42:16PM +0000, Malcolm Wallace wrote: > Frank writes: > > I would prefer short names to long. So: "Text.Parse" rather than > > "Text.ParserCombinators", ... > ... > * Text.Parse could be ambiguous - does it contain combinator > libraries, or support libraries for Happy? Or maybe: Text.Parser > - does it indeed parse text according to some syntax/grammar, > or does it just contain functions that help you to parse text? > Text.ParserCombinators is at least clear. Surely all these belong in the same subtree "Text.Parse" anyway. --Dylan Thurston From dpt@math.harvard.edu Tue Feb 27 17:14:58 2001 From: dpt@math.harvard.edu (Dylan Thurston) Date: Tue, 27 Feb 2001 12:14:58 -0500 Subject: Module versions In-Reply-To: ; from Malcolm.Wallace@cs.york.ac.uk on Tue, Feb 27, 2001 at 03:35:31PM +0000 References: <20010227135206.C20080@theseus.mathematik.uni-ulm.de> Message-ID: <20010227121458.B18256@math.harvard.edu> On Tue, Feb 27, 2001 at 03:35:31PM +0000, Malcolm Wallace wrote: > > > The implication of the Std. namespace is that all such "standard" > > > libraries will be distributed with all Haskell systems. In other > > > words, you can rely on a standard library always being there, and > > > always having the same interface on all systems. > > > > What's about version changes? How can anybody garantee that a library is > > stable? Some functions or instances may become obsolete or even disappear. > > Other may be needed in later versions of the library. > > We can't provide absolute guarantees of course. But this is no > different from the situation with standard libraries in other languages > - witness the difficulties with libc versions etc. I think the best > we can do realistically is to aim for maximum stability. But note that there is a well-defined "soname" mechanism in the Unix world to deal with this issue. This usually works on the object level rather than the source level; it is usually hard to compile against an old version of the library (without renaming the library to include a version number). Probably we don't need to worry about this now. Best, Dylan Thurston From Malcolm.Wallace@cs.york.ac.uk Tue Feb 27 17:30:59 2001 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Tue, 27 Feb 2001 17:30:59 +0000 Subject: Proposal: module namespaces. In-Reply-To: <200102271333.FAA25861@mail4.halcyon.com> Message-ID: Ashley writes: > In fact, whatever you decide it's likely to happen anyway, since people > will decide that for instance "Com.Microsoft.Research.MyModule" is > unlikely to clash with anyone outside the appropriate domains and > subdivisions. Yes, we expect companies to develop their own hierarchies if they so wish. I don't know whether the domain prefixes Com. Net. Org. and country codes Us. Uk. Fr. etc are strictly necessary - as I understand it, Java is moving to allow "vendor." as a synonym for "com.vendor." > I'm assuming that module name components have enforced capitalisation, > like all other Haskell identifiers. A namespace is a dot-separated sequence of conids, therefore yes, there is enforced capitalisation. > Eeesh, let's hope ICANN doesn't register a 'std' TLD. I would prefer > "Standard" for this reason and also because the abbreviation seems pretty > pointless. If Std. is going to be the common case, people will complain about having to type the extra five characters. Normally I would say spell it out in full is the best rule. Here, I'm prepared to compromise a little. > Do you have any kind of guarantees of copyright openness in mind? In > Java, everything under java.* is supposed to be owned by Sun. All standard libraries will be copyright to their authors, but must be released under an open source licence. (For instance Hugs at the very least will require the source.) Ideally, I think they should all have the same licence. We need to decide which. LGPL? BSD? Any opinions? > Will it be standard practice for versions of Standard be included with > Haskell compilers? This is the intention. > Could the Prelude make use of Standard? > Could Standard become an alternative to the Prelude? In principle yes. One notable omission from my hierarchy layout proposal is the current Haskell'98 standard libraries. Should they remain at the toplevel? Or should they become Standard.Prelude Standard.IO Standard.List Standard.Monad etc.? Regards, Malcolm From chak@cse.unsw.edu.au Tue Feb 27 23:23:17 2001 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Wed, 28 Feb 2001 10:23:17 +1100 Subject: Hierarchy suggestions In-Reply-To: References: <9584A4A864BD8548932F2F88EB30D1C61157EF@TVP-MSG-01.europe.corp.microsoft.com> Message-ID: <20010228102317B.chak@cse.unsw.edu.au> Malcolm Wallace wrote, > > 1) Std. > > I have a feeling that the "Std." prefix is going to be annoying, > > especially when libraries move from the base hierarchy to the Std > > hierarchy. > > I actually had the same feeling in some ways. The notion of a > "privileged" Std. hierarchy was not originally part of my proposal, > but it seemed to be quite important to some of the implementers at > the Cambridge meeting where I first presented the namespaces idea. I also don't have a good feeling about Std. > I think many people would value a clear signal about whether a library > is truly portable or not. Making that fact a part of the module name > is about as clear and unmistakable as you can get. I can understand the concerns that have surfaced at the meeting, but I am not sure that a prefix is the right way to assert the standardness of a library. > > A portable application will only use libraries from the Std hierarchy, > > so we should make this the default. Non-standard libraries should get > > the prefix, if any. > > A "NonStd." prefix perhaps? The trouble is that it would be very > hard to police. Anybody can write a library with any name, and it > will immediately look standard unless they take the trouble to follow > this convention. In some ways that completely negates the meaning > of standard. "Assume everything is a standard, unless it explicitly > says it isn't!" And it wouldn't solve the problem with having to change the name of the library at a point, where by definition, it is heavily used (because only then we take it as a standard library). > > An alternative is to simply sanction each library individually, as the > > interface is fixed and a portable, well-tested implementation exists. > > Non-sanctioned libraries aren't necessarily provided by all of the main > > implementations, and their interfaces may change (or even differ across > > implementations). > > This was my original idea. But I was swayed towards proposing > a distinguished Std. namespace, mainly because of the > clarity/documentation argument. How do I know whether a library is > portable or not? "Well it seems to work in GHC, so it must be okay..." > It's amazing how many people think some language feature is standard > Haskell'98 just because ghc implements it! There must be an official list of standard libraries. Just as we know have the Library Report that provides the official list of standard libraries. Cheers, Manuel From chak@cse.unsw.edu.au Tue Feb 27 23:56:48 2001 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Wed, 28 Feb 2001 10:56:48 +1100 Subject: Proposal: module namespaces. In-Reply-To: References: <200102271333.FAA25861@mail4.halcyon.com> Message-ID: <20010228105648Y.chak@cse.unsw.edu.au> Malcolm Wallace wrote, > Ashley writes: > > Do you have any kind of guarantees of copyright openness in mind? In > > Java, everything under java.* is supposed to be owned by Sun. > > All standard libraries will be copyright to their authors, but must > be released under an open source licence. (For instance Hugs at the > very least will require the source.) Ideally, I think they should > all have the same licence. We need to decide which. LGPL? BSD? > Any opinions? This depends a bit on what actually we mean by standard. In fact, I don't think that there can be only one standard. There reason is the varying complexity of libraries and the fact that some rely on other non-haskell libraries. For example, the current modules in the Library Report are really standard libraries in the sense that their interface is set in stone and there is as far as technically possible freely available code with absolutely no strings attached. However, this is not going to work for large libraries like HOpenGL or Gtk+HS. Their interface will never be stable simply because they have to track the changes in the corresponding C library (and because they are so big that we will always find mistakes in their interface). Moreover, it doesn't make much sense to require, e.g., that Gtk+HS comes with a license that is less restrictive than LGPL, because GTK+ is LGPL and we can't change this. BTW, this is another reason that I think, Std. doesn't make sense. It's too inflexible. > > Will it be standard practice for versions of Standard be included with > > Haskell compilers? > > This is the intention. Which immediately leads us to protability issues with libraries that are not fully implemented in Haskell, but rely on some external code. Cheers, Manuel From chak@cse.unsw.edu.au Wed Feb 28 00:01:29 2001 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Wed, 28 Feb 2001 11:01:29 +1100 Subject: Module versions In-Reply-To: <20010227121458.B18256@math.harvard.edu> References: <20010227135206.C20080@theseus.mathematik.uni-ulm.de> <20010227121458.B18256@math.harvard.edu> Message-ID: <20010228110129P.chak@cse.unsw.edu.au> Dylan Thurston wrote, > On Tue, Feb 27, 2001 at 03:35:31PM +0000, Malcolm Wallace wrote: > > > > The implication of the Std. namespace is that all such "standard" > > > > libraries will be distributed with all Haskell systems. In other > > > > words, you can rely on a standard library always being there, and > > > > always having the same interface on all systems. > > > > > > What's about version changes? How can anybody garantee that a library is > > > stable? Some functions or instances may become obsolete or even disappear. > > > Other may be needed in later versions of the library. > > > > We can't provide absolute guarantees of course. But this is no > > different from the situation with standard libraries in other languages > > - witness the difficulties with libc versions etc. I think the best > > we can do realistically is to aim for maximum stability. > > But note that there is a well-defined "soname" mechanism in the Unix > world to deal with this issue. This usually works on the object level > rather than the source level; it is usually hard to compile against an > old version of the library (without renaming the library to include a > version number). Like with soname, we could have optional version numbers at the end of each name, which defaults to the latest version if no version is given. Manuel From Christian.Brolin@carmen.se Wed Feb 28 08:49:25 2001 From: Christian.Brolin@carmen.se (Christian Brolin) Date: Wed, 28 Feb 2001 09:49:25 +0100 Subject: Proposal: module namespaces. References: Message-ID: <3A9CBB95.CC8056F7@carmen.se> Malcolm Wallace wrote: > > Christian writes: > > What about the module declaration? Should it be: > > module Text.Xml.Parser where ... > > or just > > module Parser where ... -- located in Text/Xml/Parser.hs? > > The former. The reason is that a compiler needs to generate a unique > linker symbol for each defined function. If the full module name is > not encoded in the source file, you will need to add a commandline > option to the compiler, which is the wrong way to go in my opinion. What?? The compiler knows the full name of the module without the module clause. If it didn't do that, it can't find the modules to compile! Does the compiler opens every file on the Internet to check whether it is the file to compile? How does the compiler find the file to compile in the first place? What should the command line option you mentioned do? > Why is e.g. Parser.f not sufficient as a unique symbol for > Text.Xml.Parser.f? Well, what if you also have Text.Html.Parser.f? > You really need the full thing. Of course, see above. > > I would also like to import modules using relative addresses, e.g. the > > file: > > My/Small/Test/Xml/Parser.hs > > contains: > > import .Lexer -- Relative path to the module: My.Small.Test.Xml.Lexer > > import ..Data -- Relative path to the module: My.Small.Test.Xml.Parser.Data > > import Text.ParserCombinators.HuttonMeijer -- Absolute address > > I'm sorry, I don't entirely follow what the differing numbers of > initial dots mean. They are used to specify relative addresses to other modules. Relative addresses is a very important concept, but You missed it in your proposal. The dots was just my suggestion of a syntax for relative addresses. One dot: Relative to the parent of this module. Two dots: Relative to this module. E.g. module A.B.C.D1 where import A.B.C.D1.E1 import A.B.C.D1.E1.F import A.B.C.D1.E2 import A.B.C.D2 import X.Y.Z would be the same as (delete 'A.B.C'): module A.B.C.D1 where import .D1.E1 import .D1.E1.F import .D1.E2 import .D2 import X.Y.Z would be the same as (delete 'D1'): module A.B.C.D1 where import ..E1 import ..E1.F import ..E2 import .D2 import X.Y.Z Move the package of modules (A.B.C.*) to (Std.AAA.BBB.CCC.*) and rename D1 to DDD: module Std.AAA.BBB.CCC.DDD where import ..E1 import ..E1.F import ..E2 import .D2 import X.Y.Z The only thing that needs to be changed is the module clause. Which of course would be unnecessary if the module clause was dropped. > > When the world realize that this is the XML parser, they won't accept > > the name and I refuse to change my implementation. The only thing that > > is needed to rename (an unused) module hierarchy is to move it. > > If you refuse to change your implementation, someone else will change > it for you! You can't have closed standards. It is not necessary to modify the modules if the module system supports relative addresses!!! The steering wheel of my car is positioned relative to my car, so it is NOT necessary to change that position when I move the car. -- Christian Brolin From joe@isun.informatik.uni-leipzig.de Wed Feb 28 10:17:22 2001 From: joe@isun.informatik.uni-leipzig.de (Johannes Waldmann) Date: Wed, 28 Feb 2001 11:17:22 +0100 (MET) Subject: module namespaces Message-ID: <200102281017.LAA17464@isun11.informatik.uni-leipzig.de> I think the namespace proposal wants to be strictly upward compatible, therefore it's perhaps not the right time to discuss this ... but still I think the question "why should the source text of a module contain its name?" wants an answer. Even if we stick to module headers, I don't really like the idea of `module Fully.Qualified.Name where ..' The proposal mentions the analogy to Java. My knowledge of that is minimal, but in Java, they have `package Foo.Bar.Frobs' (full name required) and `class Frobble' (only last name there). So, a Haskell module corresponds to what? I understand the argument "the compiler needs to generate unique names in the object files" but this is a matter of implementation, about which the programmer (at least theoretically) should not care. I think the underlying design decision here is: how far should the user of a set of modules expect that he can move their source/interface/object files around, and still compile them/link against them correctly. The present proposal seems to imply: not at all. This is a conservative answer. It is easy to implement, and guarantees some consistency. Is it too restrictive? But assume this policy is adopted. Then I am not allowed to move (precompiled) modules around physically. That's why I want some means of renaming them (during importing), and as I wrote earlier, not only for single modules (`import Foo as Bar') but also for complete hierarchies (`import Leipzig.Standard as Standard') A potential problem is that the root of some hierarchy perhaps is just a directory (that contains subdirs and modules) but not itself a module. One would need to write a dummy module that just (qualified-)imports and re-exports all submodules. But this had to be extended whenever a submodule is added. This doesn't feel right. (On the other hand, the libFoo.a file had to be rebuilt anyway on such an occasion.) This leads to another question - during the linking stage: when should the compilation manager look for a single object file, and when should it expect an archive? Anyway I think even the most restricitve form of hierarchical module names would be very helpful. I certainly would start using it. -- -- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ -- -- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 -- From simonmar@microsoft.com Wed Feb 28 10:32:16 2001 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 28 Feb 2001 02:32:16 -0800 Subject: Proposal: module namespaces. Message-ID: <9584A4A864BD8548932F2F88EB30D1C61157F1@TVP-MSG-01.europe.corp.microsoft.com> [ leaving out haskell@haskell.org from the recipient list ] > Malcolm Wallace wrote: > > > > Christian writes: > > > What about the module declaration? Should it be: > > > module Text.Xml.Parser where ... > > > or just > > > module Parser where ... -- located in Text/Xml/Parser.hs? > > > > The former. The reason is that a compiler needs to > generate a unique > > linker symbol for each defined function. If the full module name is > > not encoded in the source file, you will need to add a commandline > > option to the compiler, which is the wrong way to go in my opinion. > > What?? The compiler knows the full name of the module without > the module > clause. If it didn't do that, it can't find the modules to > compile! Does > the compiler opens every file on the Internet to check > whether it is the > file to compile? How does the compiler find the file to compile in the > first place? What should the command line option you mentioned do? The compiler finds the file because you tell it what the filename is. That's the way it works now, and if I understand correctly Malcolm isn't suggesting we change that (and I agree). There are really two issues here: * how do you find a module to compile in the first place (not an issue for interpreters, only for batch compilers). Just run the compiler giving it the filename. * when you import a module, how does the compiler find the interface (or source, in the case of an interpreter) for the target. My feeling is that this happens with a small extension to the current scheme: at the moment, the compilers all have a list of search paths in which to find interfaces/sources. The change is that to find a module A.B.C you search in D/A/B/ (for each D in the search path) rather than just D. GHC's package mechanism will actually work pretty much unchanged with this scheme, I believe. Cheers, Simon From mk167280@students.mimuw.edu.pl Wed Feb 28 10:37:31 2001 From: mk167280@students.mimuw.edu.pl (Marcin 'Qrczak' Kowalczyk) Date: Wed, 28 Feb 2001 11:37:31 +0100 (CET) Subject: Proposal: module namespaces. In-Reply-To: <3A9CBB95.CC8056F7@carmen.se> Message-ID: On Wed, 28 Feb 2001, Christian Brolin wrote: > What?? The compiler knows the full name of the module without the module > clause. It does not. File A/B/C/D.hs can be module A.B.C.D, or module B.C.D which happened to be placed in a directory A, or C.D etc. It's ambiguous. I'm not saying that I want to have to write full paths, but I see no other choice. > The dots was just my suggestion of a syntax for relative addresses. > One dot: Relative to the parent of this module. > Two dots: Relative to this module. It's confusing. If at all, it should be the opposite, analogous to . and .. directories. But it doesn't look clear either. -- Marcin 'Qrczak' Kowalczyk From mk167280@students.mimuw.edu.pl Wed Feb 28 10:41:12 2001 From: mk167280@students.mimuw.edu.pl (Marcin 'Qrczak' Kowalczyk) Date: Wed, 28 Feb 2001 11:41:12 +0100 (CET) Subject: Proposal: module namespaces. In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C61157F1@TVP-MSG-01.europe.corp.microsoft.com> Message-ID: On Wed, 28 Feb 2001, Simon Marlow wrote: > GHC's package mechanism will actually work pretty much unchanged with > this scheme, I believe. I hope that module name clashes across packages will not be fatal. That's why it should probably be somewhat unified with the package system, not built on top of it. I would prefer to be able to just write a full module path in the import clause, including the package name, instead of being forced to put appropriate -package options in the makefile. -- Marcin 'Qrczak' Kowalczyk From simonmar@microsoft.com Wed Feb 28 10:42:38 2001 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 28 Feb 2001 02:42:38 -0800 Subject: module namespaces Message-ID: <9584A4A864BD8548932F2F88EB30D1C60171F4C1@TVP-MSG-01.europe.corp.microsoft.com> Johannes Waldmann writes: > This leads to another question - during the linking stage: > when should the compilation manager look for a single object file, > and when should it expect an archive? I'll explain briefly how GHC would handle this. GHC has a concept of a "package", which is basically a compiled unit consisting of libraries and interfaces (not necessarily Haskell). For each package, the compiler has a specification telling it what the interface search path for this package is, what the libraries are called (and where they live), and what other packages this one depends on. In the hierarchical module scheme, the only thing that changes is that the search paths are now all "roots" of the hierarchical namespace (see my previous message). Cheers, Simon From Christian.Brolin@carmen.se Wed Feb 28 10:44:58 2001 From: Christian.Brolin@carmen.se (Christian Brolin) Date: Wed, 28 Feb 2001 11:44:58 +0100 Subject: Proposal: module namespaces. References: Message-ID: <3A9CD6AA.B331405B@carmen.se> Marcin 'Qrczak' Kowalczyk wrote: > > On Wed, 28 Feb 2001, Christian Brolin wrote: > > > What?? The compiler knows the full name of the module without the module > > clause. > > It does not. File A/B/C/D.hs can be module A.B.C.D, or module B.C.D which > happened to be placed in a directory A, or C.D etc. It's ambiguous. Only if you give the compiler include pathes to both ~ and ~/A, where ~ is the directory containing your A. > I'm not saying that I want to have to write full paths, but I see no other > choice. > > > The dots was just my suggestion of a syntax for relative addresses. > > One dot: Relative to the parent of this module. > > Two dots: Relative to this module. > > It's confusing. If at all, it should be the opposite, analogous > to . and .. directories. But it doesn't look clear either. I just want to left out the redundant information, and . and .. are what remain. import .D2 -- import [A.B.C].D2 import ..E -- import [A.B.C].[D].E -- Christian Brolin From simonmar@microsoft.com Wed Feb 28 10:45:57 2001 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 28 Feb 2001 02:45:57 -0800 Subject: Proposal: module namespaces. Message-ID: <9584A4A864BD8548932F2F88EB30D1C60171F4C2@TVP-MSG-01.europe.corp.microsoft.com> > On Wed, 28 Feb 2001, Simon Marlow wrote: > > > GHC's package mechanism will actually work pretty much > unchanged with > > this scheme, I believe. > > I hope that module name clashes across packages will not be > fatal. eek! I thought the reason for having a richer module namespace was so that we didn't have to allow module shadowing. > That's > why it should probably be somewhat unified with the package > system, not > built on top of it. > > I would prefer to be able to just write a full module path in > the import > clause, including the package name, instead of being forced to put > appropriate -package options in the makefile. This may be possible too. Cheers, Simon From simonmar@microsoft.com Wed Feb 28 11:40:06 2001 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 28 Feb 2001 11:40:06 -0000 Subject: Alternative hierarchy proposal. Message-ID: <9584A4A864BD8548932F2F88EB30D1C61157F2@TVP-MSG-01.europe.corp.microsoft.com> Here's my attempt at a library hierarchy. No ASCII art - I've just used indentation to indicate nesting. I've merged my initial sketch with Malcolm's proposal, so some of the subtrees are identical, but I've changed names here and there (eg. Interface --> Console, Encoding --> Codec or Digest). The leaves are all real modules, some of which already exist in some form in hslibs. The non-leaf nodes may also be imported as Haskell modules: more about this later. Note: I haven't addressed the issue of what parts of the tree should be "standard" or not - I've just populated the tree. I've placed most of the tree under "Haskell.". This is roughly equivalent to Malcolm's "Std.", except that my requirements for entry into Haskell are much slacker :-) I'm assuming there is a separate mechanism for deciding which libraries are standard, and a mechansim by which a library specification can be evolved into a standard. I've included the Haskell 98 standard libraries, placed in their correct places in the tree. No doubt the interfaces to these libraries, and even their existence in the new scheme, is now up for debate. The prelude is Haskell.Prelude, and is probably just a re-export of various other parts of the tree. In practice the implementation will be system-specific. I've noticed that the tree gets fairly deep in places ("Haskell.Lang.Foreign.Marshal.Array" ??) so a modification to the language extension to allow shortening of names might be in order, something like Java's "import java.lang.*". System specific libraries live in GHC.*, NHC.*, Hugs.* etc. One problem with this scheme which I haven't quite resolved, is what happens when you import a non-leaf node. I've identified four possible meanings, each of which is useful in certain cases: (a) bring into scope everything below that node (might be nice for eg. Foreign, Foreign.Ptr etc.) (b) bring into scope some things below the node (eg. Foreign exports everything except C.*) (b) get a default module of some description (eg. Pretty vs. Pretty.HughesPJ) (c) import a unique module (eg. Array vs. Array.IArray) Note that no special compiler support is required for importing a non-leaf node, and all of the above schemes can co-exist. Ok, here we go. I've marked optional libraries with (opt), the rest are assumed to have portable implementations, or be implementable in a portable way, for any Haskell compiler with FFI support. Cheers, Simon ------------------------------------------------------------------------ -- Haskell Prelude -- Haskell98 Prelude -- mostly just re-exports other parts of the tree. Lang -- "language support" Foreign Ptr -- should be in Data??? StablePtr -- should be in System.GC??? ForeignPtr -- should be in System.GC??? Storable Marshal Alloc Array Errors Utils C Types Errors Strings =20 Array -- Haskell 98 Array library IArray -- (opt) GHC's overloaded arr libs MArray -- (opt) IOArray -- mutable arrays in the IO/ST monads STArray Monad -- Haskell 98 Monad library ST LazyST Either -- monad libraries State etc. Exception -- (opt) Generics -- (opt) Memo -- (opt) Unique ShowFunctions -- sounds more impressive than it is Dynamic =09 System IO -- H98 + IOExts - IOArray - IORef Directory Select GC Weak -- (opt) StableName -- (opt) Console GetOpt Readline Time -- H98 + extensions Locale CPUTime -- split H98 "System" (too generic) into: Exit Environment (Args, Prog, Env ...) Numeric DSP FFT FIR Noise Oscillator Gaussian Source -- hslibs/hssource AbsSyn Lexer Parser Pretty Concurrent -- as hslibs/concurrent CVar -- (some of these could also go in "Data"). Chan MVar Merge QSem QSemN SampleVar Semaphore Parallel -- as hslibs/concurrent/Parallel Strategies Net -- won't need to be optional (will use FFI only) Socket -- redesign (merge w/ SocketPrim) BSD -- remove?? URI CGI -- one in hslibs is ok? Text Regex -- previously RegexString PackedString -- previously Regex (remove?) Pretty -- default (HughesPJ?) HughesPJ Wadler ... HTML -- HTML combinator lib XML Combinators Parse Pretty Types Parse -- no default Parsec Hutton_Meijer=20 ... Posix -- redesigned, use FFI only Database SQL ODBC =20 Debug Observe Quickcheck Trace Graphics UI Drawing Format -- perhaps should be under Data.Encoding Data Bits Char -- H98 Complex -- H98 Either -- H98 Int Maybe -- H98 List -- H98 PackedString Ratio -- H98 Word IORef STRef Binary -- Haskell binary I/O Digest MD5 ... -- others (CRC ?) Codec Bzip2 Gzip MPEG -- or perhaps Audio/Graphics.Format.MPEG? Structures Trees AVL RedBlack BTree Queue Bankers FIFO Collection Graphs FiniteMap Set Edison -- (opt, uses multi-param type classes) GHC Primitives UnboxedTypes ... ------------------------------------- From joe@isun.informatik.uni-leipzig.de Wed Feb 28 11:59:23 2001 From: joe@isun.informatik.uni-leipzig.de (Johannes Waldmann) Date: Wed, 28 Feb 2001 12:59:23 +0100 (MET) Subject: module namespaces In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C60171F4C1@TVP-MSG-01.europe.corp.microsoft.com> from Simon Marlow at "Feb 28, 2001 02:42:38 am" Message-ID: <200102281159.MAA17507@isun11.informatik.uni-leipzig.de> > GHC has a concept of a "package", which is basically a compiled unit > consisting of libraries and interfaces (not necessarily Haskell). OK, so this would correspond (roughly) to Java packages, while Haskell modules correspond to Java classes? Note that in Java, you can import a class (`import Foo.Bar') or a package (`import Foo.*'), and that's a syntactic difference built into the language. Do we need the same thing for Haskell? Then the compiler/linker would know: import a package: link with libPack.a; import a module: link with Module.o > For each package, the compiler has a specification telling it ^^^^^^^^^^^^^^^^ So you'd have to change the compiler (driver script) if you want to add a package? Yes I know how this works with ghc now, but I thought the new namespace proposal could somehow give a more uniform solution. -- -- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ -- -- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 -- From joe@isun.informatik.uni-leipzig.de Wed Feb 28 12:17:10 2001 From: joe@isun.informatik.uni-leipzig.de (Johannes Waldmann) Date: Wed, 28 Feb 2001 13:17:10 +0100 (MET) Subject: Alternative hierarchy proposal. In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C61157F2@TVP-MSG-01.europe.corp.microsoft.com> from Simon Marlow at "Feb 28, 2001 11:40:06 am" Message-ID: <200102281217.NAA17524@isun11.informatik.uni-leipzig.de> Please mind the "style warning" http://haskell.org/pipermail/haskell/2001-February/000473.html > MArray -- (opt) > IOArray -- mutable arrays in the IO/ST monads MArray looks cryptic. Why not Array.Mutable, and similar. There are a few more places where this applies. Of course this is rather irrelevant to the layout discussion now. But perhaps not, since it's the question of introducing small sub-modules, or using name prefixes. -- -- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ -- -- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 -- From simonmar@microsoft.com Wed Feb 28 12:12:50 2001 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 28 Feb 2001 12:12:50 -0000 Subject: module namespaces Message-ID: <9584A4A864BD8548932F2F88EB30D1C60171F4C8@TVP-MSG-01.europe.corp.microsoft.com> > > For each package, the compiler has a specification telling it=20 > ^^^^^^^^^^^^^^^^ > So you'd have to change the compiler (driver script)=20 > if you want to add a package? Yes I know how this works with ghc now, > but I thought the new namespace proposal could somehow give > a more uniform solution. At the moment, or rather in the forthcoming GHC 5.00, the package specifications are in a configuration file which GHC reads. GHC has command line options for installing new packages and deleting existing ones (actually just installing/deleting the package spec, not the package itself). Cheers, Simon From simonmar@microsoft.com Wed Feb 28 14:33:14 2001 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 28 Feb 2001 06:33:14 -0800 Subject: Alternative hierarchy proposal. Message-ID: <9584A4A864BD8548932F2F88EB30D1C60171F4C9@TVP-MSG-01.europe.corp.microsoft.com> > Please mind the "style warning" > http://haskell.org/pipermail/haskell/2001-February/000473.html > > > MArray -- (opt) > > IOArray -- mutable arrays in the IO/ST monads > > MArray looks cryptic. Why not Array.Mutable, and similar. > There are a few more places where this applies. > > Of course this is rather irrelevant to the layout discussion now. > But perhaps not, since it's the question of introducing > small sub-modules, or using name prefixes. Good point. However, this scheme is following another style guideline, which is that the module name follows the type name, when the module defines a type. Perhaps the MArray type should also be renamed to Mutable (i.e. Haskell.Lang.Array.Mutable qualified), but this doesn't look as nice. Cheers, Simon From joe@isun.informatik.uni-leipzig.de Wed Feb 28 18:16:47 2001 From: joe@isun.informatik.uni-leipzig.de (Johannes Waldmann) Date: Wed, 28 Feb 2001 19:16:47 +0100 (MET) Subject: Alternative hierarchy proposal. In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C60171F4C9@TVP-MSG-01.europe.corp.microsoft.com> from Simon Marlow at "Feb 28, 2001 06:33:14 am" Message-ID: <200102281816.TAA17652@isun11.informatik.uni-leipzig.de> > Good point. However, this scheme is following another style guideline, > which is that the module name follows the type name, when the module > defines a type. Yes this is a good principle, and it should be kept. > Perhaps the MArray type should also be renamed That was my intention. > to Mutable (i.e. Haskell.Lang.Array.Mutable qualified), but this doesn't > look as nice. So what about ...Mutable.Array, then? The type name would be `Array'. What we're in fact trying to do here, roughly, is to give different implementations of one interface. Well, it's not exactly the same, but still these are Arrays. The Edison user guide gives a good discussion of similar design decisions. Regards, -- -- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ -- -- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/252 --