[[project @ 2001-07-05 13:52:49 by simonmar]
simonmar**20010705135249
Latest revisions:
- the language extension proposal is included, importing a slightly
edited version of Malcolm's original proposal. The section on
'implicit as' is placed under a "possible extension" section
heading, as we haven't come to a conclusion on this yet.
- Note proposal to rename Org to Contrib
- Add hierarchy design guidelines
- Rename NHC to Nhc consistently
- Elaborate on what we mean by "approved extensions" in the
portability section.
] {
hunk ./doc/libraries.sgml 13
- This document consistutes part of a proposal for an
- extension to the Haskell 98
- language. The full proposal has several parts:
+ This document consistutes a proposal for an extension to the
+ Haskell
+ 98 language. The proposal has several parts:
hunk ./doc/libraries.sgml 22
- name is a sequence of components separated by periods.
+ name is a sequence of components separated by periods. The
+ extension is described in .
hunk ./doc/libraries.sgml 116
+
+ The language extension
+
+ The key concept here is to map the module namespace into a
+ hierarchical directory-like structure. We propose using the dot as
+ a separator, analogous to Java's usage for namespaces.
+
+ 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 this proposal
+ proposal here.
+
+ This is a surface change to the module naming convention. It
+ does not introduce nested definition of modules. The syntax we
+ propose (a dot separator) is familiar from other languages such as
+ Java, but could in principle be something else, for instance a
+ prime ', 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
+ qconid -> [modid .] conid
+
+
+ where currently the syntax is
+
+
+ modid -> conid
+ qconid -> [modid .] conid
+
+
+ Note that the new syntax is recursive, a
+ modid may contain multiple components separated
+ by dots, where the final component is a conid.
+
+ A 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
+
+
+
+ A possible extension
+
+ The use of qualified imports has become more verbose: for
+ instance
+
+
+ import qualified XmlParse
+ ... XmlParse.element f ...
+
+
+ becomes
+
+
+ import qualified Text.Xml.Parse
+ ... Text.Xml.Parse.element f ...
+
+
+ It is usually more convenient to make use of Haskell's
+ as keyword to shorten qualified identifiers:
+
+
+ import qualified Text.Xml.Parse as Parse
+ ... Parse.element f ...
+
+
+ A possible extension to the proposal is to make this use
+ of as 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.
+
+
+
+ Renaming subtrees
+
+ Various proposals have been made to allow you to rename a
+ whole subtree. This may occasionally be convenient: for example
+ suppose there are several libraries under
+ Org.Com.Microsoft that I need to import, it
+ would be easier to rename this subtree to just
+ Microsoft for use in future import
+ declarations. For example:
+
+
+ import Org.Com.Microsoft.* as Microsoft.*
+ import Microsoft.Foo
+ import Microsoft.Bar
+ ...
+
+
+ The exact syntax of the renaming declaration is up for
+ debate (as is whether we need it at all), please send
+ suggestions to libraries@haskell.org.
+
+
+
+
hunk ./doc/libraries.sgml 297
- of each component, and prepending
- Org.. ToDo: I don't like this
- very much, any better ideas?
+ of each component, and prepending Org..
+ ToDo: the Org name isn't great, especially when
+ the domain name also ends with Org (eg. Org.Org.Haskell?).
+ Contrib has also been suggested.
hunk ./doc/libraries.sgml 345
-
+ Apart from the User, Local and Organisation top-level
+ categories, the rest of the hierarchy is organised with a single
+ principle in mind:
+
+
+ Modules are grouped by
+ functionality, since this is the single
+ property that is most helpful for a user of the library - we
+ want users to be able to find out where to obtain
+ functionality easily, and to easily find all the modules that
+ provide relevant functionality.
+
+ So, if two modules provide similar functionality, or
+ alternative interfaces to the same functionality, then they
+ should be children of the same node in the hierarchy. Modules
+ are never grouped by standards compliance, portability,
+ stability, or any other property.
+
hunk ./doc/libraries.sgml 364
-
+
hunk ./doc/libraries.sgml 367
-
+
+
+
+ A module defining a data type or type class
+ X has the itself the name
+ X, e.g.
+ StablePtr.
+
+
+
+ A module which re-exports the modules in a subtree of
+ the hierarchy has the same name as the root of that subtree,
+ eg. Foreign re-exports
+ Foreign.Ptr,
+ Foreign.Marshal.Utils etc.
+
+
+
+ If a subtree of the hierarchy contains several modules
+ which provide similar functionality (eg. there are several
+ pretty-printing libraries under
+ Text.PrettyPrinter), then the module at
+ the root of the subtree generally re-exports just
+ one of the modules in the subtree
+ (possibly the most popular or commonly-used
+ alternative).
+
+
+
+ In Haskell you sometimes publish
+ two interfaces to your libraries; one
+ for users, and one for library writers or advanced users who
+ might want to extend things. Typically the advanced users
+ need to be able to see past certain abstractions.
+
+ The current proposal is for a module named
+ M, the advanced
version
+ would be named M.Internals. eg.
+
+
+import Text.Html -- The library
+import Text.Html.Internals -- The non-abstract library (for building other libs)
+
+
+
+
+ Acronyms are fully capitalised in a module name.
+ eg. HTML, URI,
+ CGI, etc. Exceptions may be made for
+ acronyms which have an existing well-established alternative
+ capitalisation, or acronyms which are also valid words, and
+ are more often used as such.
+
+
+
+ A module name should be made plural only if the module
+ actually defines multiple entities of a particular kind:
+ eg. Foreign.C.Types. Most module names
+ which define a type or class will follow the name of the
+ type or class, so whether to pluralize is not an
+ issue.
+
+
hunk ./doc/libraries.sgml 582
- NHC
+ Nhc
hunk ./doc/libraries.sgml 584
- Libraries specific to the NHC compiler.
+ Libraries specific to the Nhc compiler.
hunk ./doc/libraries.sgml 727
- plus approved extensions (see ),
- and may not use any platform-specific features. It may make
- use of other portable libraries only.
+ plus approved extensions, and may not use any
+ platform-specific features. It may make use of other
+ portable libraries only.
hunk ./doc/libraries.sgml 766
+
+ Approved Extensions
+
+ Very few of the core libraries can be implemented using
+ pure Haskell 98. For this reason, we decided to raise the
+ baseline for portable libraries to include a few common
+ extensions; the following langauge extensions can be
+ assumed to be present when writing
+ libraries:
+
+
+
+ The Foreign
+ Function Interface.
+
+
+ Mutable variables
+ (Data.IORef).
+
+
+ Unsafe IO monad operations
+ (System.IO.Unsafe).
+
+
+ Packed strings
+ (Data.PackedString).
+
+
+
+ Extensions which we'd like to be standard, but aren't
+ currently implemented by one or more of the our target
+ compilers:
+
+
+
+ Bit operations (Data.Bits).
+
+
+ Exceptions (synchronous only), defined by the
+ Control.Exception interface.
+
+
+ The ST monad, defined by
+ Control.Monad.ST, and the associated
+ Data.Array.ST and
+ Data.STRef libraries. ST requires a
+ small typechecker extension for the runST
+ function.
+
+
+ Concurrent Haskell (pre-emptive multitasking
+ optional). Hugs implements this, but Nhc currently does
+ not.
+
+
+
+ The following extensions are not likely to become part of
+ the baseline, but are nevertheless used by one or more libraries
+ in the core set:
+
+
+
+ Multi-parameter type classes.
+
+
+ Local unversal and existential quantification.
+
+
+ Concurrent Haskell with pre-emptive multitasking.
+
+
+ Asynchronous exceptions.
+
+
+ Stable Names.
+
+
+ Weak Pointers.
+
+
+
+ Other extensions are supported by a single compiler only,
+ and can be accessed by libraries under the top level hierarchy
+ for that compiler,
+ eg. GHC.UnboxedTypes.
+
hunk ./doc/libraries.sgml 854
-
+
hunk ./doc/libraries.sgml 925
- Malcolm.Wallace@cs.york.ac.uk (NHC representative)
+ Malcolm.Wallace@cs.york.ac.uk (Nhc representative)
hunk ./doc/libraries.sgml 990
--- $Id: libraries.sgml,v 1.3 2001/07/03 09:21:46 simonmar Exp $
+-- $Id: libraries.sgml,v 1.4 2001/07/05 13:52:49 simonmar Exp $
hunk ./doc/libraries.sgml 1000
- $Id: libraries.sgml,v 1.3 2001/07/03 09:21:46 simonmar Exp $
+ $Id: libraries.sgml,v 1.4 2001/07/05 13:52:49 simonmar Exp $
hunk ./doc/libraries.sgml 1079
-
- Module names
-
-
- A module defining a data type or type class
- X has the itself the name
- X, e.g.
- StablePtr.
-
-
-
- A module which re-exports the modules in a subtree
- of the hierarchy has the same name as the root of that
- subtree, eg. Foreign re-exports
- Foreign.Ptr,
- Foreign.Marshal.Utils etc.
-
-
-
- If a subtree of the hierarchy contains several
- modules which provide similar functionality (eg. there are
- several pretty-printing libraries under
- Text.PrettyPrinter), then the module at
- the root of the subtree generally re-exports just
- one of the modules in the subtree
- (possibly the most popular or commonly-used
- alternative).
-
-
-
- In Haskell you sometimes publish
- two interfaces to your libraries; one
- for users, and one for library writers or advanced users
- who might want to extend things. Typically the advanced
- users need to be able to see past certain
- abstractions.
-
- The current proposal is for a module named
- M, the advanced
version
- would be named M.Internals. eg.
-
-
-import Text.Html -- The library
-import Text.Html.Internals -- The non-abstract library (for building other libs)
-
-
-
-
- Acronyms are fully capitalised in a module name.
- eg. HTML, URI,
- CGI, etc. Exceptions may be made for
- acronyms which have an existing well-established
- alternative capitalisation, or acronyms which are also
- valid words, and are more often used as such.
-
-
-
- A module name should be made plural only if the
- module actually defines multiple entities of a particular
- kind: eg. Foreign.C.Types. Most module
- names which define a type or class will follow the name of
- the type or class, so whether to pluralize is not an
- issue.
-
-
-
-
-
hunk ./doc/libraries.sgml 1394
- Numeric -> ????
- not placed in hierarchy yet
+ Numeric -> Numeric
+ added showHex, showOct, showBin & showIntAtBase from NumExts,
+ but left out floatToDouble & doubleToFloat (realToFrac is more general).
hunk ./doc/libraries.sgml 1417
-
-
}