[commit: ghc] master: Clean-up Haddock in `Data.Functor` (ac0915b)

git at git.haskell.org git at git.haskell.org
Wed Nov 5 11:21:17 UTC 2014


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

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

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

commit ac0915b8f2b6f5b73f0a6d7e7739abe96c3745eb
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Wed Nov 5 12:19:13 2014 +0100

    Clean-up Haddock in `Data.Functor`
    
    This mostly cleans up irregularities introduced in
    68255588f89462e542c502f6f92548712808032f (re D352) as well as making
    sure Haddock is able to resolve all references.


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

ac0915b8f2b6f5b73f0a6d7e7739abe96c3745eb
 libraries/base/Data/Functor.hs | 131 ++++++++++++++++++++---------------------
 1 file changed, 65 insertions(+), 66 deletions(-)

diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs
index 0896947..64692cf 100644
--- a/libraries/base/Data/Functor.hs
+++ b/libraries/base/Data/Functor.hs
@@ -12,7 +12,7 @@
 -- Portability :  portable
 --
 -- Functors: uniform action over a parameterized type, generalizing the
--- 'map' function on lists.
+-- 'Data.List.map' function on lists.
 
 module Data.Functor
     (
@@ -33,33 +33,32 @@ infixl 4 <$>
 
 -- | An infix synonym for 'fmap'.
 --
---   ==== __Examples__
+-- ==== __Examples__
 --
---   Convert from a 'Maybe' 'Int' to a 'Maybe' 'String' using 'show':
+-- Convert from a @'Maybe' 'Int'@ to a @'Maybe' 'String'@ using 'show':
 --
---   >>> show <$> Nothing
---   Nothing
---   >>> show <$> Just 3
---   Just "3"
+-- >>> show <$> Nothing
+-- Nothing
+-- >>> show <$> Just 3
+-- Just "3"
 --
---   Convert from an 'Either' 'Int' 'Int' to an 'Either' 'Int'
---   'String' using 'show':
+-- Convert from an @'Either' 'Int' 'Int'@ to an @'Either' 'Int'@
+-- 'String' using 'show':
 --
---   >>> show <$> Left 17
---   Left 17
---   >>> show <$> Right 17
---   Right "17"
+-- >>> show <$> Left 17
+-- Left 17
+-- >>> show <$> Right 17
+-- Right "17"
 --
---   Double each element of a list:
+-- Double each element of a list:
 --
---   >>> (*2) <$> [1,2,3]
---   [2,4,6]
+-- >>> (*2) <$> [1,2,3]
+-- [2,4,6]
 --
---   Apply 'even' to the second element of a pair:
---
---   >>> even <$> (2,2)
---   (2,True)
+-- Apply 'even' to the second element of a pair:
 --
+-- >>> even <$> (2,2)
+-- (2,True)
 --
 (<$>) :: Functor f => (a -> b) -> f a -> f b
 (<$>) = fmap
@@ -68,77 +67,77 @@ infixl 4 $>
 
 -- | Flipped version of '<$'.
 --
---   /Since: 4.7.0.0/
+-- /Since: 4.7.0.0/
 --
---   ==== __Examples__
+-- ==== __Examples__
 --
---   Replace the contents of a 'Maybe' 'Int' with a constant 'String':
+-- Replace the contents of a @'Maybe' 'Int'@ with a constant 'String':
 --
---   >>> Nothing $> "foo"
---   Nothing
---   >>> Just 90210 $> "foo"
---   Just "foo"
+-- >>> Nothing $> "foo"
+-- Nothing
+-- >>> Just 90210 $> "foo"
+-- Just "foo"
 --
---   Replace the contents of an 'Either' 'Int' 'Int' with a constant
---   'String', resulting in an 'Either' 'Int' 'String':
+-- Replace the contents of an @'Either' 'Int' 'Int'@ with a constant
+-- 'String', resulting in an @'Either' 'Int' 'String'@:
 --
---   >>> Left 8675309 $> "foo"
---   Left 8675309
---   >>> Right 8675309 $> "foo"
---   Right "foo"
+-- >>> Left 8675309 $> "foo"
+-- Left 8675309
+-- >>> Right 8675309 $> "foo"
+-- Right "foo"
 --
---   Replace each element of a list with a constant 'String':
+-- Replace each element of a list with a constant 'String':
 --
---   >>> [1,2,3] $> "foo"
---   ["foo","foo","foo"]
+-- >>> [1,2,3] $> "foo"
+-- ["foo","foo","foo"]
 --
---   Replace the second element of a pair with a constant 'String':
+-- Replace the second element of a pair with a constant 'String':
 --
---   >>> (1,2) $> "foo"
---   (1,"foo")
+-- >>> (1,2) $> "foo"
+-- (1,"foo")
 --
 ($>) :: Functor f => f a -> b -> f b
 ($>) = flip (<$)
 
 -- | @'void' value@ discards or ignores the result of evaluation, such
---   as the return value of an 'IO' action.
+-- as the return value of an 'System.IO.IO' action.
 --
---   ==== __Examples__
+-- ==== __Examples__
 --
---   Replace the contents of a 'Maybe' 'Int' with unit:
+-- Replace the contents of a @'Maybe' 'Int'@ with unit:
 --
---   >>> void Nothing
---   Nothing
---   >>> void (Just 3)
---   Just ()
+-- >>> void Nothing
+-- Nothing
+-- >>> void (Just 3)
+-- Just ()
 --
---    Replace the contents of an 'Either' 'Int' 'Int' with unit,
---    resulting in an 'Either' 'Int' '()':
+-- Replace the contents of an @'Either' 'Int' 'Int'@ with unit,
+-- resulting in an @'Either' 'Int' '()'@:
 --
---    >>> void (Left 8675309)
---    Left 8675309
---    >>> void (Right 8675309)
---    Right ()
+-- >>> void (Left 8675309)
+-- Left 8675309
+-- >>> void (Right 8675309)
+-- Right ()
 --
---    Replace every element of a list with unit:
+-- Replace every element of a list with unit:
 --
---    >>> void [1,2,3]
---    [(),(),()]
+-- >>> void [1,2,3]
+-- [(),(),()]
 --
---    Replace the second element of a pair with unit:
+-- Replace the second element of a pair with unit:
 --
---    >>> void (1,2)
---    (1,())
+-- >>> void (1,2)
+-- (1,())
 --
---    Discard the result of an 'IO' action:
+-- Discard the result of an 'System.IO.IO' action:
 --
---    >>> mapM print [1,2]
---    1
---    2
---    [(),()]
---    >>> void $ mapM print [1,2]
---    1
---    2
+-- >>> mapM print [1,2]
+-- 1
+-- 2
+-- [(),()]
+-- >>> void $ mapM print [1,2]
+-- 1
+-- 2
 --
 void :: Functor f => f a -> f ()
 void = fmap (const ())



More information about the ghc-commits mailing list