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