Skip to content

Commit

Permalink
Fix broken Haddock links
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
pgujjula authored and andrewthad committed May 21, 2024
1 parent 16421ca commit 4391040
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 18 deletions.
4 changes: 2 additions & 2 deletions Control/Monad/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -239,14 +239,14 @@ instance PrimBase (L.ST s) where
{-# INLINE internal #-}
#endif

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

-- | 'PrimBase''s state token type can be annoying to handle
-- | 'PrimBase'\'s state token type can be annoying to handle
-- in constraints. This typeclass lets users (visually) notice
-- 'PrimState' equality constraints less, by witnessing that
-- @s ~ 'PrimState' m@.
Expand Down
8 changes: 5 additions & 3 deletions Data/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,9 +65,11 @@ the behaviors of the 'Applicative' and 'Control.Monad.Primitive.PrimMonad'
variants produce the same results and differ only in their strictness.
Monads that are sufficiently affine include:
* 'IO' and 'ST'
* Any combination of 'MaybeT', 'ExceptT', 'StateT' and 'Writer' on top
of another sufficiently affine monad.
* 'IO' and 'Control.Monad.ST'
* Any combination of 'Control.Monad.Trans.Maybe.MaybeT',
'Control.Monad.Trans.Except.ExceptT', 'Control.Monad.Trans.State.Lazy.StateT'
and 'Control.Monad.Trans.Writer.Lazy.WriterT' on top of another sufficiently
affine monad.
* Any Monad which does not include backtracking or other mechanisms where an effect can
happen more than once is an affine Monad in the sense we care about. @ContT@, @LogicT@, @ListT@ are all
examples of search/control monads which are NOT affine: they can run a sub computation more than once.
Expand Down
24 changes: 13 additions & 11 deletions Data/Primitive/PrimArray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -138,10 +138,10 @@ import qualified GHC.Exts as Exts
import Data.Primitive.Internal.Operations (mutableByteArrayContentsShim)

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

type role PrimArray nominal
Expand Down Expand Up @@ -391,7 +391,7 @@ copyPrimArray (MutablePrimArray dst#) (I# doff#) (PrimArray src#) (I# soff#) (I#
-- | Copy a slice of an immutable primitive array to a pointer.
-- The offset and length are given in elements of type @a@.
-- This function assumes that the 'Prim' instance of @a@
-- agrees with the 'Storable' instance.
-- agrees with the 'Foreign.Storable.Storable' instance.
--
-- /Note:/ this function does not do bounds or overlap checking.
copyPrimArrayToPtr :: forall m a. (PrimMonad m, Prim a)
Expand All @@ -410,7 +410,7 @@ copyPrimArrayToPtr (Ptr addr#) (PrimArray ba#) (I# soff#) (I# n#) =
-- | Copy a slice of a mutable primitive array to a pointer.
-- The offset and length are given in elements of type @a@.
-- This function assumes that the 'Prim' instance of @a@
-- agrees with the 'Storable' instance.
-- agrees with the 'Foreign.Storable.Storable' instance.
--
-- /Note:/ this function does not do bounds or overlap checking.
copyMutablePrimArrayToPtr :: forall m a. (PrimMonad m, Prim a)
Expand All @@ -429,7 +429,7 @@ copyMutablePrimArrayToPtr (Ptr addr#) (MutablePrimArray mba#) (I# soff#) (I# n#)
-- | Copy from a pointer to a mutable primitive array.
-- The offset and length are given in elements of type @a@.
-- This function assumes that the 'Prim' instance of @a@
-- agrees with the 'Storable' instance.
-- agrees with the 'Foreign.Storable.Storable' instance.
--
-- /Note:/ this function does not do bounds or overlap checking.
copyPtrToMutablePrimArray :: forall m a. (PrimMonad m, Prim a)
Expand Down Expand Up @@ -1095,17 +1095,19 @@ newAlignedPinnedPrimArray (I# n#)
(# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #))

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

-- | Yield a pointer to the array's data. This operation is only safe on
-- /pinned/ byte arrays allocated by 'newPinnedByteArray' or
-- 'newAlignedPinnedByteArray'.
-- /pinned/ byte arrays allocated by
-- 'Data.Primitive.ByteArray.newPinnedByteArray' or
-- 'Data.Primitive.ByteArray.newAlignedPinnedByteArray'.
--
-- @since 0.7.1.0
mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a
Expand Down
4 changes: 2 additions & 2 deletions Data/Primitive/SmallArray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -191,12 +191,12 @@ writeSmallArray (SmallMutableArray sma#) (I# i#) x =
-- > f sa = case indexSmallArrayM sa 0 of
-- > Box x -> ...
--
-- 'x' is not a closure that references 'sa' as it would be if we instead
-- @x@ is not a closure that references @sa@ as it would be if we instead
-- wrote:
--
-- > let x = indexSmallArray sa 0
--
-- It also does not prevent 'sa' from being garbage collected.
-- It also does not prevent @sa@ from being garbage collected.
--
-- Note that 'Identity' is not adequate for this use, as it is a newtype, and
-- cannot be evaluated without evaluating the element.
Expand Down

0 comments on commit 4391040

Please sign in to comment.