Fix Pre-Release to 0.8.0

Fix missing quotes from Stream.intercalateSuffix docs

Fix review comments

Revert Internal API to Pre-Release

Fix Pre-Release to 0.8.0 for remainig

revert Mut/Type.hs to Pre-release
This commit is contained in:
Ranjeet Kumar Ranjan 2021-05-31 21:54:52 +05:30 committed by Harendra Kumar
parent 59ebde003b
commit 191e3cbd5b
7 changed files with 18 additions and 18 deletions

View File

@ -30,7 +30,7 @@
--
-- This module is designed to be imported qualified:
--
-- > import qualified Streamly.Array as A
-- > import qualified Streamly.Data.Array.Foreign as Array
--
-- For experimental APIs see "Streamly.Internal.Data.Array.Foreign".

View File

@ -21,7 +21,7 @@
--
-- = Programmer Notes
--
-- > import qualified Streamly.FileSystem.Handle as FH
-- > import qualified Streamly.FileSystem.Handle as Handle
--
-- For additional, experimental APIs take a look at
-- "Streamly.Internal.FileSystem.Handle" module.

View File

@ -59,7 +59,7 @@ import qualified Streamly.Internal.Unicode.Stream as Unicode
-- | Unfold standard input into a stream of 'Word8'.
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINE read #-}
read :: MonadIO m => Unfold m () Word8
read = Unfold.lmap (\() -> stdin) Handle.read
@ -87,7 +87,7 @@ getChars = Unicode.decodeUtf8 getBytes
-- | Unfolds standard input into a stream of 'Word8' arrays.
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINE readChunks #-}
readChunks :: MonadIO m => Unfold m () (Array Word8)
readChunks = Unfold.lmap (\() -> stdin) Handle.readChunks
@ -129,14 +129,14 @@ getChunksLn = (Stream.splitWithSuffix (== '\n') f) getChars
-- | Fold a stream of 'Word8' to standard output.
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINE write #-}
write :: MonadIO m => Fold m Word8 ()
write = Handle.write stdout
-- | Fold a stream of 'Word8' to standard error.
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINE writeErr #-}
writeErr :: MonadIO m => Fold m Word8 ()
writeErr = Handle.write stderr
@ -164,14 +164,14 @@ putChars = putBytes . Unicode.encodeUtf8
-- | Fold a stream of @Array Word8@ to standard output.
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINE writeChunks #-}
writeChunks :: MonadIO m => Fold m (Array Word8) ()
writeChunks = Handle.writeChunks stdout
-- | Fold a stream of @Array Word8@ to standard error.
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINE writeErrChunks #-}
writeErrChunks :: MonadIO m => Fold m (Array Word8) ()
writeErrChunks = Handle.writeChunks stderr

View File

@ -395,7 +395,7 @@ length arr = MA.length (unsafeThaw arr)
-- | Unfold an array into a stream in reverse order.
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINE_NORMAL readRev #-}
readRev :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a
readRev = Unfold.lmap unsafeThaw MA.readRev

View File

@ -589,7 +589,7 @@ stdDev = sqrt <$> variance
--
-- See https://en.wikipedia.org/wiki/Rolling_hash
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINABLE rollingHashWithSalt #-}
rollingHashWithSalt :: (Monad m, Enum a) => Int64 -> Fold m a Int64
rollingHashWithSalt = foldl' step
@ -609,7 +609,7 @@ defaultSalt = -2578643520546668380
--
-- > rollingHash = Fold.rollingHashWithSalt defaultSalt
--
-- /Pre-release/
-- @since 0.8.0
{-# INLINABLE rollingHash #-}
rollingHash :: (Monad m, Enum a) => Fold m a Int64
rollingHash = rollingHashWithSalt defaultSalt

View File

@ -19,7 +19,7 @@
-- fold to produce a fold, or multiple pipes can be merged or zipped into a
-- single pipe.
--
-- > import qualified Streamly.Internal.Data.Pipe as P
-- > import qualified Streamly.Internal.Data.Pipe as Pipe
module Streamly.Internal.Data.Pipe
(

View File

@ -573,11 +573,11 @@ groups = groupsBy (==)
--
-- splitOn is an inverse of intercalating single element:
--
-- @Stream.intercalate (Stream.fromPure '.') Unfold.fromList . Stream.splitOn (== '.') Fold.toList === id@
-- > Stream.intercalate (Stream.fromPure '.') Unfold.fromList . Stream.splitOn (== '.') Fold.toList === id
--
-- Assuming the input stream does not contain the separator:
--
-- @Stream.splitOn (== '.') Fold.toList . Stream.intercalate (Stream.fromPure '.') Unfold.fromList === id@
-- > Stream.splitOn (== '.') Fold.toList . Stream.intercalate (Stream.fromPure '.') Unfold.fromList === id
--
-- @since 0.7.0
@ -639,11 +639,11 @@ splitOn predicate f =
--
-- 'splitOnSuffix' is an inverse of 'intercalateSuffix' with a single element:
--
-- @Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList . Stream.splitOnSuffix (== '.') Fold.toList === id@
-- > Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList . Stream.splitOnSuffix (== '.') Fold.toList === id
--
-- Assuming the input stream does not contain the separator:
--
-- @Stream.splitOnSuffix (== '.') Fold.toList . Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList === id@
-- > Stream.splitOnSuffix (== '.') Fold.toList . Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList === id
--
-- @since 0.7.0
@ -695,11 +695,11 @@ splitOnSuffix predicate f = foldMany (FL.takeEndBy_ predicate f)
--
-- 'splitOnPrefix' is an inverse of 'intercalatePrefix' with a single element:
--
-- @Stream.intercalatePrefix (Stream.fromPure '.') Unfold.fromList . Stream.splitOnPrefix (== '.') Fold.toList === id@
-- > Stream.intercalatePrefix (Stream.fromPure '.') Unfold.fromList . Stream.splitOnPrefix (== '.') Fold.toList === id
--
-- Assuming the input stream does not contain the separator:
--
-- @Stream.splitOnPrefix (== '.') Fold.toList . Stream.intercalatePrefix (Stream.fromPure '.') Unfold.fromList === id@
-- > Stream.splitOnPrefix (== '.') Fold.toList . Stream.intercalatePrefix (Stream.fromPure '.') Unfold.fromList === id
--
-- /Unimplemented/