[commit: ghc] wip/nfs-locking: Base: Use proper Haddock syntax (ecd1e7d)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:43:32 UTC 2017


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

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/ecd1e7db540b6cf31cc884b5dccba1bf9e01de70/ghc

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

commit ecd1e7db540b6cf31cc884b5dccba1bf9e01de70
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Dec 20 21:40:53 2015 +0100

    Base: Use proper Haddock syntax


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

ecd1e7db540b6cf31cc884b5dccba1bf9e01de70
 src/Base.hs | 44 +++++++++++++++++++++++++++-----------------
 1 file changed, 27 insertions(+), 17 deletions(-)

diff --git a/src/Base.hs b/src/Base.hs
index 33b01bd..1c72fd8 100644
--- a/src/Base.hs
+++ b/src/Base.hs
@@ -1,4 +1,5 @@
 module Base (
+    -- * General utilities
     module Control.Applicative,
     module Control.Monad.Extra,
     module Control.Monad.Reader,
@@ -7,18 +8,26 @@ module Base (
     module Data.List,
     module Data.Maybe,
     module Data.Monoid,
+
+    -- * Shake
     module Development.Shake,
     module Development.Shake.Classes,
     module Development.Shake.Config,
     module Development.Shake.FilePath,
     module Development.Shake.Util,
-    module System.Console.ANSI,
+
+    -- * Paths
     shakeFilesPath, configPath, bootPackageConstraints, packageDependencies,
-    replaceEq, replaceSeparators, decodeModule,
-    unifyPath, (-/-), chunksOfSize,
+
+    -- * Output
     putColoured, putOracle, putBuild, putSuccess, putError,
+    module System.Console.ANSI,
+
+    -- * Miscellaneous utilities
     bimap, minusOrd, intersectOrd,
-    removeFileIfExists
+    removeFileIfExists,
+    replaceEq, replaceSeparators, decodeModule,
+    unifyPath, (-/-), chunksOfSize,
     ) where
 
 import Control.Applicative
@@ -55,34 +64,35 @@ packageDependencies :: FilePath
 packageDependencies = shakeFilesPath -/- "package-dependencies"
 
 -- Utility functions
--- Find and replace all occurrences of a value in a list
+-- | Find and replace all occurrences of a value in a list
 replaceEq :: Eq a => a -> a -> [a] -> [a]
 replaceEq from = replaceIf (== from)
 
--- Find and replace all occurrences of path separators in a String with a Char
+-- | Find and replace all occurrences of path separators in a String with a Char
 replaceSeparators :: Char -> String -> String
 replaceSeparators = replaceIf isPathSeparator
 
 replaceIf :: (a -> Bool) -> a -> [a] -> [a]
 replaceIf p to = map (\from -> if p from then to else from)
 
--- Given a module name extract the directory and file names, e.g.:
--- decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity")
+-- | Given a module name extract the directory and file names, e.g.:
+--
+-- > decodeModule "Data.Functor.Identity" = ("Data/Functor/", "Identity")
 decodeModule :: String -> (FilePath, String)
 decodeModule = splitFileName . replaceEq '.' '/'
 
--- Normalise a path and convert all path separators to /, even on Windows.
+-- | Normalise a path and convert all path separators to @/@, even on Windows.
 unifyPath :: FilePath -> FilePath
 unifyPath = toStandard . normaliseEx
 
--- Combine paths using </> and apply unifyPath to the result
+-- | Combine paths using '</>' and apply 'unifyPath' to the result
 (-/-) :: FilePath -> FilePath -> FilePath
 a -/- b = unifyPath $ a </> b
 
 infixr 6 -/-
 
--- (chunksOfSize size strings) splits a given list of strings into chunks not
--- exceeding the given 'size'.
+-- | @chunksOfSize size strings@ splits a given list of strings into chunks not
+-- exceeding the given @size at .
 chunksOfSize :: Int -> [String] -> [[String]]
 chunksOfSize _    [] = []
 chunksOfSize size strings = reverse chunk : chunksOfSize size rest
@@ -94,7 +104,7 @@ chunksOfSize size strings = reverse chunk : chunksOfSize size rest
       where
         newSize = chunkSize + length s
 
--- A more colourful version of Shake's putNormal
+-- | A more colourful version of Shake's putNormal
 putColoured :: Color -> String -> Action ()
 putColoured colour msg = do
     liftIO $ setSGR [SetColor Foreground Vivid colour]
@@ -102,19 +112,19 @@ putColoured colour msg = do
     liftIO $ setSGR []
     liftIO $ hFlush stdout
 
--- Make oracle output more distinguishable
+-- | Make oracle output more distinguishable
 putOracle :: String -> Action ()
 putOracle = putColoured Blue
 
--- Make build output more distinguishable
+-- | Make build output more distinguishable
 putBuild :: String -> Action ()
 putBuild = putColoured White
 
--- A more colourful version of success message
+-- | A more colourful version of success message
 putSuccess :: String -> Action ()
 putSuccess = putColoured Green
 
--- A more colourful version of error message
+-- | A more colourful version of error message
 putError :: String -> Action a
 putError msg = do
     putColoured Red msg



More information about the ghc-commits mailing list