[commit: ghc] master: Improve Control.Monad docs (4887c30)

git at git.haskell.org git at git.haskell.org
Tue Jan 2 23:56:25 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/4887c3086149a15a1e16c765682debcfbb9de145/ghc

>---------------------------------------------------------------

commit 4887c3086149a15a1e16c765682debcfbb9de145
Author: Nathan Collins <conathan at galois.com>
Date:   Sat Dec 9 18:59:05 2017 -0800

    Improve Control.Monad docs
    
    Summary:
    * Reformat Control.Monad.mfilter docs
    
    The formatting was bad, with everything running together, and a
    paranthesis was missing. Now the examples and relation between
    `filter` and `mfilter` are typeset as code blocks instead of inline.
    
    * Add example to Control.Monad.join docs
    
    The example is using `join . atomically` to run IO actions computed by
    STM transactions.
    
    I couldn't figure out how to link to the STM docs in
    `Control.Monad.STM`, because that module comes from the `stm` package,
    not from `base`, even though `stm` is also part of the GHC source
    tree. So, instead I linked to the STM docs in `GHC.Conc`, which seems
    inferior to linking to `Control.Monad.STM`, but better than having no
    links at all.
    
    * Add example to Control.Monad.forever docs
    
    The example is a simple TCP echo server. To make the uses of `forever`
    stand out in the example code, I only link to the non-`forever`
    functions (e.g. `forkFinally`) in the import lists.
    
    Reviewers: bgamari, hvr
    
    Subscribers: rwbarton, thomie, carter
    
    Differential Revision: https://phabricator.haskell.org/D4259


>---------------------------------------------------------------

4887c3086149a15a1e16c765682debcfbb9de145
 libraries/base/Control/Monad.hs | 32 +++++++++++++++++++++++++++++++-
 1 file changed, 31 insertions(+), 1 deletion(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 8d664e6..d9bfdeb 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -152,7 +152,37 @@ f >=> g     = \x -> f x >>= g
 (<=<)       :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c)
 (<=<)       = flip (>=>)
 
--- | @'forever' act@ repeats the action infinitely.
+-- | Repeat an action indefinitely.
+--
+-- ==== __Examples__
+--
+-- Simple network servers can be created by writing a function to
+-- handle a single client connection and then using 'forever' to
+-- accept client connections and fork threads to handle them.
+--
+-- For example, here is a [TCP echo
+-- server](https://en.wikipedia.org/wiki/Echo_Protocol) implemented
+-- with 'forever':
+--
+-- @
+-- import "Control.Concurrent" ( 'Control.Concurrent.forkFinally' )
+-- import "Control.Monad"      ( 'forever' )
+-- import Network            ( PortID(..), accept, listenOn )
+-- import "System.IO"          ( 'System.IO.hClose', 'System.IO.hGetLine', 'System.IO.hPutStrLn' )
+--
+-- main :: IO ()
+-- main = do
+--   sock <- listenOn (PortNumber 7)
+--   'forever' $ do
+--     (handle, _, _) <- accept sock
+--     echo handle \`forkFinally\` const (hClose handle)
+--   where
+--     echo handle = 'forever' $
+--       hGetLine handle >>= hPutStrLn handle
+-- @
+--
+-- The @Network@ module is provided by the [network
+-- package](https://hackage.haskell.org/package/network).
 forever     :: (Applicative f) => f a -> f b
 {-# INLINE forever #-}
 forever a   = let a' = a *> a' in a'



More information about the ghc-commits mailing list