Library hierarchy, contd.
Simon Marlow
simonmar@microsoft.com
Wed, 23 May 2001 17:43:01 +0100
Dear library folks,
Having finished my current batch of compiler hacking I'd like to
kickstart the libraries discussion again. As you may recall, we were
stuck on the layout of the library hierarchy - below I've appended a new
version (relative to Malcolm's last version) with some changes which
I've listed first. I hope we can take this and converge on something
which we're all happy with.
I've also included an attempt at a set of guidelines for the contents of
the top-level categories, as requested by one or two people: this should
make it easier to place new libraries, and it's also useful to see some
of the places where categories overlap. We should also write down
guidelines on naming (not only for libraries themselves but also for
functions, types and classes) at some point.
There are several process-related issues to agree on before we can start
actually writing code, but this message is too long already so I'll try
to tackle them in separate mails tomorrow.
Cheers,
Simon
Changes to the hierarchy
- Data and Structures merged. The distinction between the two=20
isn't clear: eg. IORef and STRef could be considered structures, as
could Complex, Maybe, Either, List, PackedString etc. Put them all
under Data - I think Data.Array, Data,Trees etc. look quite natural.
- Moved Control back up to the top level (was previously in System).
I'll give way on the Lang issue, but I think we'll have to expand
the remit of Data to include not only data types themselves but also
operations and classes over data (we already have Data.Memo), so
now Dynamic and Generics fit in there too.
Having a 'Type' hierarchy doesn't seem appropriate, because most
libraries in Data also define types and it would just create
confusion.
- Moved Monad back into Control.
- Added hypothetical Network.Protocol.{HTTP,FTP,SMTP,...}
- Added Data.Bool, Data.Tuple
- Added Text.Show & Text.Read
- Moved Prelude.ShowFunctions to Text.Show.Functions.
- Clarified that Numeric exports the Haskell 98 numeric classes (Num,
Integral, Real etc.).
- Renamed URL back to URI.
- Capitalised NHC (hope that's OK).
- Algebra & Numeric could be merged (as suggested by Dylan Thurston in
the previous thread), I haven't made any changes here yet though.
Numeric seems an appropriate place for the existing numeric
operations and classes, but 'Math' would be less so.
- There are still a few things left in the Prelude that don't have a
home elsewhere: curry, uncurry, id, const, (.), asTypeOf, seq, ($!).
------------------------------------------------------------------------
-----
Hierarchy guidelines
Control=20
Libraries which provide functions, types or classes whose purpose
is primarily to express control structure.
=09
Data
Libraries which provide data types, operations over data types, or
type classes, except for libraries for which one of the other more
specific categories is appropriate.
Algebra
? (someone more knowledgable please fill this in)
Database
Libraries for providing access to or operations for building
databases.
Debug
Support for debugging Haskell programs.
FileFormat
Support for reading and/or writing various file formats (except
language source which lives in Language, and textual file formats
which are catered for in Text).
Foreign
Interaction with code written in a foreign programming language.
Graphics
Libraries for producing graphics or providing graphical user
interfaces.
Language
Libraries for operating on or generating source code in various
programming languages, including parsers, pretty printers, abstract
syntax definitions etc.
Numeric
Functions and classes which provide operations over numeric data.
Network
Libraries for communicating over a network, including
implementations of network protocols and standards.
System
Libraries for communication with the system on which the Haskell
program is running (including the runtime system).
Text
Libraries for parsing and generating data in a textual format
(including structured textual formats such as XML, HTML, but not
including programming language source, which lives in Language).
Others: GHC, NHC, Edison
Further top-level names will be allocated on an as-needed basis.
------------------------------------------------------------------------
-----
Prelude -- Haskell98 Prelude (mostly just re-exports
other parts of the tree).
Control
Exception -- (opt, inc. error & undefined)
Concurrent -- as hslibs/concurrent
CVar -- these could all be moved under Data
Chan
MVar
Merge
QSem
QSemN
SampleVar
Semaphore
Parallel -- as hslibs/concurrent/Parallel
Strategies
Monad -- Haskell 98 Monad library
ST -- ST defaults to Strict variant?
Strict -- renaming for ST
Lazy -- renaming for LazyST
Either -- monad libraries
State
Error
etc.
Data
Bits
Bool -- &&, ||, not, otherwise
Tuple -- fst, snd
Char -- H98
Complex -- H98
Dynamic
Either
Int
Maybe -- H98
List -- H98
PackedString
Ratio -- H98
Word
IORef
STRef
Binary -- Haskell binary I/O
Digest
MD5
... -- others (CRC ?)
Array -- Haskell 98 Array library
Overloaded -- (opt) IArray - GHC's overloaded arr libs
Mutable -- (opt) MArray
IO -- mutable arrays in the IO/ST monads
ST
Trees
AVL
RedBlack
BTree
Queue
Bankers
FIFO
Collection
Graphs
FiniteMap
Set
Memo -- (opt)
Unique
Algebra
DomainConstructor -- formerly DoCon
Geometric -- formerly BasGeomAlg
Database
MySQL
PostgreSQL
ODBC
Debug
Trace
Quickcheck
Observe -- choose a default amongst the variants
Textual -- Andy Gill's release 1
ToXmlFile -- Andy Gill's XML browser variant
GHood -- Claus Reinke's animated variant
Edison -- (opt, uses multi-param type classes)
Prelude -- large self-contained packages should have
Collection -- their own hierarchy? Like a vendor branch.
Queue -- Or should the whole Edison tree be placed
... -- under [Data.]Structures?
FileFormat -- 'Codec' might be a more accurate name?
Compression
Gzip
Bzip2
Graphics
Jpeg
Ppm
Png
Audio
Wav
Mp3
Video
Mpeg
QuickTime
Avi
Foreign
Ptr
StablePtr
ForeignPtr -- rename to FinalisedPtr? to void confusion with
Foreign.Ptr
Storable
Marshal
Alloc
Array
Errors
Utils
C
Types
Errors
Strings
Graphics
UI
Gtk
FranTk
Fudgets
CleanIO
Drawing
HOpenGL
Format -- use FileFormat.Graphics instead
Language
Haskell -- hslibs/hssource
Syntax
Abstract
Core
Lexer
Parser
Pretty
Python?
C?
Numeric -- exports std. H98 numeric type classes
DSP
FastFourierTransform
Noise
Oscillator
Network -- won't need to be optional (will use FFI only)
Socket -- redesign (merged Socket, SocketPrim, BSD)
URI -- general URI parsing
CGI -- one in hslibs is ok?
Protocol
HTTP
FTP
SMTP
System -- Interaction with the "system"
IO -- H98 + IOExts - IOArray - IORef
Directory
Select
Console
GetOpt
Readline
Posix -- redesigned, use FFI only
IO -- there was a suggestion to split Posix into
Process -- separate chunks like IO + Process
Win32 -- the full win32 operating system API
Mem -- rename from cryptic 'GC'
WeakPointer -- (opt)
StableName -- (opt)
Time -- H98 + extensions
Locale -- H98
CPUTime -- H98
-- split H98 "System" (too generic) into:
Exit
Environment (getArgs, getProgName, getEnv ...)
Text
Read
Show
Functions -- optional instance of Show for
functions.
Regex -- previously RegexString
PrettyPrinter -- default (HughesPJ?)
HughesPJ
Wadler
...
Html -- HTML combinator lib
Xml
Combinators
Parse
Pretty
Types
ParserCombinators -- no default
Parsec
Hutton_Meijer
...
GHC
Primitives
UnboxedTypes
...
NHC
Stuff