
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 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 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 ... Posix -- redesigned, use FFI only Database SQL ODBC 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 ... -------------------------------------

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 --

On Wed, Feb 28, 2001 at 11:40:06AM -0000, Simon Marlow wrote:
System IO -- H98 + IOExts - IOArray - IORef Directory Select
-- split H98 "System" (too generic) into: Exit Environment (Args, Prog, Env ...)
Posix -- redesigned, use FFI only
I think it would be more intuitive to have
System
IO
POSIX
BSD
...
Processes
POSIX
rather than lumping all the POSIX stuff under one top level heading.

Simon Marlow wrote:
Here's my attempt at a library hierarchy. No ASCII art
Just to let everyone know that Simon's proposed tree is now on the web alongside mine. See: http://www.cs.york.ac.uk/fp/libraries/ Regards, Malcolm

On Thu, Mar 08, 2001 at 08:24:26PM +0000, Malcolm Wallace wrote:
Simon Marlow wrote:
Here's my attempt at a library hierarchy. No ASCII art
Just to let everyone know that Simon's proposed tree is now on the web alongside mine. See:
Ermmm, OK, so what now?
What we currently seem to have seems rather akin to the Bit(s) situation
this is meant to avoid :-)
Anyway, here are my opinions and an attempt to merge the two together.
Flames^WComments welcome.
Here is a list of common top level hierarchies:
Data Database Debug Graphics Haskell Network Numeric Posix Text
Data Database Debug Graphics Lang Net Numeric Posix Text
Personally I prefer the latter list, and as I've said before I think
POSIX would be better split up.
In MW:
* Algebra
Seems fair enough
* Interface
Not sure about the name of this - contains GetOpt and Readline
GetOpt might belong better under parsing somewhere and ReadLine
in IO? Having just noticed them on SM, they are next to IO under
System.
* Win32
Dunno what would go in here. Possibly OS.Win32 or something would
be better regardless to kep the top level branches to a minimum?
In SM:
* System
THis is equivalent to Haskell.Plus.Unsafe I think. Personally I
think this is a good idea as it is not implementable in Haskell.
I'm not sure the Plus distinction is necessary though.
* Source
This appears to be parsers etc for Haskell code, and I don't see
why it should be here rather than Text.Haskell next to HTML, XML
etc
* Concurrent
I don't know anything about this but it looks fair enough
* Parallel
As the comment is "as hslibs/concurrent/Parallel" should it not go
under Concurrent?
* Prelude
MW has Haskell.Language.CoreSyntax which I think makes more sense
* GHC
Probably better under Lang.CompilerSpecific.GHC?
There's also the Std vs Non-std top branch debate. I agree with the
non-std myself.
The SM trees in general seem a bit better thought out to me too, e.g.
I don't think Bits or MD5 belong under Data.Encoding.
To summarise I think something like:
Algebra: As MW
Concurrent: As SM plus Parallel
Data: As SM
Database: As SM and MW
Debug: As SM and MW
Graphics: As MW (more detailed than SM)
Lang: As SM, plus CompilerSpecific.*, Prelude, { System.* from SM plus POSIX plus BSD }
Net: As SM (plus a POSIX module if POSIX talks about this)
Numeric: As SM and MW
OSSpecific: As explained
Text: As SM and MW
User: your@email.address gets address.email.your.* off of this
BTW, the first bit of Data is repeated twice on the SM list
Thanks
Ian
--
Ian Lynagh -

Ian Lynagh wrote:
Data Database Debug Graphics Haskell Network Numeric Posix Text Data Database Debug Graphics Lang Net Numeric Posix Text
Personally I prefer the latter list,
I really prefer full spellings to abbreviations - otherwise we might end up with Data DB Dbg Gr Hs Lang Net Num Posix Txt which is positively horrible. However, I could probably live with some shortening - Network to Net is common enough in everyday speech. One abbreviation I have always disliked intensely though is Lang. It just doesn't convey any clear meaning to me. Ok, so it is reasonably obvious that it is short for Language, but even then, on its own, it is an ambiguous category. Does it refer to natural languages, formal languages, programming languages, or this specific programming language? If the latter, then Haskell.Language seems clearer to me, or come to that, just Haskell. The other thing that bothers me about Lang is that I don't see the connection between many of the things proposed to go into it, and the Haskell language itself. The FFI is the best candidate, because it clearly extends the source language. Likewise, Generics and Dynamic. But why should libraries like Array, Memo, and Monad be in Lang? They don't extend the language. And of course some things /not/ currently in Lang seem to have everything to do with the language - like the Haskell source parser, abstract syntax, source pretty-printer etc. These were the reasons I proposed a hierarchy like Haskell Plus Foreign Generics Dynamic Language AbstractSyntax Parse PrettyPrint Here in my scheme, Haskell.Plus contains extensions to the language, and Haskell.Language contains utilities to manipulate the source language itself. Simon proposed Haskell.Source for the latter, which would also be a fine name, provided there were no Haskell.Lang category to confuse you. My final difficulty with the Lang category is that, if it contains extensions to the language, people will be misled into thinking that the extensions are truly a part of the language standard. After all, they are categorised in Lang! In my opinion, a clearer name is needed, to emphasise the extensional nature of some of the libraries. Regards, Malcolm

Sat, 10 Mar 2001 12:24:13 +0000, Malcolm Wallace
Here in my scheme, Haskell.Plus contains extensions to the language, and Haskell.Language contains utilities to manipulate the source language itself.
I must say that I haven't guessed what Haskell.Plus means until I saw it explained. It is not clear. Also tools for manipulating the language sources are very different from language support modules. They should not be put together; it's a coincidence that they could be put under the title "Haskell". Instead, tools for manipulating our language (parsers, typecheckers etc.) should be together with tools for manulpulating other languages, and language-independent tools. BTW. I'm working on a Haskell<->Python binding. Where should it go? -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

Marcin 'Qrczak' Kowalczyk wrote:
Also tools for manipulating the language sources are very different from language support modules. They should not be put together;
I think this further supports my point that the name "Lang" is ambiguous. But I really have no idea what a "language support module" might be. Why does the language need support? In a sense, don't /all/ libraries "support" the language, simply by providing useful abstractions? If the term "language support module" means something more specific, then what exactly? Does it mean that the module requires extra support /not/ found in the standard language? If so, then "language support" is misleading - you really mean "beyond-the-language support", or in simple terms "extensions".
Instead, tools for manipulating our language (parsers, typecheckers etc.) should be together with tools for manulpulating other languages, and language-independent tools.
Well, yes I could agree with this. Maybe the Haskell language should have a special "privileged" status amongst the many languages we want to manipulate, simply because we are talking about the Haskell library structure itself? But maybe not. I don't mind too much.
BTW. I'm working on a Haskell<->Python binding. Where should it go?
Haskell.Plus.Foreign.Python by analogy with Haskell.Plus.Foreign.C or maybe just Haskell.Plus.Python Haskell.Plus.C or indeed, how about Language.Python Language.C Language.Haskell ? It depends to some extent on what you want to do with the foreign language. Are you writing a foreign function interface, or are you writing tools to manipulate Python source code + abstract syntax? Should we have different hierarchies for these two different kinds of library? Regards, Malcolm

Sat, 10 Mar 2001 18:05:43 +0000, Malcolm Wallace
But I really have no idea what a "language support module" might be.
Functionality which is hardwired in the implementation, not definable portably and efficiently, exposed as a plain module. Doesn't matter if it's standard. For example IO, Array, StablePtr, Dynamic, Observe. OK, probably it should not matter for the programmer how much magic it requires to be implemented, so modules should be named basing only on the subject they are about. A tree structure, especially without aliases, doesn't work well if there are several criteria for naming things, e.g. * what kind of functionality (e.g. a HTML parser, a database interface), * conforming to what standards (e.g. Haskell 98, Posix, BSD, ghc's / nhc98's extension), * what magic it requires to be implemented (pure Haskell wrapper, needs heavy runtime system support), * where did it come from, i.e. author's / company's name. For users the first category is the most important. For implementers all except the first. I would try to use the first category as much as possible, and only make differences wrt. other categories deeper in the tree if needed. For example let's put Posix filesystem functions and BSD symlink support near Directory, Readline near Curses and hypothetical WinConsole, don't make a subtree for Haskell 98 modules, and don't expect independent vendors to put their modules in their own subtrees. If it's natural that one of several modules will be chosen basing on portability switches, it's a sign to put them together.
Haskell.Plus.Foreign.Python
Ugh, sorry, I can't stand Haskell.Plus. Every module changes Haskell-without-that-module into Haskell-plus-that-module!
Are you writing a foreign function interface, or are you writing tools to manipulate Python source code + abstract syntax?
A foreign function interface.
Should we have different hierarchies for these two different kinds of library?
I'm not sure. In interpreted languages they are blurred. In compiled languages there is a clear distinction: either it works on sources (e.g. generates documentation) or interoperates with live compiled modules. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

Marcin 'Qrczak' Kowalczyk wrote:
there are several criteria for naming things, e.g.
* what kind of functionality (e.g. a HTML parser, a database interface), * conforming to what standards (e.g. Haskell 98, Posix, BSD, ghc's / nhc98's extension), * what magic it requires to be implemented (pure Haskell wrapper, needs heavy runtime system support), * where did it come from, i.e. author's / company's name.
For users the first category is the most important. For implementers all except the first.
I would try to use the first category as much as possible, and only make differences wrt. other categories deeper in the tree if needed.
I tend to agree with this. The functionality should be primary in any naming scheme. The third category (magic required) can also (sometimes) be important to an end-user - they need to know whether a library can be used portably across compilers, but that is all. I guess we might therefore want to consider moving Foreign from Haskell.Extensions.Foreign to Haskell.Foreign whilst keeping (for instance) Haskell.Extensions.Concurrent where it is, because it is only available in ghc. Or come to that, maybe the latter really belongs in GHC.Concurrent ? Maybe there is no need for an Extensions sub-tree at all - just place them under the relevant implementation? Regards, Malcolm

On Sat, Mar 10, 2001 at 02:23:05PM +0000, Marcin 'Qrczak' Kowalczyk wrote:
Sat, 10 Mar 2001 12:24:13 +0000, Malcolm Wallace
pisze: Here in my scheme, Haskell.Plus contains extensions to the language, and Haskell.Language contains utilities to manipulate the source language itself.
I must say that I haven't guessed what Haskell.Plus means until I saw it explained. It is not clear.
I agree. I think Haskell.Extensions is far clearer.
Also tools for manipulating the language sources are very different from language support modules. They should not be put together; it's a coincidence that they could be put under the title "Haskell".
Instead, tools for manipulating our language (parsers, typecheckers etc.) should be together with tools for manulpulating other languages, and language-independent tools.
Again agreed, as I've said elsewhere.
Ian
--
Ian Lynagh -

Ian Lynagh wrote:
I must say that I haven't guessed what Haskell.Plus means until I saw it explained. It is not clear.
I agree. I think Haskell.Extensions is far clearer.
Ok. Another suggestion, that works even without the "Haskell." prefix might be "Appendix." Regards, Malcolm
participants (5)
-
Ian Lynagh
-
Johannes Waldmann
-
Malcolm Wallace
-
qrczak@knm.org.pl
-
Simon Marlow