[project @ 2002-05-10 15:41:33 by simonmar]
authorsimonmar <unknown>
Fri, 10 May 2002 15:41:34 +0000 (15:41 +0000)
committersimonmar <unknown>
Fri, 10 May 2002 15:41:34 +0000 (15:41 +0000)
More documentation

Control/Concurrent/MVar.hs
Control/Monad/ST.hs
Control/Monad/ST/Lazy.hs
Control/Monad/ST/Strict.hs
Data/Bool.hs
Data/IORef.hs
Data/STRef.hs
GHC/Base.lhs
GHC/STRef.lhs
System/Console/GetOpt.hs

index c56750f..ef1a2e6 100644 (file)
@@ -36,7 +36,6 @@ import ConcBase       ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
                  tryTakeMVar, tryPutMVar, isEmptyMVar,
                   readMVar, swapMVar,
                )
-import Prelude hiding( catch )
 #endif
 
 #ifdef __GLASGOW_HASKELL__
@@ -45,6 +44,7 @@ import GHC.Conc       ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
                )
 #endif
 
+import Prelude
 import Control.Exception as Exception
 
 #ifdef __HUGS__
index 2a3985a..59b303f 100644 (file)
@@ -8,21 +8,26 @@
 -- Stability   :  experimental
 -- Portability :  non-portable (requires universal quantification for runST)
 --
--- The State Transformer Monad, ST
+-- This library provides support for /strict/ state threads, as
+-- described in the PLDI \'94 paper by John Launchbury and Simon Peyton
+-- Jones /Lazy State Threads/.
 --
 -----------------------------------------------------------------------------
 
 module Control.Monad.ST
-      (
-       ST                  -- abstract, instance of Functor, Monad, Typeable.
-      , runST              -- :: (forall s. ST s a) -> a
-      , fixST              -- :: (a -> ST s a) -> ST s a
-      , unsafeInterleaveST  -- :: ST s a -> ST s a
-
-      , unsafeIOToST       -- :: IO a -> ST s a
-
-      , RealWorld          -- abstract
-      , stToIO             -- :: ST RealWorld a -> IO a
+  (
+       -- * The 'ST' Monad
+       ST,             -- abstract, instance of Functor, Monad, Typeable.
+       runST,          -- :: (forall s. ST s a) -> a
+       fixST,          -- :: (a -> ST s a) -> ST s a
+
+       -- * Unsafe operations
+       unsafeInterleaveST,     -- :: ST s a -> ST s a
+       unsafeIOToST,           -- :: IO a -> ST s a
+
+       -- * Converting 'ST' to 'IO'
+       RealWorld,              -- abstract
+       stToIO                  -- :: ST RealWorld a -> IO a
       ) where
 
 import Prelude
index adaca1a..b98316b 100644 (file)
@@ -8,20 +8,27 @@
 -- Stability   :  provisional
 -- Portability :  non-portable (requires universal quantification for runST)
 --
--- This module presents an identical interface to Control.Monad.ST,
--- but the underlying implementation of the state thread is lazy.
+-- This module presents an identical interface to "Control.Monad.ST",
+-- but the underlying implementation of the state thread is /lazy/ (in
+-- the sense that (@_|_ >> a@ is not necessarily equal to @_|_@).
 --
 -----------------------------------------------------------------------------
 
 module Control.Monad.ST.Lazy (
+       -- * The 'ST' monad
        ST,
-
        runST,
-       unsafeInterleaveST,
        fixST,
 
-       ST.unsafeIOToST, ST.stToIO,
+       -- * Unsafe operations
+       unsafeInterleaveST,
+       ST.unsafeIOToST,
+
+       -- * Converting 'ST' To 'IO'
+       RealWorld,
+       ST.stToIO,
 
+       -- * Converting between strict and lazy 'ST'
        strictToLazyST, lazyToStrictST
     ) where
 
@@ -80,6 +87,11 @@ fixST m = ST (\ s ->
 -- Strict <--> Lazy
 
 #ifdef __GLASGOW_HASKELL__
+{-|
+Convert a strict 'ST' computation into a lazy one.  The strict state
+thread passed to 'strictToLazyST' is not performed until the result of
+the lazy state thread it returns is demanded.
+-}
 strictToLazyST :: ST.ST s a -> ST s a
 strictToLazyST m = ST $ \s ->
         let 
@@ -89,6 +101,9 @@ strictToLazyST m = ST $ \s ->
        in
        (r, s')
 
+{-| 
+Convert a lazy 'ST' computation into a strict one.
+-}
 lazyToStrictST :: ST s a -> ST.ST s a
 lazyToStrictST (ST m) = GHC.ST.ST $ \s ->
         case (m (S# s)) of (a, S# s') -> (# s', a #)
index 677d6a2..c492766 100644 (file)
@@ -8,7 +8,7 @@
 -- Stability   :  provisional
 -- Portability :  non-portable (requires universal quantification for runST)
 --
--- The strict ST monad (identical to Control.Monad.ST)
+-- The strict ST monad (re-export of "Control.Monad.ST")
 --
 -----------------------------------------------------------------------------
 
index 2515d58..66b804a 100644 (file)
@@ -9,12 +9,14 @@
 -- Stability   :  experimental
 -- Portability :  portable
 --
--- The Bool type and related functions.
+-- The 'Bool' type and related functions.
 --
 -----------------------------------------------------------------------------
 
 module Data.Bool (
+   -- * Booleans
    Bool(..),
+   -- ** Operations 
    (&&),       -- :: Bool -> Bool -> Bool
    (||),       -- :: Bool -> Bool -> Bool
    not,                -- :: Bool -> Bool
index 5599685..2580df2 100644 (file)
 -----------------------------------------------------------------------------
 
 module Data.IORef
-       ( IORef               -- abstract, instance of: Eq, Typeable
-        , newIORef           -- :: a -> IO (IORef a)
-        , readIORef          -- :: IORef a -> IO a
-        , writeIORef         -- :: IORef a -> a -> IO ()
-       , modifyIORef         -- :: IORef a -> (a -> a) -> IO ()
+  ( 
+       -- * IORefs
+       IORef,                -- abstract, instance of: Eq, Typeable
+       newIORef,             -- :: a -> IO (IORef a)
+        readIORef,           -- :: IORef a -> IO a
+        writeIORef,          -- :: IORef a -> a -> IO ()
+       modifyIORef,          -- :: IORef a -> (a -> a) -> IO ()
 
 #if !defined(__PARALLEL_HASKELL__) && defined(__GLASGOW_HASKELL__)
-       , mkWeakIORef           -- :: IORef a -> IO () -> IO (Weak (IORef a))
+       mkWeakIORef,          -- :: IORef a -> IO () -> IO (Weak (IORef a))
 #endif
        ) where
 
@@ -38,6 +40,7 @@ import GHC.Weak
 import Data.Dynamic
 
 #if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__)
+-- |Make a 'Weak' pointer to an 'IORef'
 mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a))
 mkWeakIORef r@(IORef (STRef r#)) f = IO $ \s ->
   case mkWeak# r# r f s of (# s1, w #) -> (# s1, Weak w #)
@@ -55,6 +58,7 @@ instance Eq (IORef a) where
     (==) = eqIORef
 #endif /* __HUGS__ */
 
+-- |Mutate the contents of an 'IORef'
 modifyIORef :: IORef a -> (a -> a) -> IO ()
 modifyIORef ref f = writeIORef ref . f =<< readIORef ref
 
index 2331ef9..81b1351 100644 (file)
@@ -13,6 +13,7 @@
 -----------------------------------------------------------------------------
 
 module Data.STRef (
+       -- * STRefs
        STRef,          -- abstract, instance Eq
        newSTRef,       -- :: a -> ST s (STRef s a)
        readSTRef,      -- :: STRef s a -> ST s a
index 847c1fe..ffc3b06 100644 (file)
@@ -368,21 +368,34 @@ mapFB c f x ys = c (f x) ys
 %*********************************************************
 
 \begin{code}
+-- |The 'Bool' type is an enumeration.  It is defined with 'False'
+-- first so that the corresponding 'Enum' instance will give @'fromEnum'
+-- False@ the value zero, and @'fromEnum' True@ the value 1.
 data  Bool  =  False | True  deriving (Eq, Ord)
        -- Read in GHC.Read, Show in GHC.Show
 
 -- Boolean functions
 
-(&&), (||)             :: Bool -> Bool -> Bool
+-- | Boolean \"and\"
+(&&)                   :: Bool -> Bool -> Bool
 True  && x             =  x
 False && _             =  False
+
+-- | Boolean \"or\"
+(||)                   :: Bool -> Bool -> Bool
 True  || _             =  True
 False || x             =  x
 
+-- | Boolean \"not\"
 not                    :: Bool -> Bool
 not True               =  False
 not False              =  True
 
+-- |'otherwise' is defined as the value 'True'; it helps to make
+-- guards more readable.  eg.
+--
+-- >  f x | x \< 0     = ...
+-- >      | otherwise = ...
 otherwise              :: Bool
 otherwise              =  True
 \end{code}
index fa96db3..5eecb85 100644 (file)
@@ -20,20 +20,26 @@ import GHC.ST
 import GHC.Base
 
 data STRef s a = STRef (MutVar# s a)
+-- ^ a value of type @STRef s a@ is a mutable variable in state thread @s@,
+-- containing a value of type @a@
 
+-- |Build a new 'STRef' in the current state thread
 newSTRef :: a -> ST s (STRef s a)
 newSTRef init = ST $ \s1# ->
     case newMutVar# init s1#            of { (# s2#, var# #) ->
     (# s2#, STRef var# #) }
 
+-- |Read the value of an 'STRef'
 readSTRef :: STRef s a -> ST s a
 readSTRef (STRef var#) = ST $ \s1# -> readMutVar# var# s1#
 
+-- |Write a new value into an 'STRef'
 writeSTRef :: STRef s a -> a -> ST s ()
 writeSTRef (STRef var#) val = ST $ \s1# ->
     case writeMutVar# var# val s1#      of { s2# ->
     (# s2#, () #) }
 
+-- |Mutate the contents of an 'STRef'
 modifySTRef :: STRef s a -> (a -> a) -> ST s ()
 modifySTRef ref f = readSTRef ref >>= writeSTRef ref . f
 
index b8423df..cf1d605 100644 (file)
@@ -8,7 +8,9 @@
 -- Stability   :  experimental
 -- Portability :  portable
 --
--- A Haskell port of the GNU getopt library 
+-- This library provides facilities for parsing the command-line options
+-- in a standalone program.  It is essentially a Haskell port of the GNU 
+-- @getopt@ library.
 --
 -----------------------------------------------------------------------------
 
@@ -32,32 +34,52 @@ including a 46 line example! :-)
 -}
 
 module System.Console.GetOpt (
+       -- * GetOpt
+       getOpt,
+       usageInfo,
        ArgOrder(..),
        OptDescr(..),
        ArgDescr(..),
-       usageInfo,      -- :: String -> [OptDescr a] -> String
-       getOpt          -- :: ArgOrder a -> [OptDescr a] -> [String]
-                       --        -> ([a],[String],[String])
+
+       -- * Example
+               
+       -- $example
   ) where
 
 import Prelude
 import Data.List       ( isPrefixOf )
 
-data ArgOrder a                -- what to do with options following non-options:
-   = RequireOrder                --  no option processing after first non-option
-   | Permute                     --  freely intersperse options and non-options
-   | ReturnInOrder (String -> a) --  wrap non-options into options
+-- |What to do with options following non-options
+data ArgOrder a
+  = RequireOrder                -- ^ no option processing after first non-option
+  | Permute                     -- ^ freely intersperse options and non-options
+  | ReturnInOrder (String -> a) -- ^ wrap non-options into options
+
+{-|
+Each 'OptDescr' describes a single option.
+
+The arguments to 'Option' are:
+
+* list of short option characters
+
+* list of long option strings (without "--")
 
+* argument descriptor
+
+* explanation of option for user
+-}
 data OptDescr a =              -- description of a single options:
    Option [Char]                --    list of short option characters
           [String]              --    list of long option strings (without "--")
           (ArgDescr a)          --    argument descriptor
           String                --    explanation of option for user
 
-data ArgDescr a                        -- description of an argument option:
-   = NoArg                   a         --    no argument expected
-   | ReqArg (String       -> a) String --    option requires argument
-   | OptArg (Maybe String -> a) String --    optional argument
+-- |Describes whether an option takes an argument or not, and if so
+-- how the argument is injected into a value of type @a@.
+data ArgDescr a
+   = NoArg                   a         -- ^   no argument expected
+   | ReqArg (String       -> a) String -- ^   option requires argument
+   | OptArg (Maybe String -> a) String -- ^   optional argument
 
 data OptKind a                -- kind of cmd line arg (internal use only):
    = Opt       a                --    an option
@@ -65,6 +87,9 @@ data OptKind a                -- kind of cmd line arg (internal use only):
    | EndOfOpts                  --    end-of-options marker (i.e. "--")
    | OptErr    String           --    something went wrong...
 
+-- | Return a string describing the usage of a command, derived from
+-- the header (first argument) and the options described by the 
+-- second argument.
 usageInfo :: String                    -- header
           -> [OptDescr a]              -- option descriptors
           -> String                    -- nicely formatted decription of options
@@ -93,6 +118,20 @@ fmtLong (NoArg  _   ) lo = "--" ++ lo
 fmtLong (ReqArg _ ad) lo = "--" ++ lo ++ "=" ++ ad
 fmtLong (OptArg _ ad) lo = "--" ++ lo ++ "[=" ++ ad ++ "]"
 
+{-|
+Process the command-line, and return the list of values that matched
+(and those that didn\'t). The arguments are:
+
+* The order requirements (see 'ArgOrder')
+
+* The option descriptions (see 'OptDescr')
+
+* The actual command line arguments (presumably got from 
+  'System.Console.Environment.getArgs').
+
+'getOpt' returns a triple, consisting of the argument values, a list
+of options that didn\'t match, and a list of error messages.
+-}
 getOpt :: ArgOrder a                   -- non-option handling
        -> [OptDescr a]                 -- option descriptors
        -> [String]                     -- the commandline arguments
@@ -214,3 +253,41 @@ test order cmdline = case getOpt order options cmdline of
 --          -n USER   --name=USER           only dump USER's files
 -----------------------------------------------------------------------------------------
 -}
+
+{- $example
+
+To hopefully illuminate the role of the different "GetOpt" data
+structures, here\'s the command-line options for a (very simple)
+compiler:
+
+>    module Opts where
+>    
+>    import GetOpt
+>    import Maybe ( fromMaybe )
+>    
+>    data Flag 
+>     = Verbose  | Version 
+>     | Input String | Output String | LibDir String
+>      deriving Show
+>    
+>    options :: [OptDescr Flag]
+>    options =
+>     [ Option [\'v\']     [\"verbose\"] (NoArg Verbose)       \"chatty output on stderr\"
+>     , Option [\'V\',\'?\'] [\"version\"] (NoArg Version)       \"show version number\"
+>     , Option [\'o\']     [\"output\"]  (OptArg outp \"FILE\")  \"output FILE\"
+>     , Option [\'c\']     []          (OptArg inp  \"FILE\")  \"input FILE\"
+>     , Option [\'L\']     [\"libdir\"]  (ReqArg LibDir \"DIR\") \"library directory\"
+>     ]
+>    
+>    inp,outp :: Maybe String -> Flag
+>    outp = Output . fromMaybe \"stdout\"
+>    inp  = Input  . fromMaybe \"stdout\"
+>    
+>    compilerOpts :: [String] -> IO ([Flag], [String])
+>    compilerOpts argv = 
+>      case (getOpt Permute options argv) of
+>         (o,n,[]  ) -> return (o,n)
+>         (_,_,errs) -> failIO (concat errs ++ usageInfo header options)
+>      where header = \"Usage: ic [OPTION...] files...\"
+
+-}