summaryrefslogtreecommitdiff
path: root/libraries/base
diff options
context:
space:
mode:
authorAlec Theriault <alec.theriault@gmail.com>2018-08-21 16:05:16 -0400
committerBen Gamari <ben@smart-cactus.org>2018-08-21 18:56:11 -0400
commitddffa0cd8da568c97011007fc6470c61cd4447e5 (patch)
tree99729e70cf2d04acd2377158b47dfe378fcc8e2a /libraries/base
parent14817621aae2d45f8272a36b171b9ccce8763bba (diff)
downloadhaskell-ddffa0cd8da568c97011007fc6470c61cd4447e5.tar.gz
Fix ambiguous/out-of-scope Haddock identifiers
This drastically cuts down on the number of Haddock warnings when making docs for `base`. Plus this means more actual links end up in the docs! Also fixed other small mostly markup issues in the documentation along the way. This is a docs-only change. Reviewers: hvr, bgamari, thomie Reviewed By: thomie Subscribers: thomie, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5055
Diffstat (limited to 'libraries/base')
-rw-r--r--libraries/base/Control/Arrow.hs4
-rw-r--r--libraries/base/Control/Concurrent/Chan.hs4
-rw-r--r--libraries/base/Control/Concurrent/MVar.hs8
-rw-r--r--libraries/base/Control/Exception.hs19
-rw-r--r--libraries/base/Control/Monad.hs4
-rw-r--r--libraries/base/Control/Monad/Fail.hs4
-rw-r--r--libraries/base/Control/Monad/Fix.hs2
-rw-r--r--libraries/base/Control/Monad/ST/Imp.hs2
-rw-r--r--libraries/base/Data/Bifoldable.hs2
-rw-r--r--libraries/base/Data/Bitraversable.hs30
-rw-r--r--libraries/base/Data/Either.hs2
-rw-r--r--libraries/base/Data/Foldable.hs4
-rw-r--r--libraries/base/Data/Function.hs8
-rw-r--r--libraries/base/Data/Functor.hs31
-rw-r--r--libraries/base/Data/Functor/Const.hs4
-rw-r--r--libraries/base/Data/Functor/Contravariant.hs2
-rw-r--r--libraries/base/Data/List.hs4
-rw-r--r--libraries/base/Data/List/NonEmpty.hs2
-rw-r--r--libraries/base/Data/Maybe.hs6
-rw-r--r--libraries/base/Data/Monoid.hs14
-rw-r--r--libraries/base/Data/Traversable.hs4
-rw-r--r--libraries/base/Debug/Trace.hs5
-rw-r--r--libraries/base/Foreign/C/Types.hs11
-rw-r--r--libraries/base/Foreign/Concurrent.hs23
-rw-r--r--libraries/base/GHC/Arr.hs8
-rw-r--r--libraries/base/GHC/Base.hs24
-rw-r--r--libraries/base/GHC/Conc/IO.hs4
-rw-r--r--libraries/base/GHC/Conc/Sync.hs11
-rw-r--r--libraries/base/GHC/Environment.hs8
-rw-r--r--libraries/base/GHC/Event/Internal.hs2
-rw-r--r--libraries/base/GHC/Event/Thread.hs8
-rw-r--r--libraries/base/GHC/Float.hs2
-rw-r--r--libraries/base/GHC/Foreign.hs3
-rw-r--r--libraries/base/GHC/ForeignPtr.hs11
-rw-r--r--libraries/base/GHC/Generics.hs50
-rw-r--r--libraries/base/GHC/IO/BufferedIO.hs4
-rw-r--r--libraries/base/GHC/IO/Device.hs4
-rw-r--r--libraries/base/GHC/IO/Encoding.hs7
-rw-r--r--libraries/base/GHC/IO/Encoding/Failure.hs4
-rw-r--r--libraries/base/GHC/IO/Encoding/Types.hs4
-rw-r--r--libraries/base/GHC/IO/Exception.hs3
-rw-r--r--libraries/base/GHC/IO/Handle.hs44
-rw-r--r--libraries/base/GHC/IO/Handle/FD.hs10
-rw-r--r--libraries/base/GHC/IO/Handle/Text.hs16
-rw-r--r--libraries/base/GHC/IO/Unsafe.hs3
-rw-r--r--libraries/base/GHC/Maybe.hs2
-rw-r--r--libraries/base/GHC/Natural.hs22
-rw-r--r--libraries/base/GHC/Num.hs4
-rw-r--r--libraries/base/GHC/RTS/Flags.hsc32
-rw-r--r--libraries/base/GHC/Real.hs2
-rw-r--r--libraries/base/GHC/ResponseFile.hs2
-rw-r--r--libraries/base/GHC/Stable.hs2
-rw-r--r--libraries/base/GHC/StaticPtr.hs4
-rw-r--r--libraries/base/GHC/TypeLits.hs2
-rw-r--r--libraries/base/GHC/Unicode.hs2
-rw-r--r--libraries/base/System/Exit.hs2
-rw-r--r--libraries/base/System/IO.hs9
-rw-r--r--libraries/base/Type/Reflection.hs2
58 files changed, 262 insertions, 254 deletions
diff --git a/libraries/base/Control/Arrow.hs b/libraries/base/Control/Arrow.hs
index 377870c88c..8d910277a2 100644
--- a/libraries/base/Control/Arrow.hs
+++ b/libraries/base/Control/Arrow.hs
@@ -76,7 +76,7 @@ infixr 1 ^<<, <<^
--
-- * @'first' f >>> 'arr' ('id' *** g) = 'arr' ('id' *** g) >>> 'first' f@
--
--- * @'first' ('first' f) >>> 'arr' 'assoc' = 'arr' 'assoc' >>> 'first' f@
+-- * @'first' ('first' f) >>> 'arr' assoc = 'arr' assoc >>> 'first' f@
--
-- where
--
@@ -209,7 +209,7 @@ instance MonadPlus m => ArrowPlus (Kleisli m) where
--
-- * @'left' f >>> 'arr' ('id' +++ g) = 'arr' ('id' +++ g) >>> 'left' f@
--
--- * @'left' ('left' f) >>> 'arr' 'assocsum' = 'arr' 'assocsum' >>> 'left' f@
+-- * @'left' ('left' f) >>> 'arr' assocsum = 'arr' assocsum >>> 'left' f@
--
-- where
--
diff --git a/libraries/base/Control/Concurrent/Chan.hs b/libraries/base/Control/Concurrent/Chan.hs
index d0fed4a405..874e48a1a1 100644
--- a/libraries/base/Control/Concurrent/Chan.hs
+++ b/libraries/base/Control/Concurrent/Chan.hs
@@ -102,8 +102,8 @@ writeChan (Chan _ writeVar) val = do
-- guarantees of 'MVar's (e.g. threads blocked in this operation are woken up in
-- FIFO order).
--
--- Throws 'BlockedIndefinitelyOnMVar' when the channel is empty and no other
--- thread holds a reference to the channel.
+-- Throws 'Control.Exception.BlockedIndefinitelyOnMVar' when the channel is
+-- empty and no other thread holds a reference to the channel.
readChan :: Chan a -> IO a
readChan (Chan readVar _) = do
modifyMVar readVar $ \read_end -> do
diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs
index fa99361fb1..df28fe8406 100644
--- a/libraries/base/Control/Concurrent/MVar.hs
+++ b/libraries/base/Control/Concurrent/MVar.hs
@@ -33,12 +33,12 @@
--
-- === Applicability
--
--- 'MVar's offer more flexibility than 'IORef's, but less flexibility
--- than 'STM'. They are appropriate for building synchronization
+-- 'MVar's offer more flexibility than 'Data.IORef.IORef's, but less flexibility
+-- than 'GHC.Conc.STM'. They are appropriate for building synchronization
-- primitives and performing simple interthread communication; however
-- they are very simple and susceptible to race conditions, deadlocks or
-- uncaught exceptions. Do not use them if you need perform larger
--- atomic operations such as reading from multiple variables: use 'STM'
+-- atomic operations such as reading from multiple variables: use 'GHC.Conc.STM'
-- instead.
--
-- In particular, the "bigger" functions in this module ('swapMVar',
@@ -70,7 +70,7 @@
--
-- 'MVar' operations are always observed to take place in the order
-- they are written in the program, regardless of the memory model of
--- the underlying machine. This is in contrast to 'IORef' operations
+-- the underlying machine. This is in contrast to 'Data.IORef.IORef' operations
-- which may appear out-of-order to another thread in some cases.
--
-- === Example
diff --git a/libraries/base/Control/Exception.hs b/libraries/base/Control/Exception.hs
index 93ba3d5f91..a84005e536 100644
--- a/libraries/base/Control/Exception.hs
+++ b/libraries/base/Control/Exception.hs
@@ -264,7 +264,7 @@ to write something like
> (\e -> handler)
If you need to unmask asynchronous exceptions again in the exception
-handler, 'restore' can be used there too.
+handler, @restore@ can be used there too.
Note that 'try' and friends /do not/ have a similar default, because
there is no exception handler in this case. Don't use 'try' for
@@ -332,21 +332,24 @@ kind of situation:
The following operations are guaranteed not to be interruptible:
- * operations on 'IORef' from "Data.IORef"
+ * operations on 'Data.IORef.IORef' from "Data.IORef"
- * STM transactions that do not use 'retry'
+ * STM transactions that do not use 'GHC.Conc.retry'
* everything from the @Foreign@ modules
- * everything from @Control.Exception@ except for 'throwTo'
+ * everything from "Control.Exception" except for 'throwTo'
- * @tryTakeMVar@, @tryPutMVar@, @isEmptyMVar@
+ * 'Control.Concurrent.MVar.tryTakeMVar', 'Control.Concurrent.MVar.tryPutMVar',
+ 'Control.Concurrent.MVar.isEmptyMVar'
- * @takeMVar@ if the @MVar@ is definitely full, and conversely @putMVar@ if the @MVar@ is definitely empty
+ * 'Control.Concurrent.MVar.takeMVar' if the 'Control.Concurrent.MVar.MVar' is
+ definitely full, and conversely 'Control.Concurrent.MVar.putMVar' if the
+ 'Control.Concurrent.MVar.MVar' is definitely empty
- * @newEmptyMVar@, @newMVar@
+ * 'Control.Concurrent.MVar.newEmptyMVar', 'Control.Concurrent.MVar.newMVar'
- * @forkIO@, @forkIOUnmasked@, @myThreadId@
+ * 'Control.Concurrent.forkIO', 'Control.Concurrent.myThreadId'
-}
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index dd87418995..08c85a8b9b 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -131,7 +131,7 @@ guard :: (Alternative f) => Bool -> f ()
guard True = pure ()
guard False = empty
--- | This generalizes the list-based 'filter' function.
+-- | This generalizes the list-based 'Data.List.filter' function.
{-# INLINE filterM #-}
filterM :: (Applicative m) => (a -> m Bool) -> [a] -> m [a]
@@ -203,7 +203,7 @@ zipWithM_ :: (Applicative m) => (a -> b -> m c) -> [a] -> [b] -> m ()
{-# INLINE zipWithM_ #-}
zipWithM_ f xs ys = sequenceA_ (zipWith f xs ys)
-{- | The 'foldM' function is analogous to 'foldl', except that its result is
+{- | The 'foldM' function is analogous to 'Data.Foldable.foldl', except that its result is
encapsulated in a monad. Note that 'foldM' works from left-to-right over
the list arguments. This could be an issue where @('>>')@ and the `folded
function' are not commutative.
diff --git a/libraries/base/Control/Monad/Fail.hs b/libraries/base/Control/Monad/Fail.hs
index 91ef3ed349..ecf974bc79 100644
--- a/libraries/base/Control/Monad/Fail.hs
+++ b/libraries/base/Control/Monad/Fail.hs
@@ -50,13 +50,13 @@ import {-# SOURCE #-} GHC.IO (failIO)
-- only a single data constructor, and irrefutable patterns (@~pat@).
--
-- Instances of 'MonadFail' should satisfy the following law: @fail s@ should
--- be a left zero for '>>=',
+-- be a left zero for 'Control.Monad.>>=',
--
-- @
-- fail s >>= f = fail s
-- @
--
--- If your 'Monad' is also 'MonadPlus', a popular definition is
+-- If your 'Monad' is also 'Control.Monad.MonadPlus', a popular definition is
--
-- @
-- fail _ = mzero
diff --git a/libraries/base/Control/Monad/Fix.hs b/libraries/base/Control/Monad/Fix.hs
index a58e2828f3..f287b06541 100644
--- a/libraries/base/Control/Monad/Fix.hs
+++ b/libraries/base/Control/Monad/Fix.hs
@@ -40,7 +40,7 @@ import System.IO
-- Instances of 'MonadFix' should satisfy the following laws:
--
-- [/purity/]
--- @'mfix' ('return' . h) = 'return' ('fix' h)@
+-- @'mfix' ('Control.Monad.return' . h) = 'Control.Monad.return' ('fix' h)@
--
-- [/left shrinking/ (or /tightening/)]
-- @'mfix' (\\x -> a >>= \\y -> f x y) = a >>= \\y -> 'mfix' (\\x -> f x y)@
diff --git a/libraries/base/Control/Monad/ST/Imp.hs b/libraries/base/Control/Monad/ST/Imp.hs
index 4d6b12c119..8ba51e86f0 100644
--- a/libraries/base/Control/Monad/ST/Imp.hs
+++ b/libraries/base/Control/Monad/ST/Imp.hs
@@ -24,7 +24,7 @@ module Control.Monad.ST.Imp (
runST,
fixST,
- -- * Converting 'ST' to 'IO'
+ -- * Converting 'ST' to 'Prelude.IO'
RealWorld, -- abstract
stToIO,
diff --git a/libraries/base/Data/Bifoldable.hs b/libraries/base/Data/Bifoldable.hs
index 1f632e2ff9..4315fdb259 100644
--- a/libraries/base/Data/Bifoldable.hs
+++ b/libraries/base/Data/Bifoldable.hs
@@ -76,7 +76,7 @@ import GHC.Generics (K1(..))
-- 'bifoldr' f g z t ≡ 'appEndo' ('bifoldMap' (Endo . f) (Endo . g) t) z
-- @
--
--- If the type is also a 'Bifunctor' instance, it should satisfy:
+-- If the type is also a 'Data.Bifunctor.Bifunctor' instance, it should satisfy:
--
-- > 'bifoldMap' f g ≡ 'bifold' . 'bimap' f g
--
diff --git a/libraries/base/Data/Bitraversable.hs b/libraries/base/Data/Bitraversable.hs
index 169510844d..4064929890 100644
--- a/libraries/base/Data/Bitraversable.hs
+++ b/libraries/base/Data/Bitraversable.hs
@@ -52,8 +52,11 @@ import GHC.Generics (K1(..))
-- @'bitraverse' 'Identity' 'Identity' ≡ 'Identity'@
--
-- [/composition/]
--- @'Compose' . 'fmap' ('bitraverse' g1 g2) . 'bitraverse' f1 f2
--- ≡ 'traverse' ('Compose' . 'fmap' g1 . f1) ('Compose' . 'fmap' g2 . f2)@
+-- @'Data.Functor.Compose.Compose' .
+-- 'fmap' ('bitraverse' g1 g2) .
+-- 'bitraverse' f1 f2
+-- ≡ 'traverse' ('Data.Functor.Compose.Compose' . 'fmap' g1 . f1)
+-- ('Data.Functor.Compose.Compose' . 'fmap' g2 . f2)@
--
-- where an /applicative transformation/ is a function
--
@@ -66,26 +69,9 @@ import GHC.Generics (K1(..))
-- t (f '<*>' x) = t f '<*>' t x
-- @
--
--- and the identity functor 'Identity' and composition functors 'Compose' are
--- defined as
---
--- > newtype Identity a = Identity { runIdentity :: a }
--- >
--- > instance Functor Identity where
--- > fmap f (Identity x) = Identity (f x)
--- >
--- > instance Applicative Identity where
--- > pure = Identity
--- > 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 = Compose . pure . pure
--- > Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
+-- and the identity functor 'Identity' and composition functors
+-- 'Data.Functor.Compose.Compose' are from "Data.Functor.Identity" and
+-- "Data.Functor.Compose".
--
-- Some simple examples are 'Either' and '(,)':
--
diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs
index 5f23a3edc2..58987a3910 100644
--- a/libraries/base/Data/Either.hs
+++ b/libraries/base/Data/Either.hs
@@ -164,7 +164,7 @@ instance Monad (Either e) where
--
-- We create two values of type @'Either' 'String' 'Int'@, one using the
-- 'Left' constructor and another using the 'Right' constructor. Then
--- we apply \"either\" the 'length' function (if we have a 'String')
+-- we apply \"either\" the 'Prelude.length' function (if we have a 'String')
-- or the \"times-two\" function (if we have an 'Int'):
--
-- >>> let s = Left "foo" :: Either String Int
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 52edeb15bc..441a9be21c 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -172,8 +172,8 @@ class Foldable t where
--
-- Also note that if you want an efficient left-fold, you probably want to
-- use 'foldl'' instead of 'foldl'. The reason for this is that latter does
- -- not force the "inner" results (e.g. @z `f` x1@ in the above example)
- -- before applying them to the operator (e.g. to @(`f` x2)@). This results
+ -- not force the "inner" results (e.g. @z \`f\` x1@ in the above example)
+ -- before applying them to the operator (e.g. to @(\`f\` x2)@). This results
-- in a thunk chain @O(n)@ elements long, which then must be evaluated from
-- the outside-in.
--
diff --git a/libraries/base/Data/Function.hs b/libraries/base/Data/Function.hs
index c54e81facc..7a77160a60 100644
--- a/libraries/base/Data/Function.hs
+++ b/libraries/base/Data/Function.hs
@@ -45,16 +45,18 @@ infixl 1 &
-- 120
--
-- Instead of making a recursive call, we introduce a dummy parameter @rec@;
--- when used within 'fix', this parameter then refers to 'fix'' argument, hence
+-- when used within 'fix', this parameter then refers to 'fix' argument, hence
-- the recursion is reintroduced.
fix :: (a -> a) -> a
fix f = let x = f x in x
--- | @'on' b u x y@ runs the binary function `b` /on/ the results of applying unary function `u` to two arguments `x` and `y`. From the opposite perspective, it transforms two inputs and combines the outputs.
+-- | @'on' b u x y@ runs the binary function @b@ /on/ the results of applying
+-- unary function @u@ to two arguments @x@ and @y@. From the opposite
+-- perspective, it transforms two inputs and combines the outputs.
--
-- @((+) \``on`\` f) x y = f x + f y@
--
--- Typical usage: @'Data.List.sortBy' ('compare' \`on\` 'fst')@.
+-- Typical usage: @'Data.List.sortBy' ('Prelude.compare' \`on\` 'Prelude.fst')@.
--
-- Algebraic properties:
--
diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs
index 4cbfcfcf98..7afcffe05b 100644
--- a/libraries/base/Data/Functor.hs
+++ b/libraries/base/Data/Functor.hs
@@ -57,26 +57,27 @@ infixl 4 <$>
-- | An infix synonym for 'fmap'.
--
--- The name of this operator is an allusion to '$'.
+-- The name of this operator is an allusion to 'Prelude.$'.
-- Note the similarities between their types:
--
-- > ($) :: (a -> b) -> a -> b
-- > (<$>) :: Functor f => (a -> b) -> f a -> f b
--
--- Whereas '$' is function application, '<$>' is function
+-- Whereas 'Prelude.$' is function application, '<$>' is function
-- application lifted over a 'Functor'.
--
-- ==== __Examples__
--
--- Convert from a @'Maybe' 'Int'@ to a @'Maybe' 'String'@ using 'show':
+-- Convert from a @'Data.Maybe.Maybe' 'Data.Int.Int'@ to a @'Data.Maybe.Maybe'
+-- 'Data.String.String'@ using 'Prelude.show':
--
-- >>> show <$> Nothing
-- Nothing
-- >>> show <$> Just 3
-- Just "3"
--
--- Convert from an @'Either' 'Int' 'Int'@ to an @'Either' 'Int'@
--- 'String' using 'show':
+-- Convert from an @'Data.Either.Either' 'Data.Int.Int' 'Data.Int.Int'@ to an
+-- @'Data.Either.Either' 'Data.Int.Int'@ 'Data.String.String' using 'Prelude.show':
--
-- >>> show <$> Left 17
-- Left 17
@@ -88,7 +89,7 @@ infixl 4 <$>
-- >>> (*2) <$> [1,2,3]
-- [2,4,6]
--
--- Apply 'even' to the second element of a pair:
+-- Apply 'Prelude.even' to the second element of a pair:
--
-- >>> even <$> (2,2)
-- (2,True)
@@ -129,27 +130,29 @@ infixl 1 <&>
--
-- ==== __Examples__
--
--- Replace the contents of a @'Maybe' 'Int'@ with a constant 'String':
+-- Replace the contents of a @'Data.Maybe.Maybe' 'Data.Int.Int'@ with a constant
+-- 'Data.String.String':
--
-- >>> 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 @'Data.Either.Either' 'Data.Int.Int' 'Data.Int.Int'@
+-- with a constant 'Data.String.String', resulting in an @'Data.Either.Either'
+-- 'Data.Int.Int' 'Data.String.String'@:
--
-- >>> 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 'Data.String.String':
--
-- >>> [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 'Data.String.String':
--
-- >>> (1,2) $> "foo"
-- (1,"foo")
@@ -162,15 +165,15 @@ infixl 1 <&>
--
-- ==== __Examples__
--
--- Replace the contents of a @'Maybe' 'Int'@ with unit:
+-- Replace the contents of a @'Data.Maybe.Maybe' 'Data.Int.Int'@ with unit:
--
-- >>> 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 @'Data.Either.Either' 'Data.Int.Int' 'Data.Int.Int'@
+-- with unit, resulting in an @'Data.Either.Either' 'Data.Int.Int' '()'@:
--
-- >>> void (Left 8675309)
-- Left 8675309
diff --git a/libraries/base/Data/Functor/Const.hs b/libraries/base/Data/Functor/Const.hs
index 028ae208c3..4e4992dcf6 100644
--- a/libraries/base/Data/Functor/Const.hs
+++ b/libraries/base/Data/Functor/Const.hs
@@ -59,7 +59,7 @@ newtype Const a b = Const { getConst :: a }
)
-- | This instance would be equivalent to the derived instances of the
--- 'Const' newtype if the 'runConst' field were removed
+-- 'Const' newtype if the 'getConst' field were removed
--
-- @since 4.8.0.0
instance Read a => Read (Const a b) where
@@ -67,7 +67,7 @@ instance Read a => Read (Const a b) where
$ \r -> [(Const x,t) | ("Const", s) <- lex r, (x, t) <- readsPrec 11 s]
-- | This instance would be equivalent to the derived instances of the
--- 'Const' newtype if the 'runConst' field were removed
+-- 'Const' newtype if the 'getConst' field were removed
--
-- @since 4.8.0.0
instance Show a => Show (Const a b) where
diff --git a/libraries/base/Data/Functor/Contravariant.hs b/libraries/base/Data/Functor/Contravariant.hs
index 0bfad271bb..184eee2772 100644
--- a/libraries/base/Data/Functor/Contravariant.hs
+++ b/libraries/base/Data/Functor/Contravariant.hs
@@ -103,7 +103,7 @@ class Contravariant f where
(>$) :: b -> f b -> f a
(>$) = contramap . const
--- | If 'f' is both 'Functor' and 'Contravariant' then by the time you factor
+-- | If @f@ is both 'Functor' and 'Contravariant' then by the time you factor
-- in the laws of each of those classes, it can't actually use its argument in
-- any meaningful capacity.
--
diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs
index 2ac04a9165..4b839e954f 100644
--- a/libraries/base/Data/List.hs
+++ b/libraries/base/Data/List.hs
@@ -178,8 +178,8 @@ module Data.List
-- counterpart whose name is suffixed with \`@By@\'.
--
-- It is often convenient to use these functions together with
- -- 'Data.Function.on', for instance @'sortBy' ('compare'
- -- \`on\` 'fst')@.
+ -- 'Data.Function.on', for instance @'sortBy' ('Prelude.compare'
+ -- ``Data.Function.on`` 'Prelude.fst')@.
-- *** User-supplied equality (replacing an @Eq@ context)
-- | The predicate is assumed to define an equivalence.
diff --git a/libraries/base/Data/List/NonEmpty.hs b/libraries/base/Data/List/NonEmpty.hs
index 858a1b063c..61c1f3d414 100644
--- a/libraries/base/Data/List/NonEmpty.hs
+++ b/libraries/base/Data/List/NonEmpty.hs
@@ -380,7 +380,7 @@ groupWith1 f = groupBy1 ((==) `on` f)
groupAllWith1 :: (Ord b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupAllWith1 f = groupWith1 f . sortWith f
--- | The 'isPrefix' function returns @True@ if the first argument is
+-- | The 'isPrefixOf' function returns 'True' if the first argument is
-- a prefix of the second.
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
isPrefixOf [] _ = True
diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs
index 5f5d5ac910..d41ae92672 100644
--- a/libraries/base/Data/Maybe.hs
+++ b/libraries/base/Data/Maybe.hs
@@ -55,7 +55,7 @@ import GHC.Base
-- >>> maybe False odd Nothing
-- False
--
--- Read an integer from a string using 'readMaybe'. If we succeed,
+-- Read an integer from a string using 'Text.Read.readMaybe'. If we succeed,
-- return twice the integer; that is, apply @(*2)@ to it. If instead
-- we fail to parse an integer, return @0@ by default:
--
@@ -65,7 +65,7 @@ import GHC.Base
-- >>> maybe 0 (*2) (readMaybe "")
-- 0
--
--- Apply 'show' to a @Maybe Int@. If we have @Just n@, we want to show
+-- Apply 'Prelude.show' to a @Maybe Int@. If we have @Just n@, we want to show
-- the underlying 'Int' @n@. But if we have 'Nothing', we return the
-- empty string instead of (for example) \"Nothing\":
--
@@ -161,7 +161,7 @@ fromJust (Just x) = x
-- >>> fromMaybe "" Nothing
-- ""
--
--- Read an integer from a string using 'readMaybe'. If we fail to
+-- Read an integer from a string using 'Text.Read.readMaybe'. If we fail to
-- parse an integer, we want to return @0@ by default:
--
-- >>> import Text.Read ( readMaybe )
diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs
index 2fec717288..cf55b2150c 100644
--- a/libraries/base/Data/Monoid.hs
+++ b/libraries/base/Data/Monoid.hs
@@ -91,7 +91,7 @@ import Control.Monad.Fail (MonadFail)
import Data.Semigroup.Internal
-- $MaybeExamples
--- To implement @find@ or @findLast@ on any 'Foldable':
+-- To implement @find@ or @findLast@ on any 'Data.Foldable.Foldable':
--
-- @
-- findLast :: Foldable t => (a -> Bool) -> t a -> Maybe a
@@ -100,20 +100,20 @@ import Data.Semigroup.Internal
-- else Last Nothing)
-- @
--
--- Much of Data.Map's interface can be implemented with
--- Data.Map.alter. Some of the rest can be implemented with a new
--- @alterA@ function and either 'First' or 'Last':
+-- Much of 'Data.Map.Lazy.Map's interface can be implemented with
+-- 'Data.Map.Lazy.alter'. Some of the rest can be implemented with a new
+-- 'Data.Map.Lazy.alterF' function and either 'First' or 'Last':
--
--- > alterA :: (Applicative f, Ord k) =>
+-- > alterF :: (Functor f, Ord k) =>
-- > (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a)
-- >
--- > instance Monoid a => Applicative ((,) a) -- from Control.Applicative
+-- > instance Monoid a => Functor ((,) a) -- from Data.Functor
--
-- @
-- insertLookupWithKey :: Ord k => (k -> v -> v -> v) -> k -> v
-- -> Map k v -> (Maybe v, Map k v)
-- insertLookupWithKey combine key value =
--- Arrow.first getFirst . alterA doChange key
+-- Arrow.first getFirst . 'Data.Map.Lazy.alterF' doChange key
-- where
-- doChange Nothing = (First Nothing, Just value)
-- doChange (Just oldValue) =
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index 5e88dc7dd1..93c42258e2 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -380,14 +380,14 @@ forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
forM = flip mapM
-- |The 'mapAccumL' function behaves like a combination of 'fmap'
--- and 'foldl'; it applies a function to each element of a structure,
+-- and 'Data.Foldable.foldl'; it applies a function to each element of a structure,
-- passing an accumulating parameter from left to right, and returning
-- a final value of this accumulator together with the new structure.
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s
-- |The 'mapAccumR' function behaves like a combination of 'fmap'
--- and 'foldr'; it applies a function to each element of a structure,
+-- and 'Data.Foldable.foldr'; it applies a function to each element of a structure,
-- passing an accumulating parameter from right to left, and returning
-- a final value of this accumulator together with the new structure.
mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs
index 3d49dd22ba..7f40b10156 100644
--- a/libraries/base/Debug/Trace.hs
+++ b/libraries/base/Debug/Trace.hs
@@ -169,8 +169,9 @@ Note that the application of 'traceM' is not an action in the 'Applicative'
context, as 'traceIO' is in the 'IO' type. While the fresh bindings in the
following example will force the 'traceM' expressions to be reduced every time
the @do@-block is executed, @traceM "not crashed"@ would only be reduced once,
-and the message would only be printed once. If your monad is in 'MonadIO',
-@liftIO . traceIO@ may be a better option.
+and the message would only be printed once. If your monad is in
+'Control.Monad.IO.Class.MonadIO', @'Control.Monad.IO.Class.liftIO' . 'traceIO'@
+may be a better option.
>>> :{
do
diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs
index 411327f548..1b18935b9e 100644
--- a/libraries/base/Foreign/C/Types.hs
+++ b/libraries/base/Foreign/C/Types.hs
@@ -37,9 +37,9 @@ module Foreign.C.Types
-- | These types are represented as @newtype@s of
-- types in "Data.Int" and "Data.Word", and are instances of
-- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
- -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
- -- 'Prelude.Bounded', 'Prelude.Real', 'Prelude.Integral' and
- -- 'Bits'.
+ -- 'Prelude.Show', 'Prelude.Enum', 'Data.Typeable.Typeable',
+ -- 'Storable', 'Prelude.Bounded', 'Prelude.Real', 'Prelude.Integral'
+ -- and 'Bits'.
CChar(..), CSChar(..), CUChar(..)
, CShort(..), CUShort(..), CInt(..), CUInt(..)
, CLong(..), CULong(..)
@@ -51,7 +51,8 @@ module Foreign.C.Types
-- | These types are represented as @newtype@s of basic
-- foreign types, and are instances of
-- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
- -- 'Prelude.Show', 'Prelude.Enum', 'Typeable' and 'Storable'.
+ -- 'Prelude.Show', 'Prelude.Enum', 'Data.Typeable.Typeable' and
+ -- 'Storable'.
, CClock(..), CTime(..), CUSeconds(..), CSUSeconds(..)
-- extracted from CTime, because we don't want this comment in
@@ -66,7 +67,7 @@ module Foreign.C.Types
-- | These types are represented as @newtype@s of
-- 'Prelude.Float' and 'Prelude.Double', and are instances of
-- 'Prelude.Eq', 'Prelude.Ord', 'Prelude.Num', 'Prelude.Read',
- -- 'Prelude.Show', 'Prelude.Enum', 'Typeable', 'Storable',
+ -- 'Prelude.Show', 'Prelude.Enum', 'Data.Typeable.Typeable', 'Storable',
-- 'Prelude.Real', 'Prelude.Fractional', 'Prelude.Floating',
-- 'Prelude.RealFrac' and 'Prelude.RealFloat'. That does mean
-- that `CFloat`'s (respectively `CDouble`'s) instances of
diff --git a/libraries/base/Foreign/Concurrent.hs b/libraries/base/Foreign/Concurrent.hs
index a19b20b664..e197f798c3 100644
--- a/libraries/base/Foreign/Concurrent.hs
+++ b/libraries/base/Foreign/Concurrent.hs
@@ -40,33 +40,34 @@ newForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
-- associating a finalizer - given by the monadic operation - with the
-- reference. The storage manager will start the finalizer, in a
-- separate thread, some time after the last reference to the
--- @ForeignPtr@ is dropped. There is no guarantee of promptness, and
+-- 'ForeignPtr' is dropped. There is no guarantee of promptness, and
-- in fact there is no guarantee that the finalizer will eventually
-- run at all.
--
-- Note that references from a finalizer do not necessarily prevent
-- another object from being finalized. If A's finalizer refers to B
--- (perhaps using 'touchForeignPtr', then the only guarantee is that
--- B's finalizer will never be started before A's. If both A and B
--- are unreachable, then both finalizers will start together. See
--- 'touchForeignPtr' for more on finalizer ordering.
+-- (perhaps using 'Foreign.ForeignPtr.touchForeignPtr', then the only
+-- guarantee is that B's finalizer will never be started before A's. If both
+-- A and B are unreachable, then both finalizers will start together. See
+-- 'Foreign.ForeignPtr.touchForeignPtr' for more on finalizer ordering.
--
newForeignPtr = GHC.ForeignPtr.newConcForeignPtr
addForeignPtrFinalizer :: ForeignPtr a -> IO () -> IO ()
--- ^This function adds a finalizer to the given @ForeignPtr@. The
+-- ^This function adds a finalizer to the given 'ForeignPtr'. The
-- finalizer will run /before/ all other finalizers for the same
-- object which have already been registered.
--
--- This is a variant of @Foreign.ForeignPtr.addForeignPtrFinalizer@,
--- where the finalizer is an arbitrary @IO@ action. When it is
+-- This is a variant of 'Foreign.ForeignPtr.addForeignPtrFinalizer',
+-- where the finalizer is an arbitrary 'IO' action. When it is
-- invoked, the finalizer will run in a new thread.
--
-- NB. Be very careful with these finalizers. One common trap is that
-- if a finalizer references another finalized value, it does not
--- prevent that value from being finalized. In particular, 'Handle's
--- are finalized objects, so a finalizer should not refer to a 'Handle'
--- (including @stdout@, @stdin@ or @stderr@).
+-- prevent that value from being finalized. In particular, 'System.IO.Handle's
+-- are finalized objects, so a finalizer should not refer to a
+-- 'System.IO.Handle' (including 'System.IO.stdout', 'System.IO.stdin', or
+-- 'System.IO.stderr').
--
addForeignPtrFinalizer = GHC.ForeignPtr.addForeignPtrConcFinalizer
diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs
index af16355bc1..003d706f88 100644
--- a/libraries/base/GHC/Arr.hs
+++ b/libraries/base/GHC/Arr.hs
@@ -453,13 +453,13 @@ array :: Ix i
-- of the array. These bounds are the lowest and
-- highest indices in the array, in that order.
-- For example, a one-origin vector of length
- -- '10' has bounds '(1,10)', and a one-origin '10'
- -- by '10' matrix has bounds '((1,1),(10,10))'.
+ -- @10@ has bounds @(1,10)@, and a one-origin @10@
+ -- by @10@ matrix has bounds @((1,1),(10,10))@.
-> [(i, e)] -- ^ a list of /associations/ of the form
-- (/index/, /value/). Typically, this list will
-- be expressed as a comprehension. An
- -- association '(i, x)' defines the value of
- -- the array at index 'i' to be 'x'.
+ -- association @(i, x)@ defines the value of
+ -- the array at index @i@ to be @x@.
-> Array i e
array (l,u) ies
= let n = safeRangeSize (l,u)
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index efa8d4666f..1c927405ce 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -222,7 +222,7 @@ class Semigroup a where
-- | An associative operation.
(<>) :: a -> a -> a
- -- | Reduce a non-empty list with @\<\>@
+ -- | Reduce a non-empty list with '<>'
--
-- The default definition should be sufficient, but this can be
-- overridden for efficiency.
@@ -240,7 +240,7 @@ class Semigroup a where
--
-- By making this a member of the class, idempotent semigroups
-- and monoids can upgrade this to execute in /O(1)/ by
- -- picking @stimes = 'stimesIdempotent'@ or @stimes =
+ -- picking @stimes = 'Data.Semigroup.stimesIdempotent'@ or @stimes =
-- 'stimesIdempotentMonoid'@ respectively.
stimes :: Integral b => b -> a -> a
stimes = stimesDefault
@@ -255,7 +255,7 @@ class Semigroup a where
--
-- * @x '<>' (y '<>' z) = (x '<>' y) '<>' z@ ('Semigroup' law)
--
--- * @'mconcat' = 'foldr' '(<>)' 'mempty'@
+-- * @'mconcat' = 'foldr' ('<>') 'mempty'@
--
-- The method names refer to the monoid of lists under concatenation,
-- but there are many other instances.
@@ -263,7 +263,7 @@ class Semigroup a where
-- Some types can be viewed as a monoid in more than one way,
-- e.g. both addition and multiplication on numbers.
-- In such cases we often define @newtype@s and make those instances
--- of 'Monoid', e.g. 'Sum' and 'Product'.
+-- of 'Monoid', e.g. 'Data.Semigroup.Sum' and 'Data.Semigroup.Product'.
--
-- __NOTE__: 'Semigroup' is a superclass of 'Monoid' since /base-4.11.0.0/.
class Semigroup a => Monoid a where
@@ -273,7 +273,7 @@ class Semigroup a => Monoid a where
-- | An associative operation
--
-- __NOTE__: This method is redundant and has the default
- -- implementation @'mappend' = '(<>)'@ since /base-4.11.0.0/.
+ -- implementation @'mappend' = ('<>')@ since /base-4.11.0.0/.
mappend :: a -> a -> a
mappend = (<>)
{-# INLINE mappend #-}
@@ -473,7 +473,7 @@ class Functor f where
--
-- @('<*>') = 'liftA2' 'id'@
--
--- @'liftA2' f x y = f '<$>' x '<*>' y@
+-- @'liftA2' f x y = f 'Prelude.<$>' x '<*>' y@
--
-- Further, any definition must satisfy the following:
--
@@ -669,8 +669,8 @@ class Applicative m => Monad m where
-- failure in a @do@ expression.
--
-- As part of the MonadFail proposal (MFP), this function is moved
- -- to its own class 'MonadFail' (see "Control.Monad.Fail" for more
- -- details). The definition here will be removed in a future
+ -- to its own class 'Control.Monad.MonadFail' (see "Control.Monad.Fail" for
+ -- more details). The definition here will be removed in a future
-- release.
fail :: String -> m a
fail s = errorWithoutStackTrace s
@@ -867,7 +867,7 @@ infixl 3 <|>
-- If defined, 'some' and 'many' should be the least solutions
-- of the equations:
--
--- * @'some' v = (:) '<$>' v '<*>' 'many' v@
+-- * @'some' v = (:) 'Prelude.<$>' v '<*>' 'many' v@
--
-- * @'many' v = 'some' v '<|>' 'pure' []@
class Applicative f => Alternative f where
@@ -1254,8 +1254,8 @@ id x = x
-- The compiler may rewrite it to @('assertError' line)@.
-- | If the first argument evaluates to 'True', then the result is the
--- second argument. Otherwise an 'AssertionFailed' exception is raised,
--- containing a 'String' with the source file and line number of the
+-- second argument. Otherwise an 'Control.Exception.AssertionFailed' exception
+-- is raised, containing a 'String' with the source file and line number of the
-- call to 'assert'.
--
-- Assertions can normally be turned on or off with a compiler flag
@@ -1386,7 +1386,7 @@ unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #))
unIO (IO a) = a
{- |
-Returns the 'tag' of a constructor application; this function is used
+Returns the tag of a constructor application; this function is used
by the deriving code for Eq, Ord and Enum.
The primitive dataToTag# requires an evaluated constructor application
diff --git a/libraries/base/GHC/Conc/IO.hs b/libraries/base/GHC/Conc/IO.hs
index 7e970411e0..7b87adc7ea 100644
--- a/libraries/base/GHC/Conc/IO.hs
+++ b/libraries/base/GHC/Conc/IO.hs
@@ -85,7 +85,7 @@ ioManagerCapabilitiesChanged = return ()
-- | Block the current thread until data is available to read on the
-- given file descriptor (GHC only).
--
--- This will throw an 'IOError' if the file descriptor was closed
+-- This will throw an 'Prelude.IOError' if the file descriptor was closed
-- while this thread was blocked. To safely close a file descriptor
-- that has been used with 'threadWaitRead', use 'closeFdWith'.
threadWaitRead :: Fd -> IO ()
@@ -101,7 +101,7 @@ threadWaitRead fd
-- | Block the current thread until data can be written to the
-- given file descriptor (GHC only).
--
--- This will throw an 'IOError' if the file descriptor was closed
+-- This will throw an 'Prelude.IOError' if the file descriptor was closed
-- while this thread was blocked. To safely close a file descriptor
-- that has been used with 'threadWaitWrite', use 'closeFdWith'.
threadWaitWrite :: Fd -> IO ()
diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs
index 33709d4341..6751de72a8 100644
--- a/libraries/base/GHC/Conc/Sync.hs
+++ b/libraries/base/GHC/Conc/Sync.hs
@@ -543,8 +543,8 @@ data BlockReason
-- ^currently in a foreign call
| BlockedOnOther
-- ^blocked on some other resource. Without @-threaded@,
- -- I\/O and 'threadDelay' show up as 'BlockedOnOther', with @-threaded@
- -- they show up as 'BlockedOnMVar'.
+ -- I\/O and 'Control.Concurrent.threadDelay' show up as
+ -- 'BlockedOnOther', with @-threaded@ they show up as 'BlockedOnMVar'.
deriving ( Eq -- ^ @since 4.3.0.0
, Ord -- ^ @since 4.3.0.0
, Show -- ^ @since 4.3.0.0
@@ -720,8 +720,11 @@ unsafeIOToSTM (IO m) = STM m
--
-- However, there are functions for creating transactional variables that
-- can always be safely called in 'unsafePerformIO'. See: 'newTVarIO',
--- 'newTChanIO', 'newBroadcastTChanIO', 'newTQueueIO', 'newTBQueueIO',
--- and 'newTMVarIO'.
+-- 'Control.Concurrent.STM.TChan.newTChanIO',
+-- 'Control.Concurrent.STM.TChan.newBroadcastTChanIO',
+-- 'Control.Concurrent.STM.TQueue.newTQueueIO',
+-- 'Control.Concurrent.STM.TBQueue.newTBQueueIO', and
+-- 'Control.Concurrent.STM.TMVar.newTMVarIO'.
--
-- Using 'unsafePerformIO' inside of 'atomically' is also dangerous but for
-- different reasons. See 'unsafeIOToSTM' for more on this.
diff --git a/libraries/base/GHC/Environment.hs b/libraries/base/GHC/Environment.hs
index 0270aedf55..4db0837664 100644
--- a/libraries/base/GHC/Environment.hs
+++ b/libraries/base/GHC/Environment.hs
@@ -21,10 +21,10 @@ import qualified GHC.Foreign as GHC
# endif
#endif
--- | Computation 'getFullArgs' is the "raw" version of 'getArgs', similar
--- to @argv@ in other languages. It returns a list of the program's
--- command line arguments, starting with the program name, and
--- including those normally eaten by the RTS (+RTS ... -RTS).
+-- | Computation 'getFullArgs' is the "raw" version of
+-- 'System.Environment.getArgs', similar to @argv@ in other languages. It
+-- returns a list of the program's command line arguments, starting with the
+-- program name, and including those normally eaten by the RTS (+RTS ... -RTS).
getFullArgs :: IO [String]
getFullArgs = do
alloca $ \ p_argc -> do
diff --git a/libraries/base/GHC/Event/Internal.hs b/libraries/base/GHC/Event/Internal.hs
index cb048cd14c..5778c6f3fe 100644
--- a/libraries/base/GHC/Event/Internal.hs
+++ b/libraries/base/GHC/Event/Internal.hs
@@ -216,7 +216,7 @@ delete :: Backend -> IO ()
delete (Backend bState _ _ _ bDelete) = bDelete bState
{-# INLINE delete #-}
--- | Throw an 'IOError' corresponding to the current value of
+-- | Throw an 'Prelude.IOError' corresponding to the current value of
-- 'getErrno' if the result value of the 'IO' action is -1 and
-- 'getErrno' is not 'eINTR'. If the result value is -1 and
-- 'getErrno' returns 'eINTR' 0 is returned. Otherwise the result
diff --git a/libraries/base/GHC/Event/Thread.hs b/libraries/base/GHC/Event/Thread.hs
index d4b679206a..a9d5410d9c 100644
--- a/libraries/base/GHC/Event/Thread.hs
+++ b/libraries/base/GHC/Event/Thread.hs
@@ -72,7 +72,7 @@ registerDelay usecs = do
-- | Block the current thread until data is available to read from the
-- given file descriptor.
--
--- This will throw an 'IOError' if the file descriptor was closed
+-- This will throw an 'Prelude.IOError' if the file descriptor was closed
-- while this thread was blocked. To safely close a file descriptor
-- that has been used with 'threadWaitRead', use 'closeFdWith'.
threadWaitRead :: Fd -> IO ()
@@ -82,7 +82,7 @@ threadWaitRead = threadWait evtRead
-- | Block the current thread until the given file descriptor can
-- accept data to write.
--
--- This will throw an 'IOError' if the file descriptor was closed
+-- This will throw an 'Prelude.IOError' if the file descriptor was closed
-- while this thread was blocked. To safely close a file descriptor
-- that has been used with 'threadWaitWrite', use 'closeFdWith'.
threadWaitWrite :: Fd -> IO ()
@@ -145,7 +145,7 @@ threadWaitSTM evt fd = mask_ $ do
-- The second element of the return value pair is an IO action that can be used
-- to deregister interest in the file descriptor.
--
--- The STM action will throw an 'IOError' if the file descriptor was closed
+-- The STM action will throw an 'Prelude.IOError' if the file descriptor was closed
-- while the STM action is being executed. To safely close a file descriptor
-- that has been used with 'threadWaitReadSTM', use 'closeFdWith'.
threadWaitReadSTM :: Fd -> IO (STM (), IO ())
@@ -157,7 +157,7 @@ threadWaitReadSTM = threadWaitSTM evtRead
-- The second element of the return value pair is an IO action that can be used to deregister
-- interest in the file descriptor.
--
--- The STM action will throw an 'IOError' if the file descriptor was closed
+-- The STM action will throw an 'Prelude.IOError' if the file descriptor was closed
-- while the STM action is being executed. To safely close a file descriptor
-- that has been used with 'threadWaitWriteSTM', use 'closeFdWith'.
threadWaitWriteSTM :: Fd -> IO (STM (), IO ())
diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index 26a5987ee6..7def79e3bb 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -166,7 +166,7 @@ class (RealFrac a, Floating a) => RealFloat a where
decodeFloat :: a -> (Integer,Int)
-- | 'encodeFloat' performs the inverse of 'decodeFloat' in the
-- sense that for finite @x@ with the exception of @-0.0@,
- -- @'uncurry' 'encodeFloat' ('decodeFloat' x) = x@.
+ -- @'Prelude.uncurry' 'encodeFloat' ('decodeFloat' x) = x@.
-- @'encodeFloat' m n@ is one of the two closest representable
-- floating-point numbers to @m*b^^n@ (or @&#177;Infinity@ if overflow
-- occurs); usually the closer, but if @m@ contains too many bits,
diff --git a/libraries/base/GHC/Foreign.hs b/libraries/base/GHC/Foreign.hs
index eb5e853b38..cc985ed5be 100644
--- a/libraries/base/GHC/Foreign.hs
+++ b/libraries/base/GHC/Foreign.hs
@@ -154,7 +154,8 @@ withCStringsLen enc strs f = go [] strs
go cs (s:ss) = withCString enc s $ \c -> go (c:cs) ss
go cs [] = withArrayLen (reverse cs) f
--- | Determines whether a character can be accurately encoded in a 'CString'.
+-- | Determines whether a character can be accurately encoded in a
+-- 'Foreign.C.String.CString'.
--
-- Pretty much anyone who uses this function is in a state of sin because
-- whether or not a character is encodable will, in general, depend on the
diff --git a/libraries/base/GHC/ForeignPtr.hs b/libraries/base/GHC/ForeignPtr.hs
index d80412aac1..6aed677dbb 100644
--- a/libraries/base/GHC/ForeignPtr.hs
+++ b/libraries/base/GHC/ForeignPtr.hs
@@ -153,8 +153,8 @@ mallocForeignPtr :: Storable a => IO (ForeignPtr a)
-- implementation in GHC. It uses pinned memory in the garbage
-- collected heap, so the 'ForeignPtr' does not require a finalizer to
-- free the memory. Use of 'mallocForeignPtr' and associated
--- functions is strongly recommended in preference to 'newForeignPtr'
--- with a finalizer.
+-- functions is strongly recommended in preference to
+-- 'Foreign.ForeignPtr.newForeignPtr' with a finalizer.
--
mallocForeignPtr = doMalloc undefined
where doMalloc :: Storable b => b -> IO (ForeignPtr b)
@@ -289,9 +289,10 @@ addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()
--
-- NB. Be very careful with these finalizers. One common trap is that
-- if a finalizer references another finalized value, it does not
--- prevent that value from being finalized. In particular, 'Handle's
--- are finalized objects, so a finalizer should not refer to a 'Handle'
--- (including @stdout@, @stdin@ or @stderr@).
+-- prevent that value from being finalized. In particular, 'System.IO.Handle's
+-- are finalized objects, so a finalizer should not refer to a
+-- 'System.IO.Handle' (including 'System.IO.stdout', 'System.IO.stdin', or
+-- 'System.IO.stderr').
--
addForeignPtrConcFinalizer (ForeignPtr _ c) finalizer =
addForeignPtrConcFinalizer_ c finalizer
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index 34425f2b5f..c4e09aa198 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -105,7 +105,7 @@ module GHC.Generics (
-- This is a lot of information! However, most of it is actually merely meta-information
-- that makes names of datatypes and constructors and more available on the type level.
--
--- Here is a reduced representation for 'Tree' with nearly all meta-information removed,
+-- Here is a reduced representation for @Tree@ with nearly all meta-information removed,
-- for now keeping only the most essential aspects:
--
-- @
@@ -189,7 +189,7 @@ module GHC.Generics (
--
-- Here, 'R' is a type-level proxy that does not have any associated values.
--
--- There used to be another variant of 'K1' (namely 'Par0'), but it has since
+-- There used to be another variant of 'K1' (namely @Par0@), but it has since
-- been deprecated.
-- *** Meta information: 'M1'
@@ -273,7 +273,7 @@ module GHC.Generics (
-- between the original value and its `Rep`-based representation and then invokes the
-- generic instances.
--
--- As an example, let us look at a function 'encode' that produces a naive, but lossless
+-- As an example, let us look at a function @encode@ that produces a naive, but lossless
-- bit encoding of values of various datatypes. So we are aiming to define a function
--
-- @
@@ -367,18 +367,15 @@ module GHC.Generics (
-- @
--
-- The case for 'K1' is rather interesting. Here, we call the final function
--- 'encode' that we yet have to define, recursively. We will use another type
--- class 'Encode' for that function:
+-- @encode@ that we yet have to define, recursively. We will use another type
+-- class @Encode@ for that function:
--
-- @
-- instance (Encode c) => Encode' ('K1' i c) where
-- encode' ('K1' x) = encode x
-- @
--
--- Note how 'Par0' and 'Rec0' both being mapped to 'K1' allows us to define
--- a uniform instance here.
---
--- Similarly, we can define a uniform instance for 'M1', because we completely
+-- Note how we can define a uniform instance for 'M1', because we completely
-- disregard all meta-information:
--
-- @
@@ -386,13 +383,13 @@ module GHC.Generics (
-- encode' ('M1' x) = encode' x
-- @
--
--- Unlike in 'K1', the instance for 'M1' refers to 'encode'', not 'encode'.
+-- Unlike in 'K1', the instance for 'M1' refers to @encode'@, not @encode@.
-- *** The wrapper and generic default
--
-- |
--
--- We now define class 'Encode' for the actual 'encode' function:
+-- We now define class @Encode@ for the actual @encode@ function:
--
-- @
-- class Encode a where
@@ -401,9 +398,9 @@ module GHC.Generics (
-- encode x = encode' ('from' x)
-- @
--
--- The incoming 'x' is converted using 'from', then we dispatch to the
--- generic instances using 'encode''. We use this as a default definition
--- for 'encode'. We need the 'default encode' signature because ordinary
+-- The incoming @x@ is converted using 'from', then we dispatch to the
+-- generic instances using @encode'@. We use this as a default definition
+-- for @encode@. We need the @default encode@ signature because ordinary
-- Haskell default methods must not introduce additional class constraints,
-- but our generic default does.
--
@@ -421,10 +418,10 @@ module GHC.Generics (
-- possible to use @deriving Encode@ as well, but GHC does not yet support
-- that syntax for this situation.
--
--- Having 'Encode' as a class has the advantage that we can define
+-- Having @Encode@ as a class has the advantage that we can define
-- non-generic special cases, which is particularly useful for abstract
-- datatypes that have no structural representation. For example, given
--- a suitable integer encoding function 'encodeInt', we can define
+-- a suitable integer encoding function @encodeInt@, we can define
--
-- @
-- instance Encode Int where
@@ -457,7 +454,7 @@ module GHC.Generics (
-- any datatype where each constructor has at least one field.
--
-- An 'M1' instance is always required (but it can just ignore the
--- meta-information, as is the case for 'encode' above).
+-- meta-information, as is the case for @encode@ above).
#if 0
-- *** Using meta-information
--
@@ -470,14 +467,15 @@ module GHC.Generics (
-- |
--
-- Datatype-generic functions as defined above work for a large class
--- of datatypes, including parameterized datatypes. (We have used 'Tree'
+-- of datatypes, including parameterized datatypes. (We have used @Tree@
-- as our example above, which is of kind @* -> *@.) However, the
-- 'Generic' class ranges over types of kind @*@, and therefore, the
--- resulting generic functions (such as 'encode') must be parameterized
+-- resulting generic functions (such as @encode@) must be parameterized
-- by a generic type argument of kind @*@.
--
-- What if we want to define generic classes that range over type
--- constructors (such as 'Functor', 'Traversable', or 'Foldable')?
+-- constructors (such as 'Data.Functor.Functor',
+-- 'Data.Traversable.Traversable', or 'Data.Foldable.Foldable')?
-- *** The 'Generic1' class
--
@@ -491,7 +489,7 @@ module GHC.Generics (
-- The 'Generic1' class is also derivable.
--
-- The representation 'Rep1' is ever so slightly different from 'Rep'.
--- Let us look at 'Tree' as an example again:
+-- Let us look at @Tree@ as an example again:
--
-- @
-- data Tree a = Leaf a | Node (Tree a) (Tree a)
@@ -1335,8 +1333,8 @@ instance (SingI mn, SingI su, SingI ss, SingI ds)
-- A 'Generic' instance must satisfy the following laws:
--
-- @
--- 'from' . 'to' ≡ 'id'
--- 'to' . 'from' ≡ 'id'
+-- 'from' . 'to' ≡ 'Prelude.id'
+-- 'to' . 'from' ≡ 'Prelude.id'
-- @
class Generic a where
-- | Generic representation type
@@ -1354,8 +1352,8 @@ class Generic a where
-- A 'Generic1' instance must satisfy the following laws:
--
-- @
--- 'from1' . 'to1' ≡ 'id'
--- 'to1' . 'from1' ≡ 'id'
+-- 'from1' . 'to1' ≡ 'Prelude.id'
+-- 'to1' . 'from1' ≡ 'Prelude.id'
-- @
class Generic1 (f :: k -> Type) where
-- | Generic representation type
@@ -1484,8 +1482,6 @@ deriving instance Generic1 Down
data family Sing (a :: k)
-- | A 'SingI' constraint is essentially an implicitly-passed singleton.
--- If you need to satisfy this constraint with an explicit singleton, please
--- see 'withSingI'.
class SingI (a :: k) where
-- | Produce the singleton explicitly. You will likely need the @ScopedTypeVariables@
-- extension to use this method the way you want.
diff --git a/libraries/base/GHC/IO/BufferedIO.hs b/libraries/base/GHC/IO/BufferedIO.hs
index 4c81d9a4ec..cd38cefe07 100644
--- a/libraries/base/GHC/IO/BufferedIO.hs
+++ b/libraries/base/GHC/IO/BufferedIO.hs
@@ -32,8 +32,8 @@ import GHC.IO.Buffer
-- | The purpose of 'BufferedIO' is to provide a common interface for I/O
-- devices that can read and write data through a buffer. Devices that
-- implement 'BufferedIO' include ordinary files, memory-mapped files,
--- and bytestrings. The underlying device implementing a 'Handle' must
--- provide 'BufferedIO'.
+-- and bytestrings. The underlying device implementing a 'System.IO.Handle'
+-- must provide 'BufferedIO'.
--
class BufferedIO dev where
-- | allocate a new buffer. The size of the buffer is at the
diff --git a/libraries/base/GHC/IO/Device.hs b/libraries/base/GHC/IO/Device.hs
index 1f6304b5d9..e33dcd02b1 100644
--- a/libraries/base/GHC/IO/Device.hs
+++ b/libraries/base/GHC/IO/Device.hs
@@ -56,7 +56,7 @@ class RawIO a where
writeNonBlocking :: a -> Ptr Word8 -> Int -> IO Int
--- | I/O operations required for implementing a 'Handle'.
+-- | I/O operations required for implementing a 'System.IO.Handle'.
class IODevice a where
-- | @ready dev write msecs@ returns 'True' if the device has data
-- to read (if @write@ is 'False') or space to write new data (if
@@ -160,7 +160,7 @@ data IODeviceType
-- -----------------------------------------------------------------------------
-- SeekMode type
--- | A mode that determines the effect of 'hSeek' @hdl mode i@.
+-- | A mode that determines the effect of 'System.IO.hSeek' @hdl mode i@.
data SeekMode
= AbsoluteSeek -- ^ the position of @hdl@ is set to @i@.
| RelativeSeek -- ^ the position of @hdl@ is set to offset @i@
diff --git a/libraries/base/GHC/IO/Encoding.hs b/libraries/base/GHC/IO/Encoding.hs
index daff97e560..b734f00f5b 100644
--- a/libraries/base/GHC/IO/Encoding.hs
+++ b/libraries/base/GHC/IO/Encoding.hs
@@ -57,7 +57,8 @@ import System.IO.Unsafe (unsafePerformIO)
-- | The Latin1 (ISO8859-1) encoding. This encoding maps bytes
-- directly to the first 256 Unicode code points, and is thus not a
-- complete Unicode encoding. An attempt to write a character greater than
--- '\255' to a 'Handle' using the 'latin1' encoding will result in an error.
+-- '\255' to a 'System.IO.Handle' using the 'latin1' encoding will result in an
+-- error.
latin1 :: TextEncoding
latin1 = Latin1.latin1_checked
@@ -122,7 +123,7 @@ getFileSystemEncoding :: IO TextEncoding
-- | The Unicode encoding of the current locale, but where undecodable
-- bytes are replaced with their closest visual match. Used for
--- the 'CString' marshalling functions in "Foreign.C.String"
+-- the 'Foreign.C.String.CString' marshalling functions in "Foreign.C.String"
--
-- @since 4.5.0.0
getForeignEncoding :: IO TextEncoding
@@ -187,7 +188,7 @@ char8 = Latin1.latin1
-- | Look up the named Unicode encoding. May fail with
--
--- * 'isDoesNotExistError' if the encoding is unknown
+-- * 'System.IO.Error.isDoesNotExistError' if the encoding is unknown
--
-- The set of known encodings is system-dependent, but includes at least:
--
diff --git a/libraries/base/GHC/IO/Encoding/Failure.hs b/libraries/base/GHC/IO/Encoding/Failure.hs
index 3047d494ac..c8d29f4d50 100644
--- a/libraries/base/GHC/IO/Encoding/Failure.hs
+++ b/libraries/base/GHC/IO/Encoding/Failure.hs
@@ -34,8 +34,8 @@ import GHC.Real ( fromIntegral )
--import System.Posix.Internals
--- | The 'CodingFailureMode' is used to construct 'TextEncoding's, and
--- specifies how they handle illegal sequences.
+-- | The 'CodingFailureMode' is used to construct 'System.IO.TextEncoding's,
+-- and specifies how they handle illegal sequences.
data CodingFailureMode
= ErrorOnCodingFailure
-- ^ Throw an error when an illegal sequence is encountered
diff --git a/libraries/base/GHC/IO/Encoding/Types.hs b/libraries/base/GHC/IO/Encoding/Types.hs
index d6e00899db..2f8ffd5e59 100644
--- a/libraries/base/GHC/IO/Encoding/Types.hs
+++ b/libraries/base/GHC/IO/Encoding/Types.hs
@@ -103,11 +103,11 @@ type TextEncoder state = BufferCodec CharBufElem Word8 state
-- between sequences of bytes and sequences of Unicode characters.
--
-- For example, UTF-8 is an encoding of Unicode characters into a sequence
--- of bytes. The 'TextEncoding' for UTF-8 is 'utf8'.
+-- of bytes. The 'TextEncoding' for UTF-8 is 'System.IO.utf8'.
data TextEncoding
= forall dstate estate . TextEncoding {
textEncodingName :: String,
- -- ^ a string that can be passed to 'mkTextEncoding' to
+ -- ^ a string that can be passed to 'System.IO.mkTextEncoding' to
-- create an equivalent 'TextEncoding'.
mkTextDecoder :: IO (TextDecoder dstate),
-- ^ Creates a means of decoding bytes into characters: the result must not
diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs
index 7479a4266c..bd9a15216d 100644
--- a/libraries/base/GHC/IO/Exception.hs
+++ b/libraries/base/GHC/IO/Exception.hs
@@ -273,7 +273,8 @@ instance Show ArrayException where
. (if not (null s) then showString ": " . showString s
else id)
--- | The exception thrown when an infinite cycle is detected in 'fixIO'.
+-- | The exception thrown when an infinite cycle is detected in
+-- 'System.IO.fixIO'.
--
-- @since 4.11.0.0
data FixIOException = FixIOException
diff --git a/libraries/base/GHC/IO/Handle.hs b/libraries/base/GHC/IO/Handle.hs
index 648523a11f..01c226dfbd 100644
--- a/libraries/base/GHC/IO/Handle.hs
+++ b/libraries/base/GHC/IO/Handle.hs
@@ -183,7 +183,7 @@ isEOF = hIsEOF stdin
--
-- This operation may fail with:
--
--- * 'isEOFError' if the end of file has been reached.
+-- * 'System.IO.Error.isEOFError' if the end of file has been reached.
hLookAhead :: Handle -> IO Char
hLookAhead handle =
@@ -208,9 +208,9 @@ hLookAhead handle =
--
-- This operation may fail with:
--
--- * 'isPermissionError' if the handle has already been used for reading
--- or writing and the implementation does not allow the buffering mode
--- to be changed.
+-- * 'System.IO.Error.isPermissionError' if the handle has already been used
+-- for reading or writing and the implementation does not allow the
+-- buffering mode to be changed.
hSetBuffering :: Handle -> BufferMode -> IO ()
hSetBuffering handle mode =
@@ -251,8 +251,8 @@ hSetBuffering handle mode =
-- | The action 'hSetEncoding' @hdl@ @encoding@ changes the text encoding
-- for the handle @hdl@ to @encoding@. The default encoding when a 'Handle' is
--- created is 'localeEncoding', namely the default encoding for the current
--- locale.
+-- created is 'System.IO.localeEncoding', namely the default encoding for the
+-- current locale.
--
-- To create a 'Handle' with no encoding at all, use 'openBinaryFile'. To
-- stop further encoding or decoding on an existing 'Handle', use
@@ -295,11 +295,11 @@ hGetEncoding hdl =
--
-- This operation may fail with:
--
--- * 'isFullError' if the device is full;
+-- * 'System.IO.Error.isFullError' if the device is full;
--
--- * 'isPermissionError' if a system resource limit would be exceeded.
--- It is unspecified whether the characters in the buffer are discarded
--- or retained under these circumstances.
+-- * 'System.IO.Error.isPermissionError' if a system resource limit would be
+-- exceeded. It is unspecified whether the characters in the buffer are
+-- discarded or retained under these circumstances.
hFlush :: Handle -> IO ()
hFlush handle = wantWritableHandle "hFlush" handle flushWriteBuffer
@@ -312,14 +312,14 @@ hFlush handle = wantWritableHandle "hFlush" handle flushWriteBuffer
--
-- This operation may fail with:
--
--- * 'isFullError' if the device is full;
+-- * 'System.IO.Error.isFullError' if the device is full;
--
--- * 'isPermissionError' if a system resource limit would be exceeded.
--- It is unspecified whether the characters in the buffer are discarded
--- or retained under these circumstances;
+-- * 'System.IO.Error.isPermissionError' if a system resource limit would be
+-- exceeded. It is unspecified whether the characters in the buffer are
+-- discarded or retained under these circumstances;
--
--- * 'isIllegalOperation' if @hdl@ has buffered read data, and is not
--- seekable.
+-- * 'System.IO.Error.isIllegalOperation' if @hdl@ has buffered read data, and
+-- is not seekable.
hFlushAll :: Handle -> IO ()
hFlushAll handle = withHandle_ "hFlushAll" handle flushBuffer
@@ -358,7 +358,8 @@ hGetPosn handle = do
--
-- This operation may fail with:
--
--- * 'isPermissionError' if a system resource limit would be exceeded.
+-- * 'System.IO.Error.isPermissionError' if a system resource limit would be
+-- exceeded.
hSetPosn :: HandlePosn -> IO ()
hSetPosn (HandlePosn h i) = hSeek h AbsoluteSeek i
@@ -391,10 +392,11 @@ hSetPosn (HandlePosn h i) = hSeek h AbsoluteSeek i
--
-- This operation may fail with:
--
--- * 'isIllegalOperationError' if the Handle is not seekable, or does
--- not support the requested seek mode.
+-- * 'System.IO.Error.isIllegalOperationError' if the Handle is not seekable,
+-- or does not support the requested seek mode.
--
--- * 'isPermissionError' if a system resource limit would be exceeded.
+-- * 'System.IO.Error.isPermissionError' if a system resource limit would be
+-- exceeded.
hSeek :: Handle -> SeekMode -> Integer -> IO ()
hSeek handle mode offset =
@@ -425,7 +427,7 @@ hSeek handle mode offset =
--
-- This operation may fail with:
--
--- * 'isIllegalOperationError' if the Handle is not seekable.
+-- * 'System.IO.Error.isIllegalOperationError' if the Handle is not seekable.
--
hTell :: Handle -> IO Integer
hTell handle =
diff --git a/libraries/base/GHC/IO/Handle/FD.hs b/libraries/base/GHC/IO/Handle/FD.hs
index 786fccc4f1..883bc5fe59 100644
--- a/libraries/base/GHC/IO/Handle/FD.hs
+++ b/libraries/base/GHC/IO/Handle/FD.hs
@@ -128,11 +128,13 @@ addFilePathToIOError fun fp ioe
--
-- This operation may fail with:
--
--- * 'isAlreadyInUseError' if the file is already open and cannot be reopened;
+-- * 'System.IO.Error.isAlreadyInUseError' if the file is already open and
+-- cannot be reopened;
--
--- * 'isDoesNotExistError' if the file does not exist; or
+-- * 'System.IO.Error.isDoesNotExistError' if the file does not exist; or
--
--- * 'isPermissionError' if the user does not have permission to open the file.
+-- * 'System.IO.Error.isPermissionError' if the user does not have permission
+-- to open the file.
--
-- Note: if you will be working with files containing binary data, you'll want to
-- be using 'openBinaryFile'.
@@ -161,7 +163,7 @@ openFileBlocking fp im =
-- this is undesirable; also, as usual under Microsoft operating systems,
-- text mode treats control-Z as EOF. Binary mode turns off all special
-- treatment of end-of-line and end-of-file characters.
--- (See also 'hSetBinaryMode'.)
+-- (See also 'System.IO.hSetBinaryMode'.)
openBinaryFile :: FilePath -> IOMode -> IO Handle
openBinaryFile fp m =
diff --git a/libraries/base/GHC/IO/Handle/Text.hs b/libraries/base/GHC/IO/Handle/Text.hs
index f15c627e07..943d769fb1 100644
--- a/libraries/base/GHC/IO/Handle/Text.hs
+++ b/libraries/base/GHC/IO/Handle/Text.hs
@@ -353,10 +353,10 @@ unpack_nl !buf !r !w acc0
-- list returned by 'hGetContents' @hdl@.
--
-- Any operation that fails because a handle is closed,
--- also fails if a handle is semi-closed. The only exception is 'hClose'.
--- A semi-closed handle becomes closed:
+-- also fails if a handle is semi-closed. The only exception is
+-- 'System.IO.hClose'. A semi-closed handle becomes closed:
--
--- * if 'hClose' is applied to it;
+-- * if 'System.IO.hClose' is applied to it;
--
-- * if an I\/O error occurs when reading an item from the handle;
--
@@ -684,7 +684,7 @@ commitBuffer' raw sz@(I# _) count@(I# _) flush release h_@Handle__{..}
-- 'hPutBuf' ignores any text encoding that applies to the 'Handle',
-- writing the bytes directly to the underlying file or device.
--
--- 'hPutBuf' ignores the prevailing 'TextEncoding' and
+-- 'hPutBuf' ignores the prevailing 'System.IO.TextEncoding' and
-- 'NewlineMode' on the 'Handle', and writes bytes directly.
--
-- This operation may fail with:
@@ -804,7 +804,7 @@ writeChunkNonBlocking h_@Handle__{..} ptr bytes
-- If the handle is a pipe or socket, and the writing end
-- is closed, 'hGetBuf' will behave as if EOF was reached.
--
--- 'hGetBuf' ignores the prevailing 'TextEncoding' and 'NewlineMode'
+-- 'hGetBuf' ignores the prevailing 'System.IO.TextEncoding' and 'NewlineMode'
-- on the 'Handle', and reads bytes directly.
hGetBuf :: Handle -> Ptr a -> Int -> IO Int
@@ -886,8 +886,8 @@ bufReadEmpty h_@Handle__{..}
-- If the handle is a pipe or socket, and the writing end
-- is closed, 'hGetBufSome' will behave as if EOF was reached.
--
--- 'hGetBufSome' ignores the prevailing 'TextEncoding' and 'NewlineMode'
--- on the 'Handle', and reads bytes directly.
+-- 'hGetBufSome' ignores the prevailing 'System.IO.TextEncoding' and
+-- 'NewlineMode' on the 'Handle', and reads bytes directly.
hGetBufSome :: Handle -> Ptr a -> Int -> IO Int
hGetBufSome h ptr count
@@ -928,7 +928,7 @@ haFD h_@Handle__{..} = cast haDevice
-- If the handle is a pipe or socket, and the writing end
-- is closed, 'hGetBufNonBlocking' will behave as if EOF was reached.
--
--- 'hGetBufNonBlocking' ignores the prevailing 'TextEncoding' and
+-- 'hGetBufNonBlocking' ignores the prevailing 'System.IO.TextEncoding' and
-- 'NewlineMode' on the 'Handle', and reads bytes directly.
--
-- NOTE: on Windows, this function does not work correctly; it
diff --git a/libraries/base/GHC/IO/Unsafe.hs b/libraries/base/GHC/IO/Unsafe.hs
index c1c07ae2df..039acfe85b 100644
--- a/libraries/base/GHC/IO/Unsafe.hs
+++ b/libraries/base/GHC/IO/Unsafe.hs
@@ -96,7 +96,8 @@ times (on a multiprocessor), and you should therefore ensure that
it gives the same results each time. It may even happen that one
of the duplicated IO actions is only run partially, and then interrupted
in the middle without an exception being raised. Therefore, functions
-like 'bracket' cannot be used safely within 'unsafeDupablePerformIO'.
+like 'Control.Exception.bracket' cannot be used safely within
+'unsafeDupablePerformIO'.
@since 4.4.0.0
-}
diff --git a/libraries/base/GHC/Maybe.hs b/libraries/base/GHC/Maybe.hs
index 9fcf8b717d..373fd48714 100644
--- a/libraries/base/GHC/Maybe.hs
+++ b/libraries/base/GHC/Maybe.hs
@@ -19,7 +19,7 @@ default ()
-- @'Maybe' a@ either contains a value of type @a@ (represented as @'Just' a@),
-- or it is empty (represented as 'Nothing'). Using 'Maybe' is a good way to
-- deal with errors or exceptional cases without resorting to drastic
--- measures such as 'error'.
+-- measures such as 'Prelude.error'.
--
-- The 'Maybe' type is also a monad. It is a simple kind of error
-- monad, where all errors are represented by 'Nothing'. A richer
diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs
index a35688dcb1..0408ce6423 100644
--- a/libraries/base/GHC/Natural.hs
+++ b/libraries/base/GHC/Natural.hs
@@ -127,7 +127,8 @@ divZeroError = raise# divZeroException
-- >>> 2^20 :: Natural
-- 1267650600228229401496703205376
--
--- Operations whose result would be negative @'throw' ('Underflow' :: 'ArithException')@,
+-- Operations whose result would be negative @'Control.Exception.throw'
+-- ('Control.Exception.Underflow' :: 'Control.Exception.ArithException')@,
--
-- >>> -1 :: Natural
-- *** Exception: arithmetic underflow
@@ -320,7 +321,8 @@ timesNatural (NatJ# x) (NatS# y) = NatJ# (timesBigNatWord x y)
timesNatural (NatJ# x) (NatJ# y) = NatJ# (timesBigNat x y)
{-# CONSTANT_FOLDED timesNatural #-}
--- | 'Natural' subtraction. May @'throw' 'Underflow'@.
+-- | 'Natural' subtraction. May @'Control.Exception.throw'
+-- 'Control.Exception.Underflow'@.
minusNatural :: Natural -> Natural -> Natural
minusNatural x (NatS# 0##) = x
minusNatural (NatS# x) (NatS# y) = case subWordC# x y of
@@ -351,7 +353,7 @@ minusNaturalMaybe (NatJ# x) (NatJ# y)
res = minusBigNat x y
-- | Convert 'BigNat' to 'Natural'.
--- Throws 'Underflow' if passed a 'nullBigNat'.
+-- Throws 'Control.Exception.Underflow' if passed a 'nullBigNat'.
bigNatToNatural :: BigNat -> Natural
bigNatToNatural bn
| isTrue# (sizeofBigNat# bn ==# 1#) = NatS# (bigNatToWord bn)
@@ -393,8 +395,8 @@ wordToNaturalBase w# = NatS# w#
-- | Type representing arbitrary-precision non-negative integers.
--
--- Operations whose result would be negative
--- @'throw' ('Underflow' :: 'ArithException')@.
+-- Operations whose result would be negative @'Control.Exception.throw'
+-- ('Control.Exception.Underflow' :: 'Control.Exception.ArithException')@.
--
-- @since 4.8.0.0
newtype Natural = Natural Integer -- ^ __Invariant__: non-negative 'Integer'
@@ -410,15 +412,15 @@ newtype Natural = Natural Integer -- ^ __Invariant__: non-negative 'Integer'
isValidNatural :: Natural -> Bool
isValidNatural (Natural i) = i >= wordToInteger 0##
--- | Convert a Word# into a Natural
+-- | Convert a 'Word#' into a 'Natural'
--
--- Built-in rule ensures that applications of this function to literal Word# are
--- lifted into Natural literals.
+-- Built-in rule ensures that applications of this function to literal 'Word#'
+-- are lifted into 'Natural' literals.
wordToNatural# :: Word# -> Natural
wordToNatural# w## = Natural (wordToInteger w##)
{-# CONSTANT_FOLDED wordToNatural# #-}
--- | Convert a Word# into a Natural
+-- | Convert a 'Word#' into a Natural
--
-- In base we can't use wordToNatural# as built-in rules transform some of them
-- into Natural literals. Use this function instead.
@@ -598,7 +600,7 @@ mkNatural (W# i : is') = wordToNaturalBase (i `and#` 0xffffffff##) `orNatural`
{-# CONSTANT_FOLDED mkNatural #-}
-- | Convert 'Int' to 'Natural'.
--- Throws 'Underflow' when passed a negative 'Int'.
+-- Throws 'Control.Exception.Underflow' when passed a negative 'Int'.
intToNatural :: Int -> Natural
intToNatural (I# i#)
| isTrue# (i# <# 0#) = underflowError
diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs
index b31d186c90..1fa63fbb00 100644
--- a/libraries/base/GHC/Num.hs
+++ b/libraries/base/GHC/Num.hs
@@ -50,8 +50,8 @@ default () -- Double isn't available yet,
-- @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'
--- and 'Ord' implement an ordered ring. Indeed, in 'base' only 'Integer' and
--- 'Rational' do.
+-- and 'Ord' implement an ordered ring. Indeed, in @base@ only 'Integer' and
+-- 'Data.Ratio.Rational' do.
class Num a where
{-# MINIMAL (+), (*), abs, signum, fromInteger, (negate | (-)) #-}
diff --git a/libraries/base/GHC/RTS/Flags.hsc b/libraries/base/GHC/RTS/Flags.hsc
index 046975577e..12cb828e6a 100644
--- a/libraries/base/GHC/RTS/Flags.hsc
+++ b/libraries/base/GHC/RTS/Flags.hsc
@@ -51,7 +51,7 @@ import GHC.IO
import GHC.Real
import GHC.Show
--- | @'Time'@ is defined as a @'StgWord64'@ in @stg/Types.h@
+-- | 'RtsTime' is defined as a @StgWord64@ in @stg/Types.h@
--
-- @since 4.8.2.0
type RtsTime = Word64
@@ -149,21 +149,21 @@ data MiscFlags = MiscFlags
--
-- @since 4.8.0.0
data DebugFlags = DebugFlags
- { scheduler :: Bool -- ^ 's'
- , interpreter :: Bool -- ^ 'i'
- , weak :: Bool -- ^ 'w'
- , gccafs :: Bool -- ^ 'G'
- , gc :: Bool -- ^ 'g'
- , block_alloc :: Bool -- ^ 'b'
- , sanity :: Bool -- ^ 'S'
- , stable :: Bool -- ^ 't'
- , prof :: Bool -- ^ 'p'
- , linker :: Bool -- ^ 'l' the object linker
- , apply :: Bool -- ^ 'a'
- , stm :: Bool -- ^ 'm'
- , squeeze :: Bool -- ^ 'z' stack squeezing & lazy blackholing
- , hpc :: Bool -- ^ 'c' coverage
- , sparks :: Bool -- ^ 'r'
+ { scheduler :: Bool -- ^ @s@
+ , interpreter :: Bool -- ^ @i@
+ , weak :: Bool -- ^ @w@
+ , gccafs :: Bool -- ^ @G@
+ , gc :: Bool -- ^ @g@
+ , block_alloc :: Bool -- ^ @b@
+ , sanity :: Bool -- ^ @S@
+ , stable :: Bool -- ^ @t@
+ , prof :: Bool -- ^ @p@
+ , linker :: Bool -- ^ @l@ the object linker
+ , apply :: Bool -- ^ @a@
+ , stm :: Bool -- ^ @m@
+ , squeeze :: Bool -- ^ @z@ stack squeezing & lazy blackholing
+ , hpc :: Bool -- ^ @c@ coverage
+ , sparks :: Bool -- ^ @r@
} deriving ( Show -- ^ @since 4.8.0.0
)
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index 00c8cf54b2..c96959f55b 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -190,7 +190,7 @@ class (Real a, Enum a) => Integral a where
-- @x * recip x@ = @recip x * x@ = @fromInteger 1@
--
-- Note that it /isn't/ customarily expected that a type instance of
--- 'Fractional' implement a field. However, all instances in 'base' do.
+-- 'Fractional' implement a field. However, all instances in @base@ do.
class (Num a) => Fractional a where
{-# MINIMAL fromRational, (recip | (/)) #-}
diff --git a/libraries/base/GHC/ResponseFile.hs b/libraries/base/GHC/ResponseFile.hs
index 3c2f64894b..804bd44ff7 100644
--- a/libraries/base/GHC/ResponseFile.hs
+++ b/libraries/base/GHC/ResponseFile.hs
@@ -48,7 +48,7 @@ And a response file @args.txt@:
@
--one 1
---'two' 2
+--\'two\' 2
--"three" 3
@
diff --git a/libraries/base/GHC/Stable.hs b/libraries/base/GHC/Stable.hs
index 516b816fa9..dd585c363b 100644
--- a/libraries/base/GHC/Stable.hs
+++ b/libraries/base/GHC/Stable.hs
@@ -57,7 +57,7 @@ newStablePtr a = IO $ \ s ->
-- |
-- Obtain the Haskell value referenced by a stable pointer, i.e., the
-- same value that was passed to the corresponding call to
--- 'makeStablePtr'. If the argument to 'deRefStablePtr' has
+-- 'newStablePtr'. If the argument to 'deRefStablePtr' has
-- already been freed using 'freeStablePtr', the behaviour of
-- 'deRefStablePtr' is undefined.
--
diff --git a/libraries/base/GHC/StaticPtr.hs b/libraries/base/GHC/StaticPtr.hs
index 34f720dc10..42ca0927dc 100644
--- a/libraries/base/GHC/StaticPtr.hs
+++ b/libraries/base/GHC/StaticPtr.hs
@@ -59,7 +59,7 @@ import GHC.Word (Word64(..))
#include "MachDeps.h"
--- | A reference to a value of type 'a'.
+-- | A reference to a value of type @a@.
#if WORD_SIZE_IN_BITS < 64
data StaticPtr a = StaticPtr Word64# Word64# -- The flattened Fingerprint is
-- convenient in the compiler.
@@ -72,7 +72,7 @@ data StaticPtr a = StaticPtr Word# Word#
deRefStaticPtr :: StaticPtr a -> a
deRefStaticPtr (StaticPtr _ _ _ v) = v
--- | A key for `StaticPtrs` that can be serialized and used with
+-- | A key for 'StaticPtr's that can be serialized and used with
-- 'unsafeLookupStaticPtr'.
type StaticKey = Fingerprint
diff --git a/libraries/base/GHC/TypeLits.hs b/libraries/base/GHC/TypeLits.hs
index ba0ce974b2..7e3e514be9 100644
--- a/libraries/base/GHC/TypeLits.hs
+++ b/libraries/base/GHC/TypeLits.hs
@@ -153,7 +153,7 @@ data {-kind-} ErrorMessage = Text Symbol
infixl 5 :$$:
infixl 6 :<>:
--- | The type-level equivalent of 'error'.
+-- | The type-level equivalent of 'Prelude.error'.
--
-- The polymorphic kind of this type allows it to be used in several settings.
-- For instance, it can be used as a constraint, e.g. to provide a better error
diff --git a/libraries/base/GHC/Unicode.hs b/libraries/base/GHC/Unicode.hs
index df7c978904..6d453cbc9a 100644
--- a/libraries/base/GHC/Unicode.hs
+++ b/libraries/base/GHC/Unicode.hs
@@ -71,7 +71,7 @@ import GHC.Show ( Show )
-- >>> enumFromTo ModifierLetter SpacingCombiningMark
-- [ModifierLetter,OtherLetter,NonSpacingMark,SpacingCombiningMark]
--
--- 'Read' instance:
+-- 'Text.Read.Read' instance:
--
-- >>> read "DashPunctuation" :: GeneralCategory
-- DashPunctuation
diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs
index 4f73665c0e..e4f7b13e33 100644
--- a/libraries/base/System/Exit.hs
+++ b/libraries/base/System/Exit.hs
@@ -47,7 +47,7 @@ import GHC.IO.Exception
--
-- As an 'ExitCode' is not an 'IOError', 'exitWith' bypasses
-- the error handling in the 'IO' monad and cannot be intercepted by
--- 'catch' from the "Prelude". However it is a 'SomeException', and can
+-- 'catch' from the "Prelude". However it is a 'Control.Exception.SomeException', and can
-- be caught using the functions of "Control.Exception". This means
-- that cleanup computations added with 'Control.Exception.bracket'
-- (from "Control.Exception") are also executed properly on 'exitWith'.
diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs
index 4a9b8837ab..900963a045 100644
--- a/libraries/base/System/IO.hs
+++ b/libraries/base/System/IO.hs
@@ -381,7 +381,8 @@ hReady h = hWaitForInput h 0
--
-- * 'System.IO.Error.isFullError' if the device is full; or
--
--- * 'System.IO.Error.isPermissionError' if another system resource limit would be exceeded.
+-- * 'System.IO.Error.isPermissionError' if another system resource limit
+-- would be exceeded.
hPrint :: Show a => Handle -> a -> IO ()
hPrint hdl = hPutStrLn hdl . show
@@ -391,7 +392,7 @@ hPrint hdl = hPutStrLn hdl . show
-- closed on exit from 'withFile', whether by normal termination or by
-- raising an exception. If closing the handle raises an exception, then
-- this exception will be raised by 'withFile' rather than any exception
--- raised by 'act'.
+-- raised by @act@.
withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile name mode = bracket (openFile name mode) hClose
@@ -405,8 +406,8 @@ withBinaryFile name mode = bracket (openBinaryFile name mode) hClose
-- ---------------------------------------------------------------------------
-- fixIO
--- | The implementation of 'mfix' for 'IO'. If the function passed
--- to 'fixIO' inspects its argument, the resulting action will throw
+-- | The implementation of 'Control.Monad.Fix.mfix' for 'IO'. If the function
+-- passed to 'fixIO' inspects its argument, the resulting action will throw
-- 'FixIOException'.
fixIO :: (a -> IO a) -> IO a
fixIO k = do
diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs
index 9e87c5f73b..80842a4084 100644
--- a/libraries/base/Type/Reflection.hs
+++ b/libraries/base/Type/Reflection.hs
@@ -19,7 +19,7 @@
-- Dimitrios Vytiniotis. "A reflection on types." /Proc. Philip Wadler's 60th
-- birthday Festschrift/, Edinburgh (April 2016).
--
--- The interface provides 'TypeRep', a type representation which can
+-- The interface provides 'I.TypeRep', a type representation which can
-- be safely decomposed and composed. See "Data.Dynamic" for an example of this.
--
-- @since 4.10.0.0