Rename parseKChunks to chunkParse

This commit is contained in:
Harendra Kumar 2023-02-15 17:35:28 +05:30
parent 5cb08e7745
commit 39bc526981
6 changed files with 23 additions and 33 deletions

View File

@ -68,12 +68,12 @@ benchIOSink value name f =
-- Parsers
-------------------------------------------------------------------------------
#define PARSE_OP StreamK.parseKChunks
#define PARSE_OP StreamK.chunkParse
{-# INLINE one #-}
one :: MonadIO m =>
Int -> StreamK m (Array Int) -> m (Either ParseError (Maybe Int))
one value = StreamK.parseKChunks p
one value = StreamK.chunkParse p
where

View File

@ -179,7 +179,7 @@ refoldIterateM =
{-# INLINE parseBreak #-}
parseBreak :: Monad m => StreamK m Int -> m ()
parseBreak s = do
r <- K.parseBreak PR.one s
r <- K.parseDBreak PR.one s
case r of
(Left _, _) -> return ()
(Right _, s1) -> parseBreak s1

View File

@ -3,4 +3,3 @@ packages: streamly.cabal
, test/streamly-tests.cabal
, benchmark/streamly-benchmarks.cabal
, docs/streamly-docs.cabal
write-ghc-environment-files: always

View File

@ -53,8 +53,8 @@ module Streamly.Data.Stream.StreamK
-- ** Parsing
-- , parseBreak
, parseKBreakChunks
-- , parseKChunks
, chunkParseBreak
-- , chunkParse
-- * Combining Two Streams
-- ** Appending

View File

@ -117,10 +117,10 @@ module Streamly.Internal.Data.Stream.StreamK
, foldBreak
, foldEither
, foldConcat
, parseBreak
, parse
, parseKBreakChunks
, parseKChunks
, parseDBreak
, parseD
, chunkParseBreak
, chunkParse
-- ** Specialized Folds
, drain
@ -371,7 +371,7 @@ foldlMx' step begin done = go begin
-- Definitions:
--
-- >>> fold f = fmap fst . StreamK.foldBreak f
-- >>> fold f = StreamK.parse (Parser.fromFold f)
-- >>> fold f = StreamK.parseD (Parser.fromFold f)
--
-- Example:
--
@ -1146,13 +1146,13 @@ splitAt n ls
(xs', xs'') = splitAt' (m - 1) xs
-- | Run a 'Parser' over a stream and return rest of the Stream.
{-# INLINE_NORMAL parseBreakD #-}
parseBreakD
{-# INLINE_NORMAL parseDBreak #-}
parseDBreak
:: Monad m
=> PR.Parser a m b
-> Stream m a
-> m (Either ParseError b, Stream m a)
parseBreakD (PR.Parser pstep initial extract) stream = do
parseDBreak (PR.Parser pstep initial extract) stream = do
res <- initial
case res of
PR.IPartial s -> goStream stream [] s
@ -1232,23 +1232,14 @@ parseBreakD (PR.Parser pstep initial extract) stream = do
return (Right b, append (fromList src) st)
PR.Error err -> return (Left (ParseError err), nil)
-- | Parse a stream using the supplied 'Parser'.
--
-- /CPS/
--
{-# INLINE parseBreak #-}
parseBreak :: Monad m =>
Parser.Parser a m b -> Stream m a -> m (Either ParseError b, Stream m a)
parseBreak = parseBreakD
-- Using ParserD or ParserK on StreamK may not make much difference. We should
-- perhaps use only chunked parsing on StreamK. We can always convert a stream
-- to chunks before parsing. Or just have a ParserK element parser for StreamK
-- and convert ParserD to ParserK for element parsing using StreamK.
{-# INLINE parse #-}
parse :: Monad m =>
{-# INLINE parseD #-}
parseD :: Monad m =>
Parser.Parser a m b -> Stream m a -> m (Either ParseError b)
parse f = fmap fst . parseBreak f
parseD f = fmap fst . parseDBreak f
-------------------------------------------------------------------------------
-- Chunked parsing using ParserK
@ -1289,13 +1280,13 @@ parserDone (ParserK.Success n b) _ _ = pure $ ParserK.Done n b
parserDone (ParserK.Failure n e) _ _ = pure $ ParserK.Error n e
-- | Run a 'ParserK' over a chunked 'StreamK' and return the rest of the Stream.
{-# INLINE_NORMAL parseKBreakChunks #-}
parseKBreakChunks
{-# INLINE_NORMAL chunkParseBreak #-}
chunkParseBreak
:: (Monad m, Unbox a)
=> ParserK.Parser a m b
-> StreamK m (Array a)
-> m (Either ParseError b, StreamK m (Array a))
parseKBreakChunks parser input = do
chunkParseBreak parser input = do
let parserk = \arr -> ParserK.runParser parser parserDone 0 0 arr
in go [] parserk input
@ -1380,10 +1371,10 @@ parseKBreakChunks parser input = do
in foldStream
defState (yieldk backBuf parserk) single stop stream
{-# INLINE parseKChunks #-}
parseKChunks :: (Monad m, Unbox a) =>
{-# INLINE chunkParse #-}
chunkParse :: (Monad m, Unbox a) =>
ParserK.Parser a m b -> Stream m (Array a) -> m (Either ParseError b)
parseKChunks f = fmap fst . parseKBreakChunks f
chunkParse f = fmap fst . chunkParseBreak f
-------------------------------------------------------------------------------
-- Sorting

View File

@ -170,7 +170,7 @@ import qualified Streamly.Internal.Data.Array as A
import qualified Streamly.Internal.Data.Stream.Serial as Stream
import qualified Streamly.Internal.Data.Fold as FL
import qualified Streamly.Internal.Data.Parser.ParserD as PRD
import qualified Streamly.Internal.Data.Parser.ParserK.Type as PRK
-- import qualified Streamly.Internal.Data.Parser.ParserK.Type as PRK
import qualified Streamly.Internal.Data.Stream.IsStream.Type as IsStream
import qualified Streamly.Internal.Data.Stream.StreamD as D
(foldr1, foldlT, foldlM', mapM_, null, head, headElse, last, elem