Fix some haddock markup and since annotations

This commit is contained in:
Harendra Kumar 2021-06-03 00:11:43 +05:30
parent 8072636a12
commit 8b071538e4
4 changed files with 23 additions and 18 deletions

View File

@ -389,7 +389,7 @@ transform (Pipe pstep1 pstep2 pinitial) (Fold fstep finitial fextract) =
-- Drain all input after passing it through a monadic function. This is the
-- dual of mapM_ on stream producers.
--
-- See also: "Streamly.Prelude.mapM_"
-- See also: 'Streamly.Prelude.mapM_'
--
-- @since 0.7.0
{-# INLINABLE drainBy #-}
@ -754,7 +754,7 @@ genericIndex i = mkFold step (Partial 0) (const Nothing)
-- | Lookup the element at the given index.
--
-- See also: "Streamly.Prelude.!!"
-- See also: 'Streamly.Prelude.!!'
--
-- @since 0.7.0
{-# INLINABLE index #-}

View File

@ -363,7 +363,7 @@ mapMStep f res =
-- NOTE: The constructor is not yet exposed via exposed modules, smart
-- constructors are provided to create folds. If you think you need the
-- constructor of this type please consider using the smart constructors in
-- "Streamly.Internal.Data.Fold' instead.
-- "Streamly.Internal.Data.Fold" instead.
--
-- /since 0.8.0 (type changed)/
--
@ -406,7 +406,7 @@ rmapM f (Fold step initial extract) = Fold step1 initial1 (extract >=> f)
-- mkfoldlx step initial extract = fmap extract (foldl' step initial)
-- @
--
-- See also: "Streamly.Prelude.foldl'"
-- See also: @Streamly.Prelude.foldl'@
--
-- @since 0.8.0
--
@ -428,7 +428,7 @@ foldl' step initial =
-- mkFoldlxM step initial extract = rmapM extract (foldlM' step initial)
-- @
--
-- See also: "Streamly.Prelude.foldlM'"
-- See also: @Streamly.Prelude.foldlM'@
--
-- @since 0.8.0
--
@ -440,7 +440,7 @@ foldlM' step initial =
-- | Make a strict left fold, for non-empty streams, using first element as the
-- starting value. Returns Nothing if the stream is empty.
--
-- See also: "Streamly.Prelude.foldl1'"
-- See also: @Streamly.Prelude.foldl1'@
--
-- /Pre-release/
{-# INLINE foldl1' #-}
@ -465,7 +465,7 @@ foldl1' step = fmap toMaybe $ foldl' step1 Nothing'
--
-- > toList = foldr (:) []
--
-- See also: "Streamly.Prelude.foldr"
-- See also: 'Streamly.Prelude.foldr'
--
-- @since 0.8.0
{-# INLINE foldr #-}
@ -481,7 +481,7 @@ foldr g z = fmap ($ z) $ foldl' (\f x -> f . g x) id
--
-- > toList = foldrM (\a xs -> return $ a : xs) (return [])
--
-- See also: "Streamly.Prelude.foldrM"
-- See also: 'Streamly.Prelude.foldrM'
--
-- /Pre-release/
{-# INLINE foldrM #-}
@ -851,7 +851,7 @@ data ConcatMapState m sa a c
--
-- /Time: O(n^2) where @n@ is the number of compositions./
--
-- See also: "Streamly.Internal.Data.Stream.IsStream.foldIterateM"
-- See also: 'Streamly.Internal.Data.Stream.IsStream.foldIterateM'
--
-- @since 0.8.0
--
@ -1081,7 +1081,7 @@ data ManyState s1 s2
--
-- Stops when @collect@ stops.
--
-- See also: "Streamly.Prelude.concatMap", "Streamly.Prelude.foldMany"
-- See also: 'Streamly.Prelude.concatMap', 'Streamly.Prelude.foldMany'
--
-- @since 0.8.0
--
@ -1143,7 +1143,7 @@ many (Fold sstep sinitial sextract) (Fold cstep cinitial cextract) =
--
-- /Internal/
--
-- /See also: Streamly.Prelude.concatMap, Streamly.Prelude.foldMany/
-- /See also: 'Streamly.Prelude.concatMap', 'Streamly.Prelude.foldMany'/
--
{-# INLINE manyPost #-}
manyPost :: Monad m => Fold m a b -> Fold m b c -> Fold m a c

View File

@ -543,7 +543,9 @@ mkAsyncD m = D.Stream step Nothing
-- kicked off again to evaluate the remaining stream when there is space in the
-- buffer. The consumer consumes the stream lazily from the buffer.
--
-- /Since: 0.8.0/
-- /Since: 0.2.0 (Streamly)/
--
-- @since 0.8.0
--
{-# INLINE_NORMAL mkAsync #-}
mkAsync :: (K.IsStream t, MonadAsync m) => t m a -> t m a
@ -997,7 +999,13 @@ wAsync = joinStreamVarAsync WAsyncVar
--
-- The @W@ in the name stands for @wide@ or breadth wise scheduling in
-- contrast to the depth wise scheduling behavior of 'AsyncT'.
--
-- /Since: 0.2.0 ("Streamly")/
--
-- @since 0.8.0
-- XXX This documentation is redundant, need to be cleaned up/removed.
--
-- @
-- import qualified "Streamly.Prelude" as S
-- import Control.Concurrent
@ -1081,9 +1089,6 @@ wAsync = joinStreamVarAsync WAsyncVar
-- ThreadId 38: Delay 3
-- @
--
-- /Since: 0.2.0 ("Streamly")/
--
-- @since 0.8.0
newtype WAsyncT m a = WAsyncT {getWAsyncT :: Stream m a}
deriving (MonadTrans)

View File

@ -68,7 +68,7 @@ generally xs = fromStreamS $ S.hoist (return . runIdentity) (toStreamS xs)
-- | Lift the inner monad @m@ of a stream @t m a@ to @tr m@ using the monad
-- transformer @tr@.
--
-- / Internal/
-- @since 0.8.0
--
{-# INLINE liftInner #-}
liftInner :: (Monad m, IsStream t, MonadTrans tr, Monad (tr m))
@ -81,7 +81,7 @@ liftInner xs = fromStreamD $ D.liftInner (toStreamD xs)
-- | Evaluate the inner monad of a stream as 'ReaderT'.
--
-- / Internal/
-- @since 0.8.0
--
{-# INLINE runReaderT #-}
runReaderT :: (IsStream t, Monad m) => m s -> t (ReaderT s m) a -> t m a
@ -146,7 +146,7 @@ usingStateT s f = evalStateT s . f . liftInner
-- This is supported only for 'SerialT' as concurrent state updation may not be
-- safe.
--
-- / Internal/
-- @since 0.8.0
--
{-# INLINE runStateT #-}
runStateT :: Monad m => m s -> SerialT (StateT s m) a -> SerialT m (s, a)