diff options
author | Alec Theriault <alec.theriault@gmail.com> | 2018-09-20 23:31:00 -0700 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2018-11-22 16:07:00 -0500 |
commit | a1bbb56f40b679f4841f0b044c0f5445ff6d3c5b (patch) | |
tree | 3d45011584fa680ef71c0f468dd3275acaed94f0 | |
parent | 9f3e22b9eb2e67323f965b652c37fdd73628b007 (diff) | |
download | haskell-a1bbb56f40b679f4841f0b044c0f5445ff6d3c5b.tar.gz |
Doc-only fixes
* laws are capitalized definition lists, no emphasis on the labels
* adds missing hyperlinks
* fixes other misc. Haddock markup issues.
-rw-r--r-- | libraries/base/Control/Applicative.hs | 4 | ||||
-rw-r--r-- | libraries/base/Control/Category.hs | 9 | ||||
-rw-r--r-- | libraries/base/Control/Monad/Fix.hs | 8 | ||||
-rw-r--r-- | libraries/base/Control/Monad/Zip.hs | 17 | ||||
-rw-r--r-- | libraries/base/Data/Bifoldable.hs | 8 | ||||
-rw-r--r-- | libraries/base/Data/Bitraversable.hs | 6 | ||||
-rw-r--r-- | libraries/base/Data/Fixed.hs | 15 | ||||
-rw-r--r-- | libraries/base/Data/Functor/Classes.hs | 14 | ||||
-rw-r--r-- | libraries/base/Data/Functor/Contravariant.hs | 25 | ||||
-rw-r--r-- | libraries/base/Data/Proxy.hs | 2 | ||||
-rw-r--r-- | libraries/base/Data/STRef.hs | 2 | ||||
-rw-r--r-- | libraries/base/Data/Traversable.hs | 54 | ||||
-rw-r--r-- | libraries/base/Data/Type/Equality.hs | 4 | ||||
-rw-r--r-- | libraries/base/GHC/Base.hs | 48 | ||||
-rw-r--r-- | libraries/base/GHC/Float.hs | 1 | ||||
-rw-r--r-- | libraries/base/GHC/IORef.hs | 4 | ||||
-rw-r--r-- | libraries/base/Text/ParserCombinators/ReadP.hs | 2 | ||||
-rw-r--r-- | libraries/base/Text/Printf.hs | 12 | ||||
-rw-r--r-- | libraries/base/Text/Show/Functions.hs | 2 | ||||
-rw-r--r-- | libraries/base/Type/Reflection.hs | 4 | ||||
-rw-r--r-- | libraries/base/Unsafe/Coerce.hs | 9 |
21 files changed, 114 insertions, 136 deletions
diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs index 5e2fc8ebe6..87394e078b 100644 --- a/libraries/base/Control/Applicative.hs +++ b/libraries/base/Control/Applicative.hs @@ -118,8 +118,8 @@ newtype ZipList a = ZipList { getZipList :: [a] } -- See Data.Traversable for Traversable instance due to import loops -- | --- > f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN --- > = 'ZipList' (zipWithN f xs1 ... xsN) +-- > f <$> ZipList xs1 <*> ... <*> ZipList xsN +-- > = ZipList (zipWithN f xs1 ... xsN) -- -- where @zipWithN@ refers to the @zipWith@ function of the appropriate arity -- (@zipWith@, @zipWith3@, @zipWith4@, ...). For example: diff --git a/libraries/base/Control/Category.hs b/libraries/base/Control/Category.hs index 6407a6f509..37305bff1d 100644 --- a/libraries/base/Control/Category.hs +++ b/libraries/base/Control/Category.hs @@ -30,11 +30,10 @@ infixr 1 >>>, <<< -- | A class for categories. Instances should satisfy the laws -- --- @ --- f '.' 'id' = f -- (right identity) --- 'id' '.' f = f -- (left identity) --- f '.' (g '.' h) = (f '.' g) '.' h -- (associativity) --- @ +-- [Right identity] @f '.' 'id' = f@ +-- [Left identity] @'id' '.' f = f@ +-- [Associativity] @f '.' (g '.' h) = (f '.' g) '.' h@ +-- class Category cat where -- | the identity morphism id :: cat a a diff --git a/libraries/base/Control/Monad/Fix.hs b/libraries/base/Control/Monad/Fix.hs index f287b06541..d9a58485f2 100644 --- a/libraries/base/Control/Monad/Fix.hs +++ b/libraries/base/Control/Monad/Fix.hs @@ -39,17 +39,17 @@ import System.IO -- | Monads having fixed points with a \'knot-tying\' semantics. -- Instances of 'MonadFix' should satisfy the following laws: -- --- [/purity/] +-- [Purity] -- @'mfix' ('Control.Monad.return' . h) = 'Control.Monad.return' ('fix' h)@ -- --- [/left shrinking/ (or /tightening/)] +-- [Left shrinking (or Tightening)] -- @'mfix' (\\x -> a >>= \\y -> f x y) = a >>= \\y -> 'mfix' (\\x -> f x y)@ -- --- [/sliding/] +-- [Sliding] -- @'mfix' ('Control.Monad.liftM' h . f) = 'Control.Monad.liftM' h ('mfix' (f . h))@, -- for strict @h@. -- --- [/nesting/] +-- [Nesting] -- @'mfix' (\\x -> 'mfix' (\\y -> f x y)) = 'mfix' (\\x -> f x x)@ -- -- This class is used in the translation of the recursive @do@ notation diff --git a/libraries/base/Control/Monad/Zip.hs b/libraries/base/Control/Monad/Zip.hs index beef913119..0fada6f5a2 100644 --- a/libraries/base/Control/Monad/Zip.hs +++ b/libraries/base/Control/Monad/Zip.hs @@ -26,19 +26,18 @@ import Data.Proxy import qualified Data.List.NonEmpty as NE import GHC.Generics --- | `MonadZip` type class. Minimal definition: `mzip` or `mzipWith` +-- | Instances should satisfy the laws: -- --- Instances should satisfy the laws: +-- [Naturality] -- --- * Naturality : +-- @'liftM' (f 'Control.Arrow.***' g) ('mzip' ma mb) +-- = 'mzip' ('liftM' f ma) ('liftM' g mb)@ -- --- > liftM (f *** g) (mzip ma mb) = mzip (liftM f ma) (liftM g mb) +-- [Information Preservation] -- --- * Information Preservation: --- --- > liftM (const ()) ma = liftM (const ()) mb --- > ==> --- > munzip (mzip ma mb) = (ma, mb) +-- @'liftM' ('Prelude.const' ()) ma = 'liftM' ('Prelude.const' ()) mb@ +-- implies +-- @'munzip' ('mzip' ma mb) = (ma, mb)@ -- class Monad m => MonadZip m where {-# MINIMAL mzip | mzipWith #-} diff --git a/libraries/base/Data/Bifoldable.hs b/libraries/base/Data/Bifoldable.hs index 4315fdb259..918ddd236c 100644 --- a/libraries/base/Data/Bifoldable.hs +++ b/libraries/base/Data/Bifoldable.hs @@ -78,11 +78,15 @@ import GHC.Generics (K1(..)) -- -- If the type is also a 'Data.Bifunctor.Bifunctor' instance, it should satisfy: -- --- > 'bifoldMap' f g ≡ 'bifold' . 'bimap' f g +-- @ +-- 'bifoldMap' f g ≡ 'bifold' . 'Data.Bifunctor.bimap' f g +-- @ -- -- which implies that -- --- > 'bifoldMap' f g . 'bimap' h i ≡ 'bifoldMap' (f . h) (g . i) +-- @ +-- 'bifoldMap' f g . 'Data.Bifunctor.bimap' h i ≡ 'bifoldMap' (f . h) (g . i) +-- @ -- -- @since 4.10.0.0 class Bifoldable p where diff --git a/libraries/base/Data/Bitraversable.hs b/libraries/base/Data/Bitraversable.hs index cf1272a50f..6df69b93e6 100644 --- a/libraries/base/Data/Bitraversable.hs +++ b/libraries/base/Data/Bitraversable.hs @@ -44,14 +44,14 @@ import GHC.Generics (K1(..)) -- -- A definition of 'bitraverse' must satisfy the following laws: -- --- [/naturality/] +-- [Naturality] -- @'bitraverse' (t . f) (t . g) ≡ t . 'bitraverse' f g@ -- for every applicative transformation @t@ -- --- [/identity/] +-- [Identity] -- @'bitraverse' 'Identity' 'Identity' ≡ 'Identity'@ -- --- [/composition/] +-- [Composition] -- @'Data.Functor.Compose.Compose' . -- 'fmap' ('bitraverse' g1 g2) . -- 'bitraverse' f1 f2 diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs index b8db351257..98acb76967 100644 --- a/libraries/base/Data/Fixed.hs +++ b/libraries/base/Data/Fixed.hs @@ -12,11 +12,12 @@ -- Portability : portable -- -- This module defines a \"Fixed\" type for fixed-precision arithmetic. --- The parameter to Fixed is any type that's an instance of HasResolution. --- HasResolution has a single method that gives the resolution of the Fixed type. +-- The parameter to 'Fixed' is any type that's an instance of 'HasResolution'. +-- 'HasResolution' has a single method that gives the resolution of the 'Fixed' +-- type. -- --- This module also contains generalisations of div, mod, and divmod to work --- with any Real instance. +-- This module also contains generalisations of 'div', 'mod', and 'divMod' to +-- work with any 'Real' instance. -- ----------------------------------------------------------------------------- @@ -42,16 +43,16 @@ import Text.Read.Lex default () -- avoid any defaulting shenanigans --- | generalisation of 'div' to any instance of Real +-- | generalisation of 'div' to any instance of 'Real' div' :: (Real a,Integral b) => a -> a -> b div' n d = floor ((toRational n) / (toRational d)) --- | generalisation of 'divMod' to any instance of Real +-- | generalisation of 'divMod' to any instance of 'Real' divMod' :: (Real a,Integral b) => a -> a -> (b,a) divMod' n d = (f,n - (fromIntegral f) * d) where f = div' n d --- | generalisation of 'mod' to any instance of Real +-- | generalisation of 'mod' to any instance of 'Real' mod' :: (Real a) => a -> a -> a mod' n d = n - (fromInteger f) * d where f = div' n d diff --git a/libraries/base/Data/Functor/Classes.hs b/libraries/base/Data/Functor/Classes.hs index e44c817b64..0ae7b66e7a 100644 --- a/libraries/base/Data/Functor/Classes.hs +++ b/libraries/base/Data/Functor/Classes.hs @@ -752,7 +752,7 @@ showsBinaryWith sp1 sp2 name d x y = showParen (d > 10) $ -- and then parses its argument using 'readsPrec'. -- -- @since 4.9.0.0 -{-# DEPRECATED readsUnary "Use readsUnaryWith to define liftReadsPrec" #-} +{-# DEPRECATED readsUnary "Use 'readsUnaryWith' to define 'liftReadsPrec'" #-} readsUnary :: (Read a) => String -> (a -> t) -> String -> ReadS t readsUnary name cons kw s = [(cons x,t) | kw == name, (x,t) <- readsPrec 11 s] @@ -761,7 +761,7 @@ readsUnary name cons kw s = -- and then parses its argument using 'readsPrec1'. -- -- @since 4.9.0.0 -{-# DEPRECATED readsUnary1 "Use readsUnaryWith to define liftReadsPrec" #-} +{-# DEPRECATED readsUnary1 "Use 'readsUnaryWith' to define 'liftReadsPrec'" #-} readsUnary1 :: (Read1 f, Read a) => String -> (f a -> t) -> String -> ReadS t readsUnary1 name cons kw s = [(cons x,t) | kw == name, (x,t) <- readsPrec1 11 s] @@ -770,7 +770,8 @@ readsUnary1 name cons kw s = -- and then parses its arguments using 'readsPrec1'. -- -- @since 4.9.0.0 -{-# DEPRECATED readsBinary1 "Use readsBinaryWith to define liftReadsPrec" #-} +{-# DEPRECATED readsBinary1 + "Use 'readsBinaryWith' to define 'liftReadsPrec'" #-} readsBinary1 :: (Read1 f, Read1 g, Read a) => String -> (f a -> g a -> t) -> String -> ReadS t readsBinary1 name cons kw s = @@ -781,7 +782,7 @@ readsBinary1 name cons kw s = -- constructor with name @n@ and argument @x@, in precedence context @d@. -- -- @since 4.9.0.0 -{-# DEPRECATED showsUnary "Use showsUnaryWith to define liftShowsPrec" #-} +{-# DEPRECATED showsUnary "Use 'showsUnaryWith' to define 'liftShowsPrec'" #-} showsUnary :: (Show a) => String -> Int -> a -> ShowS showsUnary name d x = showParen (d > 10) $ showString name . showChar ' ' . showsPrec 11 x @@ -790,7 +791,7 @@ showsUnary name d x = showParen (d > 10) $ -- constructor with name @n@ and argument @x@, in precedence context @d@. -- -- @since 4.9.0.0 -{-# DEPRECATED showsUnary1 "Use showsUnaryWith to define liftShowsPrec" #-} +{-# DEPRECATED showsUnary1 "Use 'showsUnaryWith' to define 'liftShowsPrec'" #-} showsUnary1 :: (Show1 f, Show a) => String -> Int -> f a -> ShowS showsUnary1 name d x = showParen (d > 10) $ showString name . showChar ' ' . showsPrec1 11 x @@ -800,7 +801,8 @@ showsUnary1 name d x = showParen (d > 10) $ -- context @d@. -- -- @since 4.9.0.0 -{-# DEPRECATED showsBinary1 "Use showsBinaryWith to define liftShowsPrec" #-} +{-# DEPRECATED showsBinary1 + "Use 'showsBinaryWith' to define 'liftShowsPrec'" #-} showsBinary1 :: (Show1 f, Show1 g, Show a) => String -> Int -> f a -> g a -> ShowS showsBinary1 name d x y = showParen (d > 10) $ diff --git a/libraries/base/Data/Functor/Contravariant.hs b/libraries/base/Data/Functor/Contravariant.hs index 184eee2772..68a9993145 100644 --- a/libraries/base/Data/Functor/Contravariant.hs +++ b/libraries/base/Data/Functor/Contravariant.hs @@ -87,8 +87,8 @@ import Prelude hiding ((.),id) -- -- Any instance should be subject to the following laws: -- --- > contramap id = id --- > contramap f . contramap g = contramap (g . f) +-- [Identity] @'contramap' 'id' = 'id'@ +-- [Composition] @'contramap' (g . f) = 'contramap' f . 'contramap' g@ -- -- Note, that the second law follows from the free theorem of the type of -- 'contramap' and the first law, so you need only check that the former @@ -206,22 +206,11 @@ defaultComparison = Comparison compare -- -- Equivalence relations are expected to satisfy three laws: -- --- __Reflexivity__: --- --- @ --- 'getEquivalence' f a a = True --- @ --- --- __Symmetry__: --- --- @ --- 'getEquivalence' f a b = 'getEquivalence' f b a --- @ --- --- __Transitivity__: --- --- If @'getEquivalence' f a b@ and @'getEquivalence' f b c@ are both 'True' --- then so is @'getEquivalence' f a c@. +-- [Reflexivity]: @'getEquivalence' f a a = True@ +-- [Symmetry]: @'getEquivalence' f a b = 'getEquivalence' f b a@ +-- [Transitivity]: +-- If @'getEquivalence' f a b@ and @'getEquivalence' f b c@ are both 'True' +-- then so is @'getEquivalence' f a c@. -- -- The types alone do not enforce these laws, so you'll have to check them -- yourself. diff --git a/libraries/base/Data/Proxy.hs b/libraries/base/Data/Proxy.hs index 557cc1e4dd..e8f9151fbc 100644 --- a/libraries/base/Data/Proxy.hs +++ b/libraries/base/Data/Proxy.hs @@ -38,7 +38,7 @@ import GHC.Arr -- create one). -- -- Historically, @'Proxy' :: 'Proxy' a@ is a safer alternative to the --- @'undefined :: a'@ idiom. +-- @'undefined' :: a@ idiom. -- -- >>> Proxy :: Proxy (Void, Int -> Int) -- Proxy diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs index 46ca08361b..5b8c6b7901 100644 --- a/libraries/base/Data/STRef.hs +++ b/libraries/base/Data/STRef.hs @@ -42,7 +42,7 @@ import GHC.STRef -- Be warned that 'modifySTRef' does not apply the function strictly. This -- means if the program calls 'modifySTRef' many times, but seldomly uses the -- value, thunks will pile up in memory resulting in a space leak. This is a --- common mistake made when using an STRef as a counter. For example, the +-- common mistake made when using an 'STRef' as a counter. For example, the -- following will leak memory and may produce a stack overflow: -- -- >>> import Control.Monad (replicateM_) diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index 93c42258e2..a8647fdb28 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -76,27 +76,29 @@ import qualified GHC.List as List ( foldr ) -- -- A definition of 'traverse' must satisfy the following laws: -- --- [/naturality/] +-- [Naturality] -- @t . 'traverse' f = 'traverse' (t . f)@ -- for every applicative transformation @t@ -- --- [/identity/] --- @'traverse' Identity = Identity@ +-- [Identity] +-- @'traverse' 'Identity' = 'Identity'@ -- --- [/composition/] --- @'traverse' (Compose . 'fmap' g . f) = Compose . 'fmap' ('traverse' g) . 'traverse' f@ +-- [Composition] +-- @'traverse' ('Data.Functor.Compose.Compose' . 'fmap' g . f) +-- = 'Data.Functor.Compose.Compose' . 'fmap' ('traverse' g) . 'traverse' f@ -- -- A definition of 'sequenceA' must satisfy the following laws: -- --- [/naturality/] +-- [Naturality] -- @t . 'sequenceA' = 'sequenceA' . 'fmap' t@ -- for every applicative transformation @t@ -- --- [/identity/] --- @'sequenceA' . 'fmap' Identity = Identity@ +-- [Identity] +-- @'sequenceA' . 'fmap' 'Identity' = 'Identity'@ -- --- [/composition/] --- @'sequenceA' . 'fmap' Compose = Compose . 'fmap' 'sequenceA' . 'sequenceA'@ +-- [Composition] +-- @'sequenceA' . 'fmap' 'Data.Functor.Compose.Compose' +-- = 'Data.Functor.Compose.Compose' . 'fmap' 'sequenceA' . 'sequenceA'@ -- -- where an /applicative transformation/ is a function -- @@ -104,30 +106,14 @@ import qualified GHC.List as List ( foldr ) -- -- preserving the 'Applicative' operations, i.e. -- --- * @t ('pure' x) = 'pure' x@ --- --- * @t (x '<*>' y) = t x '<*>' t y@ --- --- and the identity functor @Identity@ and composition of functors @Compose@ --- are defined as --- --- > newtype Identity a = Identity a --- > --- > instance Functor Identity where --- > fmap f (Identity x) = Identity (f x) --- > --- > instance Applicative Identity where --- > pure x = Identity x --- > Identity f <*> Identity x = Identity (f x) --- > --- > newtype Compose f g a = Compose (f (g a)) --- > --- > instance (Functor f, Functor g) => Functor (Compose f g) where --- > fmap f (Compose x) = Compose (fmap (fmap f) x) --- > --- > instance (Applicative f, Applicative g) => Applicative (Compose f g) where --- > pure x = Compose (pure (pure x)) --- > Compose f <*> Compose x = Compose ((<*>) <$> f <*> x) +-- @ +-- t ('pure' x) = 'pure' x +-- t (f '<*>' x) = t f '<*>' t x +-- @ +-- +-- and the identity functor 'Identity' and composition functors +-- 'Data.Functor.Compose.Compose' are from "Data.Functor.Identity" and +-- "Data.Functor.Compose". -- -- (The naturality law is implied by parametricity.) -- diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index dfdf23b5f0..f9c9cc23da 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -23,8 +23,8 @@ -- Stability : experimental -- Portability : not portable -- --- Definition of propositional equality @(:~:)@. Pattern-matching on a variable --- of type @(a :~: b)@ produces a proof that @a ~ b@. +-- Definition of propositional equality @(':~:')@. Pattern-matching on a variable +-- of type @(a ':~:' b)@ produces a proof that @a '~' b@. -- -- @since 4.7.0.0 ----------------------------------------------------------------------------- diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 92c8a28465..924a1ff86e 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -213,9 +213,9 @@ infixr 6 <> -- | The class of semigroups (types with an associative binary operation). -- --- Instances should satisfy the associativity law: +-- Instances should satisfy the following: -- --- * @x '<>' (y '<>' z) = (x '<>' y) '<>' z@ +-- [Associativity] @x '<>' (y '<>' z) = (x '<>' y) '<>' z@ -- -- @since 4.9.0.0 class Semigroup a where @@ -247,15 +247,12 @@ class Semigroup a where -- | The class of monoids (types with an associative binary operation that --- has an identity). Instances should satisfy the following laws: +-- has an identity). Instances should satisfy the following: -- --- * @x '<>' 'mempty' = x@ --- --- * @'mempty' '<>' x = x@ --- --- * @x '<>' (y '<>' z) = (x '<>' y) '<>' z@ ('Semigroup' law) --- --- * @'mconcat' = 'foldr' ('<>') 'mempty'@ +-- [Right identity] @x '<>' 'mempty' = x@ +-- [Left identity] @'mempty' '<>' x = x@ +-- [Associativity] @x '<>' (y '<>' z) = (x '<>' y) '<>' z@ ('Semigroup' law) +-- [Concatenation] @'mconcat' = 'foldr' ('<>') 'mempty'@ -- -- The method names refer to the monoid of lists under concatenation, -- but there are many other instances. @@ -446,13 +443,13 @@ instance Monoid a => Monoid (IO a) where {- | A type @f@ is a Functor if it provides a function @fmap@ which, given any types @a@ and @b@ lets you apply any function from @(a -> b)@ to turn an @f a@ into an @f b@, preserving the -structure of @f@. Furthermore @f@ needs to adhere to the following laws: +structure of @f@. Furthermore @f@ needs to adhere to the following: -[/identity/] - @'fmap' 'id' = 'id'@ +[Identity] @'fmap' 'id' == 'id'@ +[Composition] @'fmap' (f . g) == 'fmap' f . 'fmap' g@ -[/composition/] - @'fmap' (f . g) = 'fmap' f . 'fmap' g@ +Note, that the second law follows from the free theorem of the type 'fmap' and +the first law, so you need only check that the former condition holds. -} class Functor f where @@ -480,19 +477,19 @@ class Functor f where -- -- Further, any definition must satisfy the following: -- --- [/identity/] +-- [Identity] -- -- @'pure' 'id' '<*>' v = v@ -- --- [/composition/] +-- [Composition] -- -- @'pure' (.) '<*>' u '<*>' v '<*>' w = u '<*>' (v '<*>' w)@ -- --- [/homomorphism/] +-- [Homomorphism] -- -- @'pure' f '<*>' 'pure' x = 'pure' (f x)@ -- --- [/interchange/] +-- [Interchange] -- -- @u '<*>' 'pure' y = 'pure' ('$' y) '<*>' u@ -- @@ -630,11 +627,11 @@ think of a monad as an /abstract datatype/ of actions. Haskell's @do@ expressions provide a convenient syntax for writing monadic expressions. -Instances of 'Monad' should satisfy the following laws: +Instances of 'Monad' should satisfy the following: -* @'return' a '>>=' k = k a@ -* @m '>>=' 'return' = m@ -* @m '>>=' (\\x -> k x '>>=' h) = (m '>>=' k) '>>=' h@ +[Left identity] @'return' a '>>=' k = k a@ +[Right identity] @m '>>=' 'return' = m@ +[Associativity] @m '>>=' (\\x -> k x '>>=' h) = (m '>>=' k) '>>=' h@ Furthermore, the 'Monad' and 'Applicative' operations should relate as follows: @@ -1315,9 +1312,8 @@ flip f x y = f y x -- It is also useful in higher-order situations, such as @'map' ('$' 0) xs@, -- or @'Data.List.zipWith' ('$') fs xs@. -- --- Note that @($)@ is levity-polymorphic in its result type, so that --- foo $ True where foo :: Bool -> Int# --- is well-typed +-- Note that @('$')@ is levity-polymorphic in its result type, so that +-- @foo '$' True@ where @foo :: Bool -> Int#@ is well-typed. {-# INLINE ($) #-} ($) :: forall r a (b :: TYPE r). (a -> b) -> a -> b f $ x = f x diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs index 3ac9408442..b7d9c1f64c 100644 --- a/libraries/base/GHC/Float.hs +++ b/libraries/base/GHC/Float.hs @@ -71,6 +71,7 @@ infixr 8 ** -- -- * @exp (a + b)@ = @exp a * exp b@ -- * @exp (fromInteger 0)@ = @fromInteger 1@ +-- class (Fractional a) => Floating a where pi :: a exp, log, sqrt :: a -> a diff --git a/libraries/base/GHC/IORef.hs b/libraries/base/GHC/IORef.hs index d04ae728fd..433ac575dc 100644 --- a/libraries/base/GHC/IORef.hs +++ b/libraries/base/GHC/IORef.hs @@ -34,10 +34,10 @@ import GHC.IO -- |A mutable variable in the 'IO' monad newtype IORef a = IORef (STRef RealWorld a) - deriving Eq -- ^ @since 4.2.0.0 + deriving Eq -- ^ Pointer equality. -- - -- @since 4.1.0.0 + -- @since 4.0.0.0 -- |Build a new 'IORef' newIORef :: a -> IO (IORef a) diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs index 063c08910a..2f36439b38 100644 --- a/libraries/base/Text/ParserCombinators/ReadP.hs +++ b/libraries/base/Text/ParserCombinators/ReadP.hs @@ -17,7 +17,7 @@ -- This is a library of parser combinators, originally written by Koen Claessen. -- It parses all alternatives in parallel, so it never keeps hold of -- the beginning of the input string, a common source of space leaks with --- other parsers. The '(+++)' choice combinator is genuinely commutative; +-- other parsers. The @('+++')@ choice combinator is genuinely commutative; -- it makes no difference which branch is \"shorter\". ----------------------------------------------------------------------------- diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs index 177e8f2230..a97a0fd4f0 100644 --- a/libraries/base/Text/Printf.hs +++ b/libraries/base/Text/Printf.hs @@ -14,7 +14,7 @@ -- A C @printf(3)@-like formatter. This version has been -- extended by Bart Massey as per the recommendations of -- John Meacham and Simon Marlow --- \<<http://comments.gmane.org/gmane.comp.lang.haskell.libraries/4726>\> +-- <http://comments.gmane.org/gmane.comp.lang.haskell.libraries/4726> -- to support extensible formatting for new datatypes. It -- has also been extended to support almost all C -- @printf(3)@ syntax. @@ -107,7 +107,7 @@ import System.IO -- hello, 123, 3.1416 -- -- The return value is either 'String' or @('IO' a)@ (which --- should be @('IO' '()')@, but Haskell's type system +-- should be @('IO' ())@, but Haskell's type system -- makes this hard). -- -- The format string consists of ordinary characters and @@ -115,8 +115,8 @@ import System.IO -- one of the arguments to 'printf' in the output string. A -- format specification is introduced by the @%@ character; -- this character can be self-escaped into the format string --- using @%%@. A format specification ends with a /format --- character/ that provides the primary information about +-- using @%%@. A format specification ends with a +-- /format character/ that provides the primary information about -- how to format the value. The rest of the conversion -- specification is optional. In order, one may have flag -- characters, a width specifier, a precision specifier, and @@ -423,7 +423,7 @@ data FormatAdjustment = LeftAdjust | ZeroPad -- @since 4.7.0.0 data FormatSign = SignPlus | SignSpace --- | Description of field formatting for 'formatArg'. See UNIX `printf`(3) +-- | Description of field formatting for 'formatArg'. See UNIX @printf(3)@ -- for a description of how field formatting works. -- -- @since 4.7.0.0 @@ -436,7 +436,7 @@ data FieldFormat = FieldFormat { -- plus sign for positive -- numbers. fmtAlternate :: Bool, -- ^ Indicates an "alternate - -- format". See printf(3) + -- format". See @printf(3)@ -- for the details, which -- vary by argument spec. fmtModifiers :: String, -- ^ Characters that appeared diff --git a/libraries/base/Text/Show/Functions.hs b/libraries/base/Text/Show/Functions.hs index fa2c1e0e37..bfc73cafe1 100644 --- a/libraries/base/Text/Show/Functions.hs +++ b/libraries/base/Text/Show/Functions.hs @@ -15,7 +15,7 @@ -- Optional instance of 'Text.Show.Show' for functions: -- -- > instance Show (a -> b) where --- > showsPrec _ _ = showString \"\<function\>\" +-- > showsPrec _ _ = showString "<function>" -- ----------------------------------------------------------------------------- diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs index 80842a4084..9c03c20a64 100644 --- a/libraries/base/Type/Reflection.hs +++ b/libraries/base/Type/Reflection.hs @@ -16,8 +16,8 @@ -- described by, -- -- * Simon Peyton-Jones, Stephanie Weirich, Richard Eisenberg, --- Dimitrios Vytiniotis. "A reflection on types." /Proc. Philip Wadler's 60th --- birthday Festschrift/, Edinburgh (April 2016). +-- Dimitrios Vytiniotis. "A reflection on types." +-- /Proc. Philip Wadler's 60th birthday Festschrift/, Edinburgh (April 2016). -- -- The interface provides 'I.TypeRep', a type representation which can -- be safely decomposed and composed. See "Data.Dynamic" for an example of this. diff --git a/libraries/base/Unsafe/Coerce.hs b/libraries/base/Unsafe/Coerce.hs index 5bcbb01e1a..86e2d9fd65 100644 --- a/libraries/base/Unsafe/Coerce.hs +++ b/libraries/base/Unsafe/Coerce.hs @@ -20,12 +20,13 @@ -- from compiler to compiler (and version to version). -- -- * Documentation for correct usage in GHC will be found under --- 'unsafeCoerce#' in GHC.Base (around which 'unsafeCoerce' is just a +-- 'unsafeCoerce#' in "GHC.Base" (around which 'unsafeCoerce' is just a -- trivial wrapper). -- --- * In nhc98, the only representation-safe coercions are between Enum --- types with the same range (e.g. Int, Int32, Char, Word32), --- or between a newtype and the type that it wraps. +-- * In nhc98, the only representation-safe coercions are between +-- 'Prelude.Enum' types with the same range (e.g. 'Prelude.Int', +-- 'Data.Int.Int32', 'Prelude.Char', 'Data.Word.Word32'), or between a +-- newtype and the type that it wraps. -- ----------------------------------------------------------------------------- |