[project @ 1997-11-24 20:31:09 by reid]
authorreid <unknown>
Mon, 24 Nov 1997 20:31:09 +0000 (20:31 +0000)
committerreid <unknown>
Mon, 24 Nov 1997 20:31:09 +0000 (20:31 +0000)
Added IOExts.unsafePtrEq :: a -> a -> Bool

ghc/docs/libraries/libs.sgml

index f791cae..7ce5045 100644 (file)
-<!doctype linuxdoc system>\r
-\r
-<!-- ToDo:\r
-  o Add indexing support (to linuxdoc)\r
-  o Fix citations in html\r
-  -->\r
-\r
-<article>\r
-\r
-<title>The Hugs-GHC Extension Libraries\r
-<author>Alastair Reid <tt/reid-alastair@cs.yale.edu/\r
-<date>v0.6, 17 November 1997\r
-<abstract>\r
-Hugs and GHC provide a common set of libraries to aid portability.\r
-This document specifies the interfaces to these libraries and documents\r
-known differences.  We hope that these modules will be adopted for inclusion\r
-as Standard Haskell Libraries sometime soon.\r
-</abstract>\r
-\r
-<!--  Commented out the table of contents - ADR\r
-<toc>\r
--->\r
-\r
-<sect> <idx/LazyST/ <p>\r
-\r
-This library provides support for both <em/lazy/ and <em/strict/ state\r
-threads, as described in the PLDI '94 paper by John Launchbury and\r
-Simon Peyton Jones <cite id="LazyStateThreads">.  In addition to the\r
-monad <tt/ST/, it also provides mutable variables <tt/STRef/ and\r
-mutable arrays <tt/STArray/.  As the name suggests, the monad <tt/ST/\r
-instance is <em/lazy/.\r
-\r
-<tscreen><verb>\r
-module LazyST( module LazyST, module Monad ) where\r
-import Monad\r
-\r
-data ST s a        -- abstract type\r
-runST              :: forall a. (forall s. ST s a) -> a\r
-returnST           :: a -> ST s a\r
-thenLazyST         :: ST s a -> (a -> ST s b) -> ST s b\r
-thenStrictST       :: ST s a -> (a -> ST s b) -> ST s b\r
-fixST              :: (a -> ST s a) -> ST s a\r
-unsafeInterleaveST :: ST s a -> ST s a\r
-instance Functor (ST s)\r
-instance Monad   (ST s)\r
-\r
-data STRef s a     -- mutable variables in state thread s\r
-                   -- containing values of type a.\r
-newSTRef           :: a -> ST s (STRef s a)\r
-readSTRef          :: STRef s a -> ST s a\r
-writeSTRef         :: STRef s a -> a -> ST s ()\r
-instance Eq (STRef s a)\r
-\r
-data STArray s ix elt -- mutable arrays in state thread s\r
-                      -- indexed by values of type ix\r
-                      -- containing values of type a.\r
-newSTArray          :: Ix ix => (ix,ix) -> elt -> ST s (STArray s ix elt)\r
-boundsSTArray       :: Ix ix => STArray s ix elt -> (ix, ix)\r
-readSTArray         :: Ix ix => STArray s ix elt -> ix -> ST s elt\r
-writeSTArray        :: Ix ix => STArray s ix elt -> ix -> elt -> ST s ()\r
-thawSTArray         :: Ix ix => Array ix elt -> ST s (STArray s ix elt)\r
-freezeSTArray       :: Ix ix => STArray s ix elt -> ST s (Array ix elt)\r
-unsafeFreezeSTArray :: Ix ix => STArray s ix elt -> ST s (Array ix elt)  \r
-instance Eq (STArray s ix elt)\r
-</verb></tscreen>\r
-\r
-Notes:\r
-<itemize>\r
-\r
-<item> \r
-GHC also supports ByteArrays --- these aren't supported by Hugs yet.\r
-\r
-<item> \r
-The operations <tt/freezeSTArray/ and <tt/thawSTArray/ convert mutable\r
-arrays to and from immutable arrays.  Semantically, they are identical\r
-to copying the array and they are usually implemented that way.  The\r
-operation <tt/unsafeFreezeSTArray/ is a faster version of\r
-<tt/freezeSTArray/ which omits the copying step.  It's a safe substitute for\r
-<tt/freezeSTArray/ if you don't modify the mutable array after freezing it.\r
-\r
-<item>\r
-In the current version of Hugs, the <tt/<idx/runST// operation,\r
-used to specify encapsulation, is implemented as a language construct,\r
-and <tt/runST/ is treated as a keyword.  We plan to change this to match\r
-GHC soon.\r
-\r
-<!-- \r
-  <item>\r
-     Note that it is possible to install Hugs 1.4 without support for lazy\r
-     state threads, and hence the primitives described here may not be\r
-     available in all implementations.  Also, in contrast with the\r
-     implementation of lazy state threads in previous releases of Hugs and\r
-     Gofer, there is no direct relationship between the\r
-     <tt/<idx/ST monad// and the <tt/<idx/IO monad//.\r
-  -->\r
-\r
-<item>\r
-The only difference between the lazy and strict instances of the\r
-<tt/ST/ monad is in their bind operators.  The monadic bind operators\r
-<tt/thenLazyST/ and <tt/thenStrictST/ are provided so that you can\r
-import <tt/LazyST/ (say) and still use the strict instance in those\r
-places where it matters.  GHC also allows you to write <tt/LazyST.>>=/\r
-and <tt/ST.>>=/ but this is not supported by Hugs yet.\r
-\r
-\r
-</itemize>\r
-\r
-<sect> <idx/ST/ <p>\r
-\r
-This library is identical to <tt/LazyST/ except that the <tt/ST/ monad\r
-instance is <em/strict/.  Most programmers use the <em/strict/ instance\r
-to avoid the space leaks associated with the <em/lazy/ instance.\r
-\r
-<sect> <idx/IOExts/ <p>\r
-\r
-This library provides the following extensions to the IO monad:\r
-<itemize>\r
-<item>\r
-The operations <tt/fixIO/, <tt/unsafePerformIO/ and <tt/unsafeInterleaveIO/\r
-described in <cite id="ImperativeFP">\r
-\r
-<item>\r
-References (aka mutable variables) and mutable arrays (but no form of \r
-mutable byte arrays)\r
-\r
-<item>\r
-<tt/performGC/ triggers an immediate garbage collection\r
-\r
-<item>\r
-When called, <tt/trace/ prints the string in its first argument, and then\r
-returns the second argument as its result.  The <tt/trace/ function is not\r
-referentially transparent, and should only be used for debugging, or for\r
-monitoring execution. \r
-\r
-<!--\r
-  You should also be warned that, unless you understand some of the\r
-  details about the way that Haskell programs are executed, results\r
-  obtained using <tt/trace/ can be rather confusing.  For example, the\r
-  messages may not appear in the order that you expect.  Even ignoring the\r
-  output that they produce, adding calls to <tt/trace/ can change the\r
-  semantics of your program.  Consider this a warning!\r
-  -->\r
-\r
-</itemize>\r
-\r
-<tscreen><verb>\r
-module IOExts where\r
-\r
-fixIO               :: (a -> IO a) -> IO a\r
-unsafePerformIO     :: IO a -> a\r
-unsafeInterleaveIO  :: IO a -> IO a\r
-                   \r
-data IORef a        -- mutable variables containing values of type a\r
-newIORef           :: a -> IO (IORef a)\r
-readIORef          :: IORef a -> IO a\r
-writeIORef         :: IORef a -> a -> IO ()\r
-instance Eq (IORef a)\r
-\r
-data IOArray ix elt -- mutable arrays indexed by values of type ix\r
-                    -- containing values of type a.\r
-newIOArray          :: Ix ix => (ix,ix) -> elt -> IO (IOArray ix elt)\r
-boundsIOArray       :: Ix ix => IOArray ix elt -> (ix, ix)\r
-readIOArray         :: Ix ix => IOArray ix elt -> ix -> IO elt\r
-writeIOArray        :: Ix ix => IOArray ix elt -> ix -> elt -> IO ()\r
-freezeIOArray       :: Ix ix => IOArray ix elt -> IO (Array ix elt)\r
-instance Eq (IOArray ix elt)\r
-\r
-trace               :: String -> a -> a\r
-performGC           :: IO ()\r
-</verb></tscreen>\r
-\r
-<!--\r
-  <sect> <idx/GlaExts/ <p>\r
-  \r
-  This library provides a convenient bundle of most of the extensions\r
-  available in GHC and Hugs.  This module is generally more stable than\r
-  the other modules of non-standard extensions so you might choose to \r
-  import them from here rather than going straight to the horses mouth.\r
-  \r
-  <tscreen><verb>\r
-  module GlaExts( module GlaExts, module IOExts, module ST, module Addr ) where\r
-  import IOExts\r
-  import ST\r
-  import Addr\r
-  trace              :: String -> a -> a\r
-  performGC          :: IO ()\r
-  </verb></tscreen>\r
-  \r
-  The GHC version also provides the types <tt/PrimIO/, <tt/RealWorld/,\r
-  <tt/ByteArray/, <tt/Lift/ and operations on these types. It also\r
-  provides the unboxed views of the types\r
-  <tt/Int/, \r
-  <tt/Addr/, \r
-  <tt/Word/, \r
-  <tt/Float/, \r
-  <tt/Double/, \r
-  <tt/Integer/ and\r
-  <tt/Char/ \r
-  and a number of ``primitive operations'' (<tt/+&num/,\r
-  <tt/plusFloat&num/, etc.).\r
-  \r
-  -->\r
-\r
-<sect> <idx/Bits/ <p>\r
-\r
-This library defines bitwise operations for signed and unsigned ints.\r
-\r
-<tscreen><verb>\r
-module Bits where\r
-infixl 8 `shift`, `rotate`\r
-infixl 7 .&.\r
-infixl 6 `xor`\r
-infixl 5 .|.\r
-\r
-class Bits a where\r
-  (.&.), (.|.), xor :: a -> a -> a\r
-  complement        :: a -> a\r
-  shift             :: a -> Int -> a\r
-  rotate            :: a -> Int -> a\r
-  bit               :: Int -> a        \r
-  setBit            :: a -> Int -> a   \r
-  clearBit          :: a -> Int -> a   \r
-  complementBit     :: a -> Int -> a   \r
-  testBit           :: a -> Int -> Bool\r
-  bitSize           :: a -> Int\r
-  isSigned          :: a -> Bool\r
-\r
-shiftL, shiftR   :: Bits a => a -> Int -> a\r
-rotateL, rotateR :: Bits a => a -> Int -> a\r
-shiftL  a i = shift  a i\r
-shiftR  a i = shift  a (-i)\r
-rotateL a i = rotate a i\r
-rotateR a i = rotate a (-i)\r
-</verb></tscreen>\r
-\r
-Notes:\r
-<itemize>\r
-<item>\r
-  <tt/bitSize/ and <tt/isSigned/ are like <tt/floatRadix/ and <tt/floatDigits/\r
-  -- they return parameters of the <em/type/ of their argument rather than \r
-  of the particular argument they are applied to.  <tt/bitSize/ returns\r
-  the number of bits in the type (or <tt/Nothing/ for unbounded types); and\r
-  <tt/isSigned/ returns whether the type is signed or not.  \r
-<item>\r
-  <tt/shift/ performs sign extension.  \r
-  That is, right shifts fill the top bits with 1 if the  number is negative\r
-  and with 0 otherwise.\r
-  (Since unsigned types are always positive, the top bit is always filled with\r
-  0.)\r
-<item> \r
-  Bits are numbered from 0 with bit 0 being the least significant bit.\r
-<item>\r
-  <tt/shift x i/ and <tt/rotate x i/ shift to the left if <tt/i/ is\r
-  positive and to the right otherwise.  \r
-<!--\r
-  <item>\r
-    <tt/rotate/ is well defined only if bitSize returns a number.\r
-    (Maybe we should impose a Bounded constraint on it?)\r
-  -->\r
-<item>\r
-  <tt/bit i/ is the value with the i'th bit set.\r
-</itemize>\r
-\r
-<sect> <idx/Word/ <p>\r
-\r
-This library provides unsigned integers of various sizes.\r
-The types supported are as follows:\r
-\r
-<tabular ca="|l|l|">\r
-type    | number of bits @ \r
-<hline> \r
-Word8    | 8  @\r
-Word16   | 16 @\r
-Word32   | 32 @\r
-Word64   | 64 @\r
-<hline> \r
-</tabular>\r
-\r
-For each type <it/W/ above, we provide the following functions and\r
-instances.  The type <it/I/ refers to the signed integer type of the\r
-same size.\r
-\r
-<tscreen><verb>\r
-data W            -- Unsigned Ints\r
-instance Eq       W\r
-instance Ord      W\r
-instance Show     W\r
-instance Read     W\r
-instance Bounded  W\r
-instance Num      W\r
-instance Real     W\r
-instance Integral W\r
-instance Enum     W\r
-instance Ix       W\r
-instance Bits     W\r
-</verb></tscreen>\r
-Plus\r
-<tscreen><verb>\r
-word8ToWord32  :: Word8  -> Word32\r
-word32ToWord8  :: Word32 -> Word8\r
-word16ToWord32 :: Word16 -> Word32\r
-word32ToWord16 :: Word32 -> Word16\r
-\r
-word8ToInt     :: Word8  -> Int\r
-intToWord8     :: Int    -> Word8\r
-word16ToInt    :: Word16 -> Int\r
-intToWord16    :: Int    -> Word16\r
-word32ToInt    :: Word32 -> Int\r
-intToWord32    :: Int    -> Word32\r
-</verb></tscreen>\r
-\r
-Notes: \r
-<itemize>\r
-<item>\r
-  All arithmetic is performed modulo 2^n\r
-\r
-  One non-obvious consequequence of this is that <tt/negate/\r
-  should <em/not/ raise an error on negative arguments.\r
-\r
-<item>\r
-The coercion <tt/wToI/ converts an unsigned n-bit value to the\r
-signed n-bit value with the same representation.  For example,\r
-<tt/word8ToInt8 0xff = -1/. \r
-Likewise, <tt/iToW/ converts signed n-bit values to the\r
-corresponding unsigned n-bit value.\r
-\r
-<item>\r
-ToDo: complete the set of coercion functions.\r
-\r
-<item>\r
-Use <tt/Prelude.fromIntegral :: (Integral a, Num b) => a -> b/ to\r
-coerce between different sizes or to preserve sign when converting\r
-between values of the same size.\r
-\r
-<item>\r
-It would be very natural to add a type a type <tt/Natural/ providing\r
-an unbounded size unsigned integer --- just as <tt/Integer/ provides\r
-unbounded size signed integers.  We do not do that yet since there is\r
-no demand for it.  Doing so would require <tt/Bits.bitSize/ to return\r
-<tt/Maybe Int/.\r
-\r
-<item>\r
-The <tt/Enum/ instances stop when they reach their upper or lower\r
-bound --- they don't overflow the way the <tt/Int/ and <tt/Float/\r
-instances do.\r
-\r
-<item>\r
-It would be useful to provide a function (or a family of functions?)\r
-which coerced between any two Word types (without going through\r
-Integer).\r
-\r
-</itemize>\r
-\r
-Hugs only provides <tt/Eq/, <tt/Ord/, <tt/Read/ and <tt/Show/\r
-instances for <tt/Word64/ at the moment.\r
-\r
-<sect> <idx/Int/ <p>\r
-\r
-This library provides signed integers of various sizes.  The types\r
-supported are as follows:\r
-\r
-<tabular ca="|l|l|l|">\r
-type    | number of bits @ \r
-<hline> \r
-Int8    | 8  @\r
-Int16   | 16 @\r
-Int32   | 32 @\r
-Int64   | 64 @\r
-<hline> \r
-</tabular>\r
-\r
-For each type <it/I/ above, we provide the following instances.\r
-\r
-<tscreen><verb>\r
-data I            -- Signed Ints\r
-iToInt            :: I -> Int  -- not provided for Int64\r
-intToi            :: Int -> I  -- not provided for Int64\r
-instance Eq       I\r
-instance Ord      I\r
-instance Show     I\r
-instance Read     I\r
-instance Bounded  I\r
-instance Num      I\r
-instance Real     I\r
-instance Integral I\r
-instance Enum     I\r
-instance Ix       I\r
-instance Bits     I\r
-</verb></tscreen>\r
-Plus\r
-<tscreen><verb>\r
-int8ToInt  :: Int8  -> Int\r
-intToInt8  :: Int   -> Int8\r
-int16ToInt :: Int16 -> Int\r
-intToInt16 :: Int   -> Int16\r
-int32ToInt :: Int32 -> Int\r
-intToInt32 :: Int   -> Int32\r
-</verb></tscreen>\r
-\r
-<itemize>\r
-<item>\r
-Hugs does not provide <tt/Int64/ at the moment.\r
-\r
-<item>\r
-ToDo: complete the set of coercion functions.\r
-\r
-</itemize>\r
-\r
-<sect> <idx/Addr/ <p>\r
-\r
-This library provides machine addresses and is primarily intended for \r
-use in creating foreign function interfaces using GreenCard.\r
-\r
-<tscreen><verb>\r
-module Addr where\r
-data Addr  -- Address type\r
-instance Eq Addr\r
-\r
-nullAddr           :: Addr\r
-plusAddr           :: Addr -> Int -> Addr\r
-\r
--- read value out of _immutable_ memory\r
-indexCharOffAddr   :: Addr -> Int -> Char\r
-indexIntOffAddr    :: Addr -> Int -> Int     -- should we drop this?\r
-indexAddrOffAddr   :: Addr -> Int -> Addr\r
-indexFloatOffAddr  :: Addr -> Int -> Float\r
-indexDoubleOffAddr :: Addr -> Int -> Double\r
-indexWord8OffAddr  :: Addr -> Int -> Word8\r
-indexWord16OffAddr :: Addr -> Int -> Word16\r
-indexWord32OffAddr :: Addr -> Int -> Word32\r
-indexWord64OffAddr :: Addr -> Int -> Word64\r
-indexInt8OffAddr   :: Addr -> Int -> Int8\r
-indexInt16OffAddr  :: Addr -> Int -> Int16\r
-indexInt32OffAddr  :: Addr -> Int -> Int32\r
-indexInt64OffAddr  :: Addr -> Int -> Int64\r
-\r
--- read value out of mutable memory\r
-readCharOffAddr    :: Addr -> Int -> IO Char\r
-readIntOffAddr     :: Addr -> Int -> IO Int  -- should we drop this?\r
-readAddrOffAddr    :: Addr -> Int -> IO Addr\r
-readFloatOffAddr   :: Addr -> Int -> IO Float\r
-readDoubleOffAddr  :: Addr -> Int -> IO Double\r
-readWord8OffAddr   :: Addr -> Int -> IO Word8\r
-readWord16OffAddr  :: Addr -> Int -> IO Word16\r
-readWord32OffAddr  :: Addr -> Int -> IO Word32\r
-readWord64OffAddr  :: Addr -> Int -> IO Word64\r
-readInt8OffAddr    :: Addr -> Int -> IO Int8\r
-readInt16OffAddr   :: Addr -> Int -> IO Int16\r
-readInt32OffAddr   :: Addr -> Int -> IO Int32\r
-readInt64OffAddr   :: Addr -> Int -> IO Int64\r
-\r
--- write value into mutable memory\r
-writeCharOffAddr   :: Addr -> Int -> Char   -> IO ()\r
-writeIntOffAddr    :: Addr -> Int -> Int    -> IO ()  -- should we drop this?\r
-writeAddrOffAddr   :: Addr -> Int -> Addr   -> IO ()\r
-writeFloatOffAddr  :: Addr -> Int -> Float  -> IO ()\r
-writeDoubleOffAddr :: Addr -> Int -> Double -> IO ()\r
-writeWord8OffAddr  :: Addr -> Int -> Word8  -> IO ()\r
-writeWord16OffAddr :: Addr -> Int -> Word16 -> IO ()\r
-writeWord32OffAddr :: Addr -> Int -> Word32 -> IO ()\r
-writeWord64OffAddr :: Addr -> Int -> Word64 -> IO ()\r
-writeInt8OffAddr   :: Addr -> Int -> Int8   -> IO ()\r
-writeInt16OffAddr  :: Addr -> Int -> Int16  -> IO ()\r
-writeInt32OffAddr  :: Addr -> Int -> Int32  -> IO ()\r
-writeInt64OffAddr  :: Addr -> Int -> Int64  -> IO ()\r
-</verb></tscreen>\r
-\r
-Hugs provides <tt/Addr/ and <tt/nullAddr/ but does not provide any of\r
-the index, read or write functions.  They can be implemented using \r
-GreenCard if required.\r
-\r
-<sect> <idx/ForeignObj/ <p>\r
-\r
-This module is provided by GHC but not by Hugs.\r
-GreenCard for Hugs provides the <tt/ForeignObj/ type.\r
-\r
-<sect> <idx/Concurrent/ <p>\r
-\r
-This library provides the Concurrent Haskell extensions\r
-<cite id="concurrentHaskell:popl96">.\r
-\r
-We are grateful to the Glasgow Haskell Project for allowing us to\r
-redistribute their implementation of this module.\r
-\r
-<tscreen><verb>\r
-module Concurrent where\r
-\r
-data ThreadId    -- thread identifiers\r
-instance Eq ThreadId\r
-\r
-forkIO           :: IO () -> IO ThreadId\r
-killThread       :: ThreadId -> IO ()\r
-\r
-data MVar a      -- Synchronisation variables\r
-newEmptyMVar     :: IO (MVar a)\r
-newMVar          :: a -> IO (MVar a)\r
-takeMVar         :: MVar a -> IO a\r
-putMVar          :: MVar a -> a -> IO ()\r
-swapMVar         :: MVar a -> a -> IO a\r
-readMVar         :: MVar a -> IO a \r
-instance Eq (MVar a)\r
-\r
-data Chan a      -- channels\r
-newChan          :: IO (Chan a)\r
-writeChan        :: Chan a -> a -> IO ()\r
-readChan         :: Chan a -> IO a\r
-dupChan          :: Chan a -> IO (Chan a)\r
-unReadChan       :: Chan a -> a -> IO ()\r
-readChanContents :: Chan a -> IO [a]\r
-writeList2Chan   :: Chan a -> [a] -> IO ()\r
-                      \r
-data CVar a       -- one element channels\r
-newCVar          :: IO (CVar a)\r
-putCVar          :: CVar a -> a -> IO ()\r
-getCVar          :: CVar a -> IO a\r
-                      \r
-data QSem        -- General/quantity semaphores\r
-newQSem          :: Int  -> IO QSem\r
-waitQSem         :: QSem -> IO ()\r
-signalQSem       :: QSem -> IO ()\r
-                      \r
-data QSemN       -- General/quantity semaphores\r
-newQSemN         :: Int   -> IO QSemN\r
-waitQSemN        :: QSemN -> Int -> IO ()\r
-signalQSemN      :: QSemN -> Int -> IO ()\r
-\r
-type SampleVar a -- Sample variables \r
-newEmptySampleVar:: IO (SampleVar a)\r
-newSampleVar     :: a -> IO (SampleVar a)\r
-emptySampleVar   :: SampleVar a -> IO ()\r
-readSampleVar    :: SampleVar a -> IO a\r
-writeSampleVar   :: SampleVar a -> a -> IO ()\r
-</verb></tscreen>\r
-\r
-Notes:\r
-<itemize>\r
-\r
-<item> \r
-  GHC uses preemptive multitasking:\r
-  Context switches can occur at any time, except if you call a C\r
-  function (like \verb"getchar") that blocks waiting for input.\r
-\r
-  Hugs uses cooperative multitasking:\r
-  Context switches only occur when you use one of the primitives\r
-  defined in this module.  This means that programs such as:\r
-\r
-<tscreen><verb>\r
-main = forkIO (write 'a') >> write 'b'\r
- where write c = putChar c >> write c\r
-</verb></tscreen>\r
-\r
-  will print either <tt/aaaaaaaaaaaaaa.../ or <tt/bbbbbbbbbbbb.../,\r
-  instead of some random interleaving of <tt/a/s and <tt/b/s.\r
-\r
-  In practice, cooperative multitasking is sufficient for writing \r
-  simple graphical user interfaces.\r
-\r
-<item>\r
-Hugs does not provide the functions <tt/mergeIO/ or <tt/nmergeIO/ since these\r
-require preemptive multitasking.\r
-\r
-<item>\r
-<tt/killThread/ has not been implemented yet on either system.\r
-The plan is that <tt/killThread/ will raise an IO exception in the\r
-killed thread which it can catch --- perhaps allowing it to kill its\r
-children before exiting.\r
-\r
-<item>\r
-The <tt/Ord/ instance for <tt/ThreadId/s provides an arbitrary total ordering\r
-which might be used to build an ordered binary tree, say.  \r
-\r
-</itemize>\r
-\r
-<sect> <idx/Pretty/ <p>\r
-\r
-This library contains Simon Peyton Jones' implementation of John\r
-Hughes's pretty printer combinators.\r
-\r
-<tscreen><verb>\r
-module Pretty where\r
-infixl 6 <> \r
-infixl 6 <+>\r
-infixl 5 $$, $+$\r
-data Doc  -- the Document datatype\r
-\r
--- The primitive Doc values\r
-empty                     :: Doc\r
-text                      :: String   -> Doc \r
-char                      :: Char     -> Doc\r
-int                       :: Int      -> Doc\r
-integer                   :: Integer  -> Doc\r
-float                     :: Float    -> Doc\r
-double                    :: Double   -> Doc\r
-rational                  :: Rational -> Doc\r
-semi, comma, colon, space, equals              :: Doc\r
-lparen, rparen, lbrack, rbrack, lbrace, rbrace :: Doc\r
-parens, brackets, braces  :: Doc -> Doc \r
-quotes, doubleQuotes      :: Doc -> Doc\r
-\r
--- Combining Doc values\r
-(<>)   :: Doc -> Doc -> Doc     -- Beside\r
-hcat   :: [Doc] -> Doc          -- List version of <>\r
-(<+>)  :: Doc -> Doc -> Doc     -- Beside, separated by space\r
-hsep   :: [Doc] -> Doc          -- List version of <+>\r
-($$)   :: Doc -> Doc -> Doc     -- Above; if there is no\r
-                                  -- overlap it "dovetails" the two\r
-vcat   :: [Doc] -> Doc          -- List version of $$\r
-cat    :: [Doc] -> Doc          -- Either hcat or vcat\r
-sep    :: [Doc] -> Doc          -- Either hsep or vcat\r
-fcat   :: [Doc] -> Doc          -- ``Paragraph fill'' version of cat\r
-fsep   :: [Doc] -> Doc          -- ``Paragraph fill'' version of sep\r
-nest   :: Int -> Doc -> Doc     -- Nested\r
-hang   :: Doc -> Int -> Doc -> Doc\r
-punctuate :: Doc -> [Doc] -> [Doc]      \r
--- punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]\r
-\r
--- Displaying Doc values\r
-instance Show Doc\r
-render     :: Doc -> String             -- Uses default style\r
-renderStyle  :: Style -> Doc -> String\r
-data Style = Style { lineLength     :: Int,   -- In chars\r
-                       ribbonsPerLine :: Float, -- Ratio of ribbon length\r
-                                                -- to line length\r
-                       mode :: Mode\r
-               }\r
-data Mode = PageMode            -- Normal \r
-            | ZigZagMode          -- With zig-zag cuts\r
-            | LeftMode            -- No indentation, infinitely long lines\r
-            | OneLineMode         -- All on one line\r
-</verb></tscreen>\r
-\r
-<biblio files="refs" style="abbrv">\r
-\r
-\r
-</article>\r
-\r
+<!doctype linuxdoc system>
+
+<!-- ToDo:
+  o Add indexing support (to linuxdoc)
+  o Fix citations in html
+  -->
+
+<article>
+
+<title>The Hugs-GHC Extension Libraries
+<author>Alastair Reid <tt/reid-alastair@cs.yale.edu/
+<date>v0.7, 21 November 1997
+<abstract>
+Hugs and GHC provide a common set of libraries to aid portability.
+This document specifies the interfaces to these libraries and documents
+known differences.  We hope that these modules will be adopted for inclusion
+as Standard Haskell Libraries sometime soon.
+</abstract>
+
+<!--  Commented out the table of contents - ADR
+<toc>
+-->
+
+<sect> <idx/LazyST/ <p>
+
+This library provides support for both <em/lazy/ and <em/strict/ state
+threads, as described in the PLDI '94 paper by John Launchbury and
+Simon Peyton Jones <cite id="LazyStateThreads">.  In addition to the
+monad <tt/ST/, it also provides mutable variables <tt/STRef/ and
+mutable arrays <tt/STArray/.  As the name suggests, the monad <tt/ST/
+instance is <em/lazy/.
+
+<tscreen><verb>
+module LazyST( module LazyST, module Monad ) where
+import Monad
+
+data ST s a        -- abstract type
+runST              :: forall a. (forall s. ST s a) -> a
+returnST           :: a -> ST s a
+thenLazyST         :: ST s a -> (a -> ST s b) -> ST s b
+thenStrictST       :: ST s a -> (a -> ST s b) -> ST s b
+fixST              :: (a -> ST s a) -> ST s a
+unsafeInterleaveST :: ST s a -> ST s a
+instance Functor (ST s)
+instance Monad   (ST s)
+
+data STRef s a     -- mutable variables in state thread s
+                   -- containing values of type a.
+newSTRef           :: a -> ST s (STRef s a)
+readSTRef          :: STRef s a -> ST s a
+writeSTRef         :: STRef s a -> a -> ST s ()
+instance Eq (STRef s a)
+
+data STArray s ix elt -- mutable arrays in state thread s
+                      -- indexed by values of type ix
+                      -- containing values of type a.
+newSTArray          :: Ix ix => (ix,ix) -> elt -> ST s (STArray s ix elt)
+boundsSTArray       :: Ix ix => STArray s ix elt -> (ix, ix)
+readSTArray         :: Ix ix => STArray s ix elt -> ix -> ST s elt
+writeSTArray        :: Ix ix => STArray s ix elt -> ix -> elt -> ST s ()
+thawSTArray         :: Ix ix => Array ix elt -> ST s (STArray s ix elt)
+freezeSTArray       :: Ix ix => STArray s ix elt -> ST s (Array ix elt)
+unsafeFreezeSTArray :: Ix ix => STArray s ix elt -> ST s (Array ix elt)  
+instance Eq (STArray s ix elt)
+</verb></tscreen>
+
+Notes:
+<itemize>
+
+<item> 
+GHC also supports ByteArrays --- these aren't supported by Hugs yet.
+
+<item> 
+The operations <tt/freezeSTArray/ and <tt/thawSTArray/ convert mutable
+arrays to and from immutable arrays.  Semantically, they are identical
+to copying the array and they are usually implemented that way.  The
+operation <tt/unsafeFreezeSTArray/ is a faster version of
+<tt/freezeSTArray/ which omits the copying step.  It's a safe substitute for
+<tt/freezeSTArray/ if you don't modify the mutable array after freezing it.
+
+<item>
+In the current version of Hugs, the <tt/<idx/runST// operation,
+used to specify encapsulation, is implemented as a language construct,
+and <tt/runST/ is treated as a keyword.  We plan to change this to match
+GHC soon.
+
+<!-- 
+  <item>
+     Note that it is possible to install Hugs 1.4 without support for lazy
+     state threads, and hence the primitives described here may not be
+     available in all implementations.  Also, in contrast with the
+     implementation of lazy state threads in previous releases of Hugs and
+     Gofer, there is no direct relationship between the
+     <tt/<idx/ST monad// and the <tt/<idx/IO monad//.
+  -->
+
+<item>
+The only difference between the lazy and strict instances of the
+<tt/ST/ monad is in their bind operators.  The monadic bind operators
+<tt/thenLazyST/ and <tt/thenStrictST/ are provided so that you can
+import <tt/LazyST/ (say) and still use the strict instance in those
+places where it matters.  GHC also allows you to write <tt/LazyST.>>=/
+and <tt/ST.>>=/ but this is not supported by Hugs yet.
+
+
+</itemize>
+
+<sect> <idx/ST/ <p>
+
+This library is identical to <tt/LazyST/ except that the <tt/ST/ monad
+instance is <em/strict/.  Most programmers use the <em/strict/ instance
+to avoid the space leaks associated with the <em/lazy/ instance.
+
+<sect> <idx/IOExts/ <p>
+
+This library provides the following extensions to the IO monad:
+<itemize>
+<item>
+The operations <tt/fixIO/, <tt/unsafePerformIO/ and <tt/unsafeInterleaveIO/
+described in <cite id="ImperativeFP">
+
+<item>
+References (aka mutable variables) and mutable arrays (but no form of 
+mutable byte arrays)
+
+<item>
+<tt/performGC/ triggers an immediate garbage collection
+
+<item>
+When called, <tt/trace/ prints the string in its first argument, and then
+returns the second argument as its result.  The <tt/trace/ function is not
+referentially transparent, and should only be used for debugging, or for
+monitoring execution. 
+
+<!--
+  You should also be warned that, unless you understand some of the
+  details about the way that Haskell programs are executed, results
+  obtained using <tt/trace/ can be rather confusing.  For example, the
+  messages may not appear in the order that you expect.  Even ignoring the
+  output that they produce, adding calls to <tt/trace/ can change the
+  semantics of your program.  Consider this a warning!
+  -->
+
+<item>
+<tt/unsafePtrEq/ compares two values for pointer equality without
+evaluating them.  The results are not referentially transparent and
+may vary significantly from one compiler to another or in the face of
+semantics-preserving program changes.  However, pointer equality is useful
+in creating a number of referentially transparent constructs such as this
+simplified memoisation function:
+
+<tscreen><verb>
+> cache :: (a -> b) -> (a -> b)
+> cache f = \x -> unsafePerformIO (check x)
+>  where
+>   ref = unsafePerformIO (newIORef (error "cache", error "cache"))
+>   check x = readIORef ref >>= \ (x',a) ->
+>             if x `unsafePtrEq` x' then
+>               return a
+>             else
+>               let a = f x in
+>               writeIORef ref (x, a) >>
+>               return a
+</verb></tscreen>
+
+
+</itemize>
+
+<tscreen><verb>
+module IOExts where
+
+fixIO               :: (a -> IO a) -> IO a
+unsafePerformIO     :: IO a -> a
+unsafeInterleaveIO  :: IO a -> IO a
+                   
+data IORef a        -- mutable variables containing values of type a
+newIORef           :: a -> IO (IORef a)
+readIORef          :: IORef a -> IO a
+writeIORef         :: IORef a -> a -> IO ()
+instance Eq (IORef a)
+
+data IOArray ix elt -- mutable arrays indexed by values of type ix
+                    -- containing values of type a.
+newIOArray          :: Ix ix => (ix,ix) -> elt -> IO (IOArray ix elt)
+boundsIOArray       :: Ix ix => IOArray ix elt -> (ix, ix)
+readIOArray         :: Ix ix => IOArray ix elt -> ix -> IO elt
+writeIOArray        :: Ix ix => IOArray ix elt -> ix -> elt -> IO ()
+freezeIOArray       :: Ix ix => IOArray ix elt -> IO (Array ix elt)
+instance Eq (IOArray ix elt)
+
+performGC           :: IO ()
+trace               :: String -> a -> a
+unsafePtrEq         :: a -> a -> Bool
+</verb></tscreen>
+
+<!--
+  <sect> <idx/GlaExts/ <p>
+  
+  This library provides a convenient bundle of most of the extensions
+  available in GHC and Hugs.  This module is generally more stable than
+  the other modules of non-standard extensions so you might choose to 
+  import them from here rather than going straight to the horses mouth.
+  
+  <tscreen><verb>
+  module GlaExts( module GlaExts, module IOExts, module ST, module Addr ) where
+  import IOExts
+  import ST
+  import Addr
+  trace              :: String -> a -> a
+  performGC          :: IO ()
+  </verb></tscreen>
+  
+  The GHC version also provides the types <tt/PrimIO/, <tt/RealWorld/,
+  <tt/ByteArray/, <tt/Lift/ and operations on these types. It also
+  provides the unboxed views of the types
+  <tt/Int/, 
+  <tt/Addr/, 
+  <tt/Word/, 
+  <tt/Float/, 
+  <tt/Double/, 
+  <tt/Integer/ and
+  <tt/Char/ 
+  and a number of ``primitive operations'' (<tt/+&num/,
+  <tt/plusFloat&num/, etc.).
+  
+  -->
+
+<sect> <idx/Bits/ <p>
+
+This library defines bitwise operations for signed and unsigned ints.
+
+<tscreen><verb>
+module Bits where
+infixl 8 `shift`, `rotate`
+infixl 7 .&.
+infixl 6 `xor`
+infixl 5 .|.
+
+class Bits a where
+  (.&.), (.|.), xor :: a -> a -> a
+  complement        :: a -> a
+  shift             :: a -> Int -> a
+  rotate            :: a -> Int -> a
+  bit               :: Int -> a        
+  setBit            :: a -> Int -> a   
+  clearBit          :: a -> Int -> a   
+  complementBit     :: a -> Int -> a   
+  testBit           :: a -> Int -> Bool
+  bitSize           :: a -> Int
+  isSigned          :: a -> Bool
+
+shiftL, shiftR   :: Bits a => a -> Int -> a
+rotateL, rotateR :: Bits a => a -> Int -> a
+shiftL  a i = shift  a i
+shiftR  a i = shift  a (-i)
+rotateL a i = rotate a i
+rotateR a i = rotate a (-i)
+</verb></tscreen>
+
+Notes:
+<itemize>
+<item>
+  <tt/bitSize/ and <tt/isSigned/ are like <tt/floatRadix/ and <tt/floatDigits/
+  -- they return parameters of the <em/type/ of their argument rather than 
+  of the particular argument they are applied to.  <tt/bitSize/ returns
+  the number of bits in the type (or <tt/Nothing/ for unbounded types); and
+  <tt/isSigned/ returns whether the type is signed or not.  
+<item>
+  <tt/shift/ performs sign extension.  
+  That is, right shifts fill the top bits with 1 if the  number is negative
+  and with 0 otherwise.
+  (Since unsigned types are always positive, the top bit is always filled with
+  0.)
+<item> 
+  Bits are numbered from 0 with bit 0 being the least significant bit.
+<item>
+  <tt/shift x i/ and <tt/rotate x i/ shift to the left if <tt/i/ is
+  positive and to the right otherwise.  
+<!--
+  <item>
+    <tt/rotate/ is well defined only if bitSize returns a number.
+    (Maybe we should impose a Bounded constraint on it?)
+  -->
+<item>
+  <tt/bit i/ is the value with the i'th bit set.
+</itemize>
+
+<sect> <idx/Word/ <p>
+
+This library provides unsigned integers of various sizes.
+The types supported are as follows:
+
+<tabular ca="|l|l|">
+type    | number of bits @ 
+<hline> 
+Word8    | 8  @
+Word16   | 16 @
+Word32   | 32 @
+Word64   | 64 @
+<hline> 
+</tabular>
+
+For each type <it/W/ above, we provide the following functions and
+instances.  The type <it/I/ refers to the signed integer type of the
+same size.
+
+<tscreen><verb>
+data W            -- Unsigned Ints
+instance Eq       W
+instance Ord      W
+instance Show     W
+instance Read     W
+instance Bounded  W
+instance Num      W
+instance Real     W
+instance Integral W
+instance Enum     W
+instance Ix       W
+instance Bits     W
+</verb></tscreen>
+Plus
+<tscreen><verb>
+word8ToWord32  :: Word8  -> Word32
+word32ToWord8  :: Word32 -> Word8
+word16ToWord32 :: Word16 -> Word32
+word32ToWord16 :: Word32 -> Word16
+
+word8ToInt     :: Word8  -> Int
+intToWord8     :: Int    -> Word8
+word16ToInt    :: Word16 -> Int
+intToWord16    :: Int    -> Word16
+word32ToInt    :: Word32 -> Int
+intToWord32    :: Int    -> Word32
+</verb></tscreen>
+
+Notes: 
+<itemize>
+<item>
+  All arithmetic is performed modulo 2^n
+
+  One non-obvious consequequence of this is that <tt/negate/
+  should <em/not/ raise an error on negative arguments.
+
+<item>
+The coercion <tt/wToI/ converts an unsigned n-bit value to the
+signed n-bit value with the same representation.  For example,
+<tt/word8ToInt8 0xff = -1/. 
+Likewise, <tt/iToW/ converts signed n-bit values to the
+corresponding unsigned n-bit value.
+
+<item>
+ToDo: complete the set of coercion functions.
+
+<item>
+Use <tt/Prelude.fromIntegral :: (Integral a, Num b) => a -> b/ to
+coerce between different sizes or to preserve sign when converting
+between values of the same size.
+
+<item>
+It would be very natural to add a type a type <tt/Natural/ providing
+an unbounded size unsigned integer --- just as <tt/Integer/ provides
+unbounded size signed integers.  We do not do that yet since there is
+no demand for it.  Doing so would require <tt/Bits.bitSize/ to return
+<tt/Maybe Int/.
+
+<item>
+The <tt/Enum/ instances stop when they reach their upper or lower
+bound --- they don't overflow the way the <tt/Int/ and <tt/Float/
+instances do.
+
+<item>
+It would be useful to provide a function (or a family of functions?)
+which coerced between any two Word types (without going through
+Integer).
+
+</itemize>
+
+Hugs only provides <tt/Eq/, <tt/Ord/, <tt/Read/ and <tt/Show/
+instances for <tt/Word64/ at the moment.
+
+<sect> <idx/Int/ <p>
+
+This library provides signed integers of various sizes.  The types
+supported are as follows:
+
+<tabular ca="|l|l|l|">
+type    | number of bits @ 
+<hline> 
+Int8    | 8  @
+Int16   | 16 @
+Int32   | 32 @
+Int64   | 64 @
+<hline> 
+</tabular>
+
+For each type <it/I/ above, we provide the following instances.
+
+<tscreen><verb>
+data I            -- Signed Ints
+iToInt            :: I -> Int  -- not provided for Int64
+intToi            :: Int -> I  -- not provided for Int64
+instance Eq       I
+instance Ord      I
+instance Show     I
+instance Read     I
+instance Bounded  I
+instance Num      I
+instance Real     I
+instance Integral I
+instance Enum     I
+instance Ix       I
+instance Bits     I
+</verb></tscreen>
+Plus
+<tscreen><verb>
+int8ToInt  :: Int8  -> Int
+intToInt8  :: Int   -> Int8
+int16ToInt :: Int16 -> Int
+intToInt16 :: Int   -> Int16
+int32ToInt :: Int32 -> Int
+intToInt32 :: Int   -> Int32
+</verb></tscreen>
+
+<itemize>
+<item>
+Hugs does not provide <tt/Int64/ at the moment.
+
+<item>
+ToDo: complete the set of coercion functions.
+
+</itemize>
+
+<sect> <idx/Addr/ <p>
+
+This library provides machine addresses and is primarily intended for 
+use in creating foreign function interfaces using GreenCard.
+
+<tscreen><verb>
+module Addr where
+data Addr  -- Address type
+instance Eq Addr
+
+nullAddr           :: Addr
+plusAddr           :: Addr -> Int -> Addr
+
+-- read value out of _immutable_ memory
+indexCharOffAddr   :: Addr -> Int -> Char
+indexIntOffAddr    :: Addr -> Int -> Int     -- should we drop this?
+indexAddrOffAddr   :: Addr -> Int -> Addr
+indexFloatOffAddr  :: Addr -> Int -> Float
+indexDoubleOffAddr :: Addr -> Int -> Double
+indexWord8OffAddr  :: Addr -> Int -> Word8
+indexWord16OffAddr :: Addr -> Int -> Word16
+indexWord32OffAddr :: Addr -> Int -> Word32
+indexWord64OffAddr :: Addr -> Int -> Word64
+indexInt8OffAddr   :: Addr -> Int -> Int8
+indexInt16OffAddr  :: Addr -> Int -> Int16
+indexInt32OffAddr  :: Addr -> Int -> Int32
+indexInt64OffAddr  :: Addr -> Int -> Int64
+
+-- read value out of mutable memory
+readCharOffAddr    :: Addr -> Int -> IO Char
+readIntOffAddr     :: Addr -> Int -> IO Int  -- should we drop this?
+readAddrOffAddr    :: Addr -> Int -> IO Addr
+readFloatOffAddr   :: Addr -> Int -> IO Float
+readDoubleOffAddr  :: Addr -> Int -> IO Double
+readWord8OffAddr   :: Addr -> Int -> IO Word8
+readWord16OffAddr  :: Addr -> Int -> IO Word16
+readWord32OffAddr  :: Addr -> Int -> IO Word32
+readWord64OffAddr  :: Addr -> Int -> IO Word64
+readInt8OffAddr    :: Addr -> Int -> IO Int8
+readInt16OffAddr   :: Addr -> Int -> IO Int16
+readInt32OffAddr   :: Addr -> Int -> IO Int32
+readInt64OffAddr   :: Addr -> Int -> IO Int64
+
+-- write value into mutable memory
+writeCharOffAddr   :: Addr -> Int -> Char   -> IO ()
+writeIntOffAddr    :: Addr -> Int -> Int    -> IO ()  -- should we drop this?
+writeAddrOffAddr   :: Addr -> Int -> Addr   -> IO ()
+writeFloatOffAddr  :: Addr -> Int -> Float  -> IO ()
+writeDoubleOffAddr :: Addr -> Int -> Double -> IO ()
+writeWord8OffAddr  :: Addr -> Int -> Word8  -> IO ()
+writeWord16OffAddr :: Addr -> Int -> Word16 -> IO ()
+writeWord32OffAddr :: Addr -> Int -> Word32 -> IO ()
+writeWord64OffAddr :: Addr -> Int -> Word64 -> IO ()
+writeInt8OffAddr   :: Addr -> Int -> Int8   -> IO ()
+writeInt16OffAddr  :: Addr -> Int -> Int16  -> IO ()
+writeInt32OffAddr  :: Addr -> Int -> Int32  -> IO ()
+writeInt64OffAddr  :: Addr -> Int -> Int64  -> IO ()
+</verb></tscreen>
+
+Hugs provides <tt/Addr/ and <tt/nullAddr/ but does not provide any of
+the index, read or write functions.  They can be implemented using 
+GreenCard if required.
+
+<sect> <idx/ForeignObj/ <p>
+
+This module is provided by GHC but not by Hugs.
+GreenCard for Hugs provides the <tt/ForeignObj/ type.
+
+<sect> <idx/Concurrent/ <p>
+
+This library provides the Concurrent Haskell extensions
+<cite id="concurrentHaskell:popl96">.
+
+We are grateful to the Glasgow Haskell Project for allowing us to
+redistribute their implementation of this module.
+
+<tscreen><verb>
+module Concurrent where
+
+data ThreadId    -- thread identifiers
+instance Eq ThreadId
+
+forkIO           :: IO () -> IO ThreadId
+killThread       :: ThreadId -> IO ()
+
+data MVar a      -- Synchronisation variables
+newEmptyMVar     :: IO (MVar a)
+newMVar          :: a -> IO (MVar a)
+takeMVar         :: MVar a -> IO a
+putMVar          :: MVar a -> a -> IO ()
+swapMVar         :: MVar a -> a -> IO a
+readMVar         :: MVar a -> IO a 
+instance Eq (MVar a)
+
+data Chan a      -- channels
+newChan          :: IO (Chan a)
+writeChan        :: Chan a -> a -> IO ()
+readChan         :: Chan a -> IO a
+dupChan          :: Chan a -> IO (Chan a)
+unReadChan       :: Chan a -> a -> IO ()
+readChanContents :: Chan a -> IO [a]
+writeList2Chan   :: Chan a -> [a] -> IO ()
+                      
+data CVar a       -- one element channels
+newCVar          :: IO (CVar a)
+putCVar          :: CVar a -> a -> IO ()
+getCVar          :: CVar a -> IO a
+                      
+data QSem        -- General/quantity semaphores
+newQSem          :: Int  -> IO QSem
+waitQSem         :: QSem -> IO ()
+signalQSem       :: QSem -> IO ()
+                      
+data QSemN       -- General/quantity semaphores
+newQSemN         :: Int   -> IO QSemN
+waitQSemN        :: QSemN -> Int -> IO ()
+signalQSemN      :: QSemN -> Int -> IO ()
+
+type SampleVar a -- Sample variables 
+newEmptySampleVar:: IO (SampleVar a)
+newSampleVar     :: a -> IO (SampleVar a)
+emptySampleVar   :: SampleVar a -> IO ()
+readSampleVar    :: SampleVar a -> IO a
+writeSampleVar   :: SampleVar a -> a -> IO ()
+</verb></tscreen>
+
+Notes:
+<itemize>
+
+<item> 
+  GHC uses preemptive multitasking:
+  Context switches can occur at any time, except if you call a C
+  function (like \verb"getchar") that blocks waiting for input.
+
+  Hugs uses cooperative multitasking:
+  Context switches only occur when you use one of the primitives
+  defined in this module.  This means that programs such as:
+
+<tscreen><verb>
+main = forkIO (write 'a') >> write 'b'
+ where write c = putChar c >> write c
+</verb></tscreen>
+
+  will print either <tt/aaaaaaaaaaaaaa.../ or <tt/bbbbbbbbbbbb.../,
+  instead of some random interleaving of <tt/a/s and <tt/b/s.
+
+  In practice, cooperative multitasking is sufficient for writing 
+  simple graphical user interfaces.
+
+<item>
+Hugs does not provide the functions <tt/mergeIO/ or <tt/nmergeIO/ since these
+require preemptive multitasking.
+
+<item>
+<tt/killThread/ has not been implemented yet on either system.
+The plan is that <tt/killThread/ will raise an IO exception in the
+killed thread which it can catch --- perhaps allowing it to kill its
+children before exiting.
+
+<item>
+The <tt/Ord/ instance for <tt/ThreadId/s provides an arbitrary total ordering
+which might be used to build an ordered binary tree, say.  
+
+</itemize>
+
+<sect> <idx/Pretty/ <p>
+
+This library contains Simon Peyton Jones' implementation of John
+Hughes's pretty printer combinators.
+
+<tscreen><verb>
+module Pretty where
+infixl 6 <> 
+infixl 6 <+>
+infixl 5 $$, $+$
+data Doc  -- the Document datatype
+
+-- The primitive Doc values
+empty                     :: Doc
+text                      :: String   -> Doc 
+char                      :: Char     -> Doc
+int                       :: Int      -> Doc
+integer                   :: Integer  -> Doc
+float                     :: Float    -> Doc
+double                    :: Double   -> Doc
+rational                  :: Rational -> Doc
+semi, comma, colon, space, equals              :: Doc
+lparen, rparen, lbrack, rbrack, lbrace, rbrace :: Doc
+parens, brackets, braces  :: Doc -> Doc 
+quotes, doubleQuotes      :: Doc -> Doc
+
+-- Combining Doc values
+(<>)   :: Doc -> Doc -> Doc     -- Beside
+hcat   :: [Doc] -> Doc          -- List version of <>
+(<+>)  :: Doc -> Doc -> Doc     -- Beside, separated by space
+hsep   :: [Doc] -> Doc          -- List version of <+>
+($$)   :: Doc -> Doc -> Doc     -- Above; if there is no
+                                  -- overlap it "dovetails" the two
+vcat   :: [Doc] -> Doc          -- List version of $$
+cat    :: [Doc] -> Doc          -- Either hcat or vcat
+sep    :: [Doc] -> Doc          -- Either hsep or vcat
+fcat   :: [Doc] -> Doc          -- ``Paragraph fill'' version of cat
+fsep   :: [Doc] -> Doc          -- ``Paragraph fill'' version of sep
+nest   :: Int -> Doc -> Doc     -- Nested
+hang   :: Doc -> Int -> Doc -> Doc
+punctuate :: Doc -> [Doc] -> [Doc]      
+-- punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
+
+-- Displaying Doc values
+instance Show Doc
+render     :: Doc -> String             -- Uses default style
+renderStyle  :: Style -> Doc -> String
+data Style = Style { lineLength     :: Int,   -- In chars
+                       ribbonsPerLine :: Float, -- Ratio of ribbon length
+                                                -- to line length
+                       mode :: Mode
+               }
+data Mode = PageMode            -- Normal 
+            | ZigZagMode          -- With zig-zag cuts
+            | LeftMode            -- No indentation, infinitely long lines
+            | OneLineMode         -- All on one line
+</verb></tscreen>
+
+<biblio files="refs" style="abbrv">
+
+
+</article>
+