Skip to content

Commit 4391040

Browse files
pgujjulaandrewthad
authored andcommitted
Fix broken Haddock links
Fix all broken Haddock links. Now Haddock doesn't emit any warnings about out-of-scope identifiers. Warnings about unknown link destinations are more complicated to resolve and are not handled in this commit.
1 parent 16421ca commit 4391040

File tree

4 files changed

+22
-18
lines changed

4 files changed

+22
-18
lines changed

Control/Monad/Primitive.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -239,14 +239,14 @@ instance PrimBase (L.ST s) where
239239
{-# INLINE internal #-}
240240
#endif
241241

242-
-- | 'PrimMonad''s state token type can be annoying to handle
242+
-- | 'PrimMonad'\'s state token type can be annoying to handle
243243
-- in constraints. This typeclass lets users (visually) notice
244244
-- 'PrimState' equality constraints less, by witnessing that
245245
-- @s ~ 'PrimState' m@.
246246
class (PrimMonad m, s ~ PrimState m) => MonadPrim s m
247247
instance (PrimMonad m, s ~ PrimState m) => MonadPrim s m
248248

249-
-- | 'PrimBase''s state token type can be annoying to handle
249+
-- | 'PrimBase'\'s state token type can be annoying to handle
250250
-- in constraints. This typeclass lets users (visually) notice
251251
-- 'PrimState' equality constraints less, by witnessing that
252252
-- @s ~ 'PrimState' m@.

Data/Primitive.hs

+5-3
Original file line numberDiff line numberDiff line change
@@ -65,9 +65,11 @@ the behaviors of the 'Applicative' and 'Control.Monad.Primitive.PrimMonad'
6565
variants produce the same results and differ only in their strictness.
6666
Monads that are sufficiently affine include:
6767
68-
* 'IO' and 'ST'
69-
* Any combination of 'MaybeT', 'ExceptT', 'StateT' and 'Writer' on top
70-
of another sufficiently affine monad.
68+
* 'IO' and 'Control.Monad.ST'
69+
* Any combination of 'Control.Monad.Trans.Maybe.MaybeT',
70+
'Control.Monad.Trans.Except.ExceptT', 'Control.Monad.Trans.State.Lazy.StateT'
71+
and 'Control.Monad.Trans.Writer.Lazy.WriterT' on top of another sufficiently
72+
affine monad.
7173
* Any Monad which does not include backtracking or other mechanisms where an effect can
7274
happen more than once is an affine Monad in the sense we care about. @ContT@, @LogicT@, @ListT@ are all
7375
examples of search/control monads which are NOT affine: they can run a sub computation more than once.

Data/Primitive/PrimArray.hs

+13-11
Original file line numberDiff line numberDiff line change
@@ -138,10 +138,10 @@ import qualified GHC.Exts as Exts
138138
import Data.Primitive.Internal.Operations (mutableByteArrayContentsShim)
139139

140140
-- | Arrays of unboxed elements. This accepts types like 'Double', 'Char',
141-
-- 'Int' and 'Word', as well as their fixed-length variants ('Word8',
142-
-- 'Word16', etc.). Since the elements are unboxed, a 'PrimArray' is strict
143-
-- in its elements. This differs from the behavior of 'Data.Primitive.Array.Array',
144-
-- which is lazy in its elements.
141+
-- 'Int' and 'Word', as well as their fixed-length variants ('Data.Word.Word8',
142+
-- 'Data.Word.Word16', etc.). Since the elements are unboxed, a 'PrimArray' is
143+
-- strict in its elements. This differs from the behavior of
144+
-- 'Data.Primitive.Array.Array', which is lazy in its elements.
145145
data PrimArray a = PrimArray ByteArray#
146146

147147
type role PrimArray nominal
@@ -391,7 +391,7 @@ copyPrimArray (MutablePrimArray dst#) (I# doff#) (PrimArray src#) (I# soff#) (I#
391391
-- | Copy a slice of an immutable primitive array to a pointer.
392392
-- The offset and length are given in elements of type @a@.
393393
-- This function assumes that the 'Prim' instance of @a@
394-
-- agrees with the 'Storable' instance.
394+
-- agrees with the 'Foreign.Storable.Storable' instance.
395395
--
396396
-- /Note:/ this function does not do bounds or overlap checking.
397397
copyPrimArrayToPtr :: forall m a. (PrimMonad m, Prim a)
@@ -410,7 +410,7 @@ copyPrimArrayToPtr (Ptr addr#) (PrimArray ba#) (I# soff#) (I# n#) =
410410
-- | Copy a slice of a mutable primitive array to a pointer.
411411
-- The offset and length are given in elements of type @a@.
412412
-- This function assumes that the 'Prim' instance of @a@
413-
-- agrees with the 'Storable' instance.
413+
-- agrees with the 'Foreign.Storable.Storable' instance.
414414
--
415415
-- /Note:/ this function does not do bounds or overlap checking.
416416
copyMutablePrimArrayToPtr :: forall m a. (PrimMonad m, Prim a)
@@ -429,7 +429,7 @@ copyMutablePrimArrayToPtr (Ptr addr#) (MutablePrimArray mba#) (I# soff#) (I# n#)
429429
-- | Copy from a pointer to a mutable primitive array.
430430
-- The offset and length are given in elements of type @a@.
431431
-- This function assumes that the 'Prim' instance of @a@
432-
-- agrees with the 'Storable' instance.
432+
-- agrees with the 'Foreign.Storable.Storable' instance.
433433
--
434434
-- /Note:/ this function does not do bounds or overlap checking.
435435
copyPtrToMutablePrimArray :: forall m a. (PrimMonad m, Prim a)
@@ -1095,17 +1095,19 @@ newAlignedPinnedPrimArray (I# n#)
10951095
(# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #))
10961096

10971097
-- | Yield a pointer to the array's data. This operation is only safe on
1098-
-- /pinned/ prim arrays allocated by 'newPinnedByteArray' or
1099-
-- 'newAlignedPinnedByteArray'.
1098+
-- /pinned/ prim arrays allocated by
1099+
-- 'Data.Primitive.ByteArray.newPinnedByteArray' or
1100+
-- 'Data.Primitive.ByteArray.newAlignedPinnedByteArray'.
11001101
--
11011102
-- @since 0.7.1.0
11021103
primArrayContents :: PrimArray a -> Ptr a
11031104
{-# INLINE primArrayContents #-}
11041105
primArrayContents (PrimArray arr#) = Ptr (byteArrayContents# arr#)
11051106

11061107
-- | Yield a pointer to the array's data. This operation is only safe on
1107-
-- /pinned/ byte arrays allocated by 'newPinnedByteArray' or
1108-
-- 'newAlignedPinnedByteArray'.
1108+
-- /pinned/ byte arrays allocated by
1109+
-- 'Data.Primitive.ByteArray.newPinnedByteArray' or
1110+
-- 'Data.Primitive.ByteArray.newAlignedPinnedByteArray'.
11091111
--
11101112
-- @since 0.7.1.0
11111113
mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a

Data/Primitive/SmallArray.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -191,12 +191,12 @@ writeSmallArray (SmallMutableArray sma#) (I# i#) x =
191191
-- > f sa = case indexSmallArrayM sa 0 of
192192
-- > Box x -> ...
193193
--
194-
-- 'x' is not a closure that references 'sa' as it would be if we instead
194+
-- @x@ is not a closure that references @sa@ as it would be if we instead
195195
-- wrote:
196196
--
197197
-- > let x = indexSmallArray sa 0
198198
--
199-
-- It also does not prevent 'sa' from being garbage collected.
199+
-- It also does not prevent @sa@ from being garbage collected.
200200
--
201201
-- Note that 'Identity' is not adequate for this use, as it is a newtype, and
202202
-- cannot be evaluated without evaluating the element.

0 commit comments

Comments
 (0)