Move Streamly.Data.Unfold module to streamly-core package (#1771)

* Move Streamly.Data.Unfold to streamly-core package

* Remove readStream, just use the monomorphic fromStream

Co-authored-by: Harendra Kumar <harendra@composewell.com>
This commit is contained in:
Ranjeet Ranjan 2022-08-20 10:59:13 +05:30 committed by GitHub
parent ec760805c9
commit 7dde623b7d
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
6 changed files with 9 additions and 30 deletions

View File

@ -160,7 +160,7 @@ module Streamly.Data.Unfold
-- * Unfolds
-- One to one correspondence with
-- "Streamly.Internal.Data.Stream.IsStream.Generate"
-- "Streamly.Internal.Data.Stream.Generate"
-- ** Basic Constructors
, unfoldrM
@ -212,22 +212,4 @@ import Prelude hiding
( concat, map, mapM, takeWhile, take, filter, const, drop, dropWhile
, zipWith
)
import Streamly.Internal.Data.Stream.IsStream.Type (IsStream)
import Streamly.Internal.Data.Unfold hiding (fromStream)
import qualified Streamly.Internal.Data.Stream.IsStream.Type as IsStream
import qualified Streamly.Internal.Data.Unfold as Unfold
-- XXX Using Unfold.fromStreamD seems to be faster (using cross product test
-- case) than using fromStream even if it is implemented using fromStreamD.
-- Check if StreamK to StreamD rewrite rules are working correctly when
-- implementing fromStream using fromStreamD.
-- | Convert a stream into an 'Unfold'. Note that a stream converted to an
-- 'Unfold' may not be as efficient as an 'Unfold' in some situations.
--
-- /Since: 0.8.0/
--
{-# INLINE_NORMAL fromStream #-}
fromStream :: (IsStream t, Applicative m) => Unfold m (t m a) a
fromStream = lmap IsStream.toStream Unfold.fromStreamK
import Streamly.Internal.Data.Unfold

View File

@ -344,6 +344,7 @@ library
, Streamly.Data.Fold
, Streamly.Data.Fold.Tee
, Streamly.Data.Array.Unboxed
, Streamly.Data.Unfold
build-depends:
-- Core libraries shipped with ghc, the min and max

View File

@ -14,6 +14,8 @@
writeWithBufferOf -> writeWith
writeChunksWithBufferOf -> writeChunksWith
* Signature changed: Streamly.Data.Unfold.fromStream
### Deprecations
* In `Streamly.Data.Fold`:

View File

@ -569,7 +569,6 @@ concatMapM f m = fromStreamD $ D.concatMapM (fmap toStreamD . f) (toStreamD m)
-- >>> concatMap f = Stream.concatMapM (return . f)
-- >>> concatMap f = Stream.concatMapWith Stream.serial f
-- >>> concatMap f = Stream.concat . Stream.map f
-- >>> concatMap f = Stream.unfoldMany (Unfold.lmap f Unfold.fromStream)
--
-- @since 0.6.0
{-# INLINE concatMap #-}

View File

@ -1289,10 +1289,6 @@ ejectExpired reset ejectPred extract session@SessionState{..} curTime = do
assert (IsMap.mapNull mp) (return ())
return (hp, mp, out, cnt)
{-# INLINE readSerial #-}
readSerial :: Applicative m => Unfold.Unfold m (IsStream.SerialT m a) a
readSerial = Unfold.fromStream
-- XXX Use mutable IORef in accumulator
{-# INLINE classifySessionsByGeneric #-}
classifySessionsByGeneric
@ -1307,7 +1303,7 @@ classifySessionsByGeneric
-> t m (Key f, b) -- ^ session key, fold result
classifySessionsByGeneric _ tick reset ejectPred tmout
(Fold step initial extract) input =
Expand.unfoldMany (Unfold.lmap sessionOutputStream readSerial)
Expand.unfoldMany (Unfold.lmap sessionOutputStream Unfold.fromStream)
$ scanlMAfter' sstep (return szero) (flush extract)
$ interjectSuffix tick (return Nothing)
$ map Just input

View File

@ -215,6 +215,7 @@ extra-source-files:
core/src/Streamly/Data/Stream.hs
core/src/Streamly/Data/Fold.hs
core/src/Streamly/Data/Fold/Tee.hs
core/src/Streamly/Data/Unfold.hs
core/src/Streamly/Internal/Data/Fold/Window.hs
core/src/Streamly/Data/Array/Unboxed.hs
core/src/Streamly/Internal/Data/Time/Clock/Darwin.c
@ -436,10 +437,7 @@ library
-- dependency order To view dependency graph:
-- graphmod | dot -Tps > deps.ps
-- XXX To be moved to streamly-core
Streamly.Data.Unfold
, Streamly.Internal.Data.IsMap.HashMap
Streamly.Internal.Data.IsMap.HashMap
-- XXX To be removed or put under dev flag
, Streamly.Internal.Data.SmallArray.Type
@ -637,6 +635,7 @@ library
, Streamly.Internal.Data.Stream.StreamK
-- streamly-core exposed modules
, Streamly.Data.Unfold
, Streamly.Data.Stream
, Streamly.Data.Fold
, Streamly.Data.Fold.Tee