Re: Proposal: module namespaces.

2001-02-28 Thread Christian Brolin

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

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-28 Thread Marcin 'Qrczak' Kowalczyk

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



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-28 Thread Christian Brolin

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

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-28 Thread Marcin 'Qrczak' Kowalczyk

Wed, 28 Feb 2001 11:44:58 +0100, Christian Brolin [EMAIL PROTECTED] pisze:

  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.

When I am in the directory and compile D.hs, I get different result
than when I'm one level up and compile C/D.hs? It's fragile.

 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

Skipping D alone is not a big deal, and it's known because it's the
current module, so the second form is not needed - you could say .D.E
as well.

It's still confusing: in path names, you write the initial '/'
for an absolute name and omit it for a relative name, but here
it's the opposite. I would drop it.

Instead I would let the current directory play as an implicit module
root. I.e. you can refer to D2 as D2, and in this case you cannot refer
to the global module D2 if it exists (but you can refer to D2.Other
if D2 is a global directory and there is no local directory named D2).

A prefix to add to names of compiled modules will have to be
specifiable at the compiler commandline, otherwise projects would be
forced to put all their files in deep subdirectories only to generate
right module paths.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTPCZA
QRCZAK


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-28 Thread Christian Brolin

Marcin 'Qrczak' Kowalczyk wrote:
 
 Wed, 28 Feb 2001 11:44:58 +0100, Christian Brolin [EMAIL PROTECTED] pisze:
 
   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.
 
 When I am in the directory and compile D.hs, I get different result
 than when I'm one level up and compile C/D.hs? It's fragile.

This dilemma comes from the fact that you don't tell the compiler what
module to compile, but just give it some Haskell code. You should always
compile the module with:
compile A.B.C.D, i.e. tell the compiler which module you want to
compile, and the compiler will find the source code.

  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
 
 Skipping D alone is not a big deal, and it's known because it's the
 current module, so the second form is not needed - you could say .D.E
 as well.

Or A.B.C.D.E, so the first is not needed either. The idea is to avoid
redundant information, not to save some typing. I can go with:
import parent.D2
import parent.this.E

where 'parent' and 'this' are two new reserwed words. I want relative
addresses to be able to easily move packages of modules. 

 It's still confusing: in path names, you write the initial '/'
 for an absolute name and omit it for a relative name, but here
 it's the opposite. I would drop it.

What? The concept of relative addresses or just my home made dot-syntax? 

 Instead I would let the current directory play as an implicit module
 root. I.e. you can refer to D2 as D2, and in this case you cannot refer
 to the global module D2 if it exists (but you can refer to D2.Other
 if D2 is a global directory and there is no local directory named D2).

I think this is very confusing! And restrictive.

 A prefix to add to names of compiled modules will have to be
 specifiable at the compiler commandline, otherwise projects would be
 forced to put all their files in deep subdirectories only to generate
 right module paths.

Yes, in the case of a file system, you have to specify a set of
directories for the compiler to search for the sources. The compiler
should look for the module A.B.C.D and not the module D.

I would like to compile the program above with:
hcc -i~brolin/haskell/test A.B.C.D

The compiler understands the import clauses and locates the imported
modules and recursively compiles the ones that need to be compiled.

The above command is not the same as:
hcc -i~brolin/haskell/test/A/B/C D

Since this compiles the module D and not the module A.B.C.D. (The last
dot is a period and is not part of the module identification:)

The module A.B.C.D can be mapped to the file system, e.g. Unix:
~brolin/haskell/test/A/B/C/D.hs
or maybe:
~brolin/haskell/test/A.B.C.D.hs
or maybe a compiled package:
~brolin/haskell/packages/ABCD.har

--
Christian Brolin

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-28 Thread Marcin 'Qrczak' Kowalczyk

Wed, 28 Feb 2001 17:31:13 +0100, Christian Brolin [EMAIL PROTECTED] pisze:

 This dilemma comes from the fact that you don't tell the compiler what
 module to compile, but just give it some Haskell code. You should always
 compile the module with:
 compile A.B.C.D, i.e. tell the compiler which module you want to
 compile, and the compiler will find the source code.

It must work well with Makefiles. I can imagine that it's doable in
this case, but generally it should work to specify the filename too.

  I would drop it.
 
 What? The concept of relative addresses or just my home made dot-syntax?

The dot-syntax, and faced with inability of finding a better scheme -
the concept.

  Instead I would let the current directory play as an implicit module
  root. I.e. you can refer to D2 as D2, and in this case you cannot refer
  to the global module D2 if it exists (but you can refer to D2.Other
  if D2 is a global directory and there is no local directory named D2).
 
 I think this is very confusing! And restrictive.

It may be confusing (but not more than having your own function
called sortBy).

It's not restrictive. When you want to use a module, don't provide
a module of the same name - *that* would be confusing when used
(if allowed).

It has an advantage that it's simpler. The compiler has a set of
roots and there is just one form of module paths.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTPCZA
QRCZAK


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-27 Thread Ketil Malde

Malcolm Wallace [EMAIL PROTECTED] 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

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-27 Thread Stefan Karrmann

Malcolm Wallace schrieb folgendes am Mon, Feb 26, 2001 at 05:59:30PM +:
 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

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-27 Thread Frank Atanassow

I have two nitpicking comments.

Malcolm Wallace wrote (on 26-02-01 17:59 +):
   * 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

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-27 Thread Christian Brolin

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

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Proposal: module namespaces.

2001-02-27 Thread Ashley Yakeley

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


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell