[commit: ghc] master: base: Misc haddock fixes (c088137)

git at git.haskell.org git at git.haskell.org
Fri Nov 2 21:10:43 UTC 2018


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

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

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

commit c088137949bd69ee463c08a0d221517bc5108945
Author: Simon Jakobi <simon.jakobi at gmail.com>
Date:   Tue Oct 23 16:29:13 2018 +0200

    base: Misc haddock fixes
    
    (cherry picked from commit ee545ff44e0ba9a165de40807548c75bf181dda3)


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

c088137949bd69ee463c08a0d221517bc5108945
 libraries/base/GHC/Float.hs |  4 ++--
 libraries/base/GHC/Num.hs   | 14 +++++++-------
 libraries/base/GHC/Real.hs  | 10 +++++-----
 3 files changed, 14 insertions(+), 14 deletions(-)

diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index 9296978..3ac9408 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -65,11 +65,11 @@ infixr 8  **
 
 -- | Trigonometric and hyperbolic functions and related functions.
 --
--- The Haskell Report defines no laws for 'Floating'. However, '(+)', '(*)'
+-- The Haskell Report defines no laws for 'Floating'. However, @('+')@, @('*')@
 -- and 'exp' are customarily expected to define an exponential field and have
 -- the following properties:
 --
--- * @exp (a + b)@ = @exp a * exp b
+-- * @exp (a + b)@ = @exp a * exp b@
 -- * @exp (fromInteger 0)@ = @fromInteger 1@
 class  (Fractional a) => Floating a  where
     pi                  :: a
diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs
index 1fa63fb..aed11a3 100644
--- a/libraries/base/GHC/Num.hs
+++ b/libraries/base/GHC/Num.hs
@@ -36,17 +36,17 @@ default ()              -- Double isn't available yet,
 
 -- | Basic numeric class.
 --
--- The Haskell Report defines no laws for 'Num'. However, '(+)' and '(*)' are
+-- The Haskell Report defines no laws for 'Num'. However, @('+')@ and @('*')@ are
 -- customarily expected to define a ring and have the following properties:
 --
--- [__Associativity of (+)__]: @(x + y) + z@ = @x + (y + z)@
--- [__Commutativity of (+)__]: @x + y@ = @y + x@
--- [__ at fromInteger 0@ is the additive identity__]: @x + fromInteger 0@ = @x@
+-- [__Associativity of @('+')@__]: @(x + y) + z@ = @x + (y + z)@
+-- [__Commutativity of @('+')@__]: @x + y@ = @y + x@
+-- [__@'fromInteger' 0@ is the additive identity__]: @x + fromInteger 0@ = @x@
 -- [__'negate' gives the additive inverse__]: @x + negate x@ = @fromInteger 0@
--- [__Associativity of (*)__]: @(x * y) * z@ = @x * (y * z)@
--- [__ at fromInteger 1@ is the multiplicative identity__]:
+-- [__Associativity of @('*')@__]: @(x * y) * z@ = @x * (y * z)@
+-- [__@'fromInteger' 1@ is the multiplicative identity__]:
 -- @x * fromInteger 1@ = @x@ and @fromInteger 1 * x@ = @x@
--- [__Distributivity of (*) with respect to (+)__]:
+-- [__Distributivity of @('*')@ with respect to @('+')@__]:
 -- @a * (b + c)@ = @(a * b) + (a * c)@ and @(b + c) * a@ = @(b * a) + (c * a)@
 --
 -- Note that it /isn't/ customarily expected that a type instance of both 'Num'
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index c96959f..da64c8b 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -138,7 +138,7 @@ class  (Num a, Ord a) => Real a  where
 --
 -- The Haskell Report defines no laws for 'Integral'. However, 'Integral'
 -- instances are customarily expected to define a Euclidean domain and have the
--- following properties for the 'div'/'mod' and 'quot'/'rem' pairs, given
+-- following properties for the `div`\/`mod` and `quot`\/`rem` pairs, given
 -- suitable Euclidean functions @f@ and @g@:
 --
 -- * @x@ = @y * quot x y + rem x y@ with @rem x y@ = @fromInteger 0@ or
@@ -182,8 +182,8 @@ class  (Real a, Enum a) => Integral a  where
 
 -- | Fractional numbers, supporting real division.
 --
--- The Haskell Report defines no laws for 'Fractional'. However, '(+)' and
--- '(*)' are customarily expected to define a division ring and have the
+-- The Haskell Report defines no laws for 'Fractional'. However, @('+')@ and
+-- @('*')@ are customarily expected to define a division ring and have the
 -- following properties:
 --
 -- [__'recip' gives the multiplicative inverse__]:
@@ -194,9 +194,9 @@ class  (Real a, Enum a) => Integral a  where
 class  (Num a) => Fractional a  where
     {-# MINIMAL fromRational, (recip | (/)) #-}
 
-    -- | fractional division
+    -- | Fractional division.
     (/)                 :: a -> a -> a
-    -- | reciprocal fraction
+    -- | Reciprocal fraction.
     recip               :: a -> a
     -- | Conversion from a 'Rational' (that is @'Ratio' 'Integer'@).
     -- A floating literal stands for an application of 'fromRational'



More information about the ghc-commits mailing list