Rename some parser APIs, reorg the export list

And add some proposed commented APIs.
This commit is contained in:
Harendra Kumar 2022-05-07 01:26:00 +05:30
parent 8bf2703daf
commit 6ed0c935c5
5 changed files with 136 additions and 144 deletions

View File

@ -92,12 +92,12 @@ takeEQ value = IP.parse (PR.takeEQ value FL.drain)
dropWhile :: MonadCatch m => Int -> SerialT m Int -> m ()
dropWhile value = IP.parse (PR.dropWhile (<= value))
{-# INLINE sliceBeginWith #-}
sliceBeginWith :: MonadCatch m => Int -> SerialT m Int -> m ()
sliceBeginWith value stream = do
{-# INLINE takeStartBy #-}
takeStartBy :: MonadCatch m => Int -> SerialT m Int -> m ()
takeStartBy value stream = do
stream1 <- return . fromMaybe (S.fromPure (value + 1)) =<< S.tail stream
let stream2 = value `S.cons` stream1
IP.parse (PR.sliceBeginWith (== value) FL.drain) stream2
IP.parse (PR.takeStartBy (== value) FL.drain) stream2
{-# INLINE takeWhile #-}
takeWhile :: MonadCatch m => Int -> SerialT m Int -> m ()
@ -212,10 +212,10 @@ split_ value =
(PR.dropWhile (<= value))
)
{-# INLINE sliceSepByP #-}
sliceSepByP :: MonadCatch m
{-# INLINE takeEndBy_ #-}
takeEndBy_ :: MonadCatch m
=> Int -> SerialT m Int -> m()
sliceSepByP value = IP.parse (PR.sliceSepByP (>= value) (PR.fromFold FL.drain))
takeEndBy_ value = IP.parse (PR.takeEndBy_ (>= value) (PR.fromFold FL.drain))
{-# INLINE teeAllAny #-}
teeAllAny :: MonadCatch m
@ -362,7 +362,7 @@ o_1_space_serial value =
, benchIOSink value "takeWhile" $ takeWhile value
, benchIOSink value "takeP" $ takeP value
, benchIOSink value "dropWhile" $ dropWhile value
, benchIOSink value "sliceBeginWith" $ sliceBeginWith value
, benchIOSink value "takeStartBy" $ takeStartBy value
, benchIOSink value "groupBy" $ groupBy
, benchIOSink value "groupByRolling" $ groupByRolling
, benchIOSink value "wordBy" $ wordBy value
@ -372,7 +372,7 @@ o_1_space_serial value =
, benchIOSink value "splitApBefore" $ splitApBefore value
, benchIOSink value "splitApAfter" $ splitApAfter value
, benchIOSink value "serialWith" $ serialWith value
, benchIOSink value "sliceSepByP" $ sliceSepByP value
, benchIOSink value "takeEndBy_" $ takeEndBy_ value
, benchIOSink value "many" many
, benchIOSink value "many (wordBy even)" $ manyWordByEven
, benchIOSink value "some" some

View File

@ -79,12 +79,12 @@ benchIOSinkRandom value name f =
drainWhile :: MonadThrow m => (a -> Bool) -> PR.Parser m a ()
drainWhile p = PR.takeWhile p FL.drain
{-# INLINE sliceBeginWith #-}
sliceBeginWith :: MonadCatch m => Int -> SerialT m Int -> m ()
sliceBeginWith value stream = do
{-# INLINE takeStartBy #-}
takeStartBy :: MonadCatch m => Int -> SerialT m Int -> m ()
takeStartBy value stream = do
stream1 <- return . fromMaybe (S.fromPure (value + 1)) =<< S.tail stream
let stream2 = value `S.cons` stream1
IP.parseD (PR.sliceBeginWith (== value) FL.drain) stream2
IP.parseD (PR.takeStartBy (== value) FL.drain) stream2
{-# INLINE takeWhile #-}
takeWhile :: MonadThrow m => Int -> SerialT m Int -> m ()
@ -135,9 +135,9 @@ someAlt xs = do
x <- IP.parseD (AP.some (PR.satisfy (> 0))) xs
return $ Prelude.length x
{-#INLINE sliceSepByP #-}
sliceSepByP :: MonadCatch m => Int -> SerialT m Int -> m ()
sliceSepByP value = IP.parseD (PR.sliceSepByP (>= value) (PR.fromFold FL.drain))
{-#INLINE takeEndBy_ #-}
takeEndBy_ :: MonadCatch m => Int -> SerialT m Int -> m ()
takeEndBy_ value = IP.parseD (PR.takeEndBy_ (>= value) (PR.fromFold FL.drain))
{-# INLINE manyTill #-}
manyTill :: MonadCatch m => Int -> SerialT m Int -> m Int
@ -323,7 +323,7 @@ o_1_space_serial value =
[ benchIOSink value "takeWhile" $ takeWhile value
, benchIOSink value "takeP" $ takeP value
, benchIOSink value "takeBetween" $ takeBetween value
, benchIOSink value "sliceBeginWith" $ sliceBeginWith value
, benchIOSink value "takeStartBy" $ takeStartBy value
, benchIOSink value "groupBy" $ groupBy
, benchIOSink value "groupByRolling" $ groupByRolling
, benchIOSink value "wordBy" $ wordBy value
@ -331,7 +331,7 @@ o_1_space_serial value =
, benchIOSink value "many" many
, benchIOSink value "many (wordBy even)" $ manyWordByEven
, benchIOSink value "some" some
, benchIOSink value "sliceSepByP" $ sliceSepByP value
, benchIOSink value "takeEndBy_" $ takeEndBy_ value
, benchIOSink value "manyTill" $ manyTill value
, benchIOSink value "tee (all,any)" $ teeAllAny value
, benchIOSink value "teeFst (all,any)" $ teeFstAllAny value

View File

@ -80,11 +80,14 @@ module Streamly.Internal.Data.Parser
, maybe
, either
-- * Sequence parsers
-- * Sequence parsers (tokenizers)
--
-- | Parsers chained in series, if one parser terminates the composition
-- terminates.
, lookAhead
-- ** By length
-- | Grab a sequence of input elements without inspecting them
, takeBetween
-- , take -- takeBetween 0 n
@ -93,30 +96,40 @@ module Streamly.Internal.Data.Parser
, takeP
-- Grab a sequence of input elements by inspecting them
-- ** Exact match
, eqBy
, list
, lookAhead
-- ** By predicate
, takeWhileP
, takeWhile
-- $takeWhile
, takeWhile1
, dropWhile
-- Separators
, sliceSepByP
, sliceBeginWith
, sliceSepWith
-- Quoting and Escaping
, escapedSliceSepBy
, escapedFrameBy
-- Words and grouping
-- ** Separators
-- , takeEndBy
, takeEndBy_
, takeEndByEsc
-- , takeEndByEsc_
, takeStartBy
-- , takeStartBy_
, takeEitherSepBy
, wordBy
-- , wordByEsc
-- ** By comparing
, groupBy
, groupByRolling
, groupByRollingEither
-- ** Framing
-- , takeFramedBy
-- , takeFramedBy_
, takeFramedByEsc
-- , wordByQuoted
-- , wordByQuotedEsc
-- | Unimplemented
--
-- @
@ -143,6 +156,24 @@ module Streamly.Internal.Data.Parser
-- secondary parser.
, deintercalate
-- *** Special cases
-- | TODO: traditional implmentations of these may be of limited use. For
-- example, consider parsing lines separated by @\\r\\n@. The main parser
-- will have to detect and exclude the sequence @\\r\\n@ anyway so that we
-- can apply the "sep" parser.
--
-- We can instead implement these as special cases of deintercalate.
--
-- @
-- , endBy
-- , sepEndBy
-- , beginBy
-- , sepBeginBy
-- , sepAroundBy
-- @
, sepBy1
, sepBy
-- ** Sequential Alternative
, alt
@ -167,24 +198,6 @@ module Streamly.Internal.Data.Parser
, manyTill
, manyThen
-- ** Special cases
-- | TODO: traditional implmentations of these may be of limited use. For
-- example, consider parsing lines separated by @\\r\\n@. The main parser
-- will have to detect and exclude the sequence @\\r\\n@ anyway so that we
-- can apply the "sep" parser.
--
-- We can instead implement these as special cases of deintercalate.
--
-- @
-- , endBy
, sepBy1
, sepBy
-- , sepEndBy
-- , beginBy
-- , sepBeginBy
-- , sepAroundBy
-- @
-- * Distribution
--
-- | A simple and stupid impl would be to just convert the stream to an
@ -524,12 +537,9 @@ either = D.toParserK . D.either
-- @takeBetween@ is the most general take operation, other take operations can
-- be defined in terms of takeBetween. For example:
--
-- @
-- take = takeBetween 0 n -- equivalent of take
-- take1 = takeBetween 1 n -- equivalent of takeLE1
-- takeEQ = takeBetween n n
-- takeGE = takeBetween n maxBound
-- @
-- >>> take n = Parser.takeBetween 0 n
-- >>> takeEQ n = Parser.takeBetween n n
-- >>> takeGE n = Parser.takeBetween n maxBound
--
-- /Pre-release/
--
@ -584,10 +594,10 @@ takeGE n = D.toParserK . D.takeGE n
-- input. The combinator stops when the condition fails or if the collecting
-- parser stops.
--
-- This is a generalized version of takeWhile, for example 'takeWhile1' can be
-- implemented in terms of this:
-- Other interesting parsers can be implemented in terms of this parser:
--
-- >>> takeWhile1 cond p = takeWhile cond (takeBetween 1 maxBound p)
-- >>> takeWhile1 cond p = Parser.takeWhileP cond (Parser.takeBetween 1 maxBound p)
-- >>> takeWhileBetween cond m n p = Parser.takeWhileP cond (Parser.takeBetween m n p)
--
-- Stops: when the condition fails or the collecting parser stops.
-- Fails: when the collecting parser fails.
@ -650,89 +660,73 @@ dropWhile p = takeWhile p FL.drain
-- Separators
-------------------------------------------------------------------------------
-- | @sliceSepByP cond parser@ parses a slice of the input using @parser@ until
-- @cond@ succeeds or the parser stops.
-- | @takeEndBy_ cond parser@ parses a token that ends by a separator chosen by
-- the supplied predicate. The separator is dropped.
--
-- This is a generalized slicing parser which can be used to implement other
-- parsers e.g.:
-- This can be combined with other parsers to implement other interesting
-- parsers as follows:
--
-- @
-- sliceSepByMax cond n p = sliceSepByP cond (take n p)
-- sliceSepByBetween cond m n p = sliceSepByP cond (takeBetween m n p)
-- @
-- >>> takeEndByOrMax cond n p = Parser.takeEndBy_ cond (Parser.fromFold $ Fold.take n p)
-- >>> takeEndByBetween cond m n p = Parser.takeEndBy_ cond (Parser.takeBetween m n p)
--
-- /Pre-release/
--
{-# INLINE sliceSepByP #-}
sliceSepByP ::
MonadCatch m =>
(a -> Bool) -> Parser m a b -> Parser m a b
sliceSepByP cond = D.toParserK . D.sliceSepByP cond . D.fromParserK
{-# INLINE takeEndBy_ #-}
takeEndBy_ :: MonadCatch m => (a -> Bool) -> Parser m a b -> Parser m a b
takeEndBy_ cond = D.toParserK . D.takeEndBy_ cond . D.fromParserK
-- | Like 'sliceSepBy' but does not drop the separator element, instead
-- separator is emitted as a separate element in the output.
-- | Take either the separator or the token. Separator is a Left value and
-- token is Right value.
--
-- /Unimplemented/
{-# INLINE sliceSepWith #-}
sliceSepWith :: -- MonadCatch m =>
(a -> Bool) -> Fold m a b -> Parser m a b
sliceSepWith _cond = undefined -- D.toParserK . D.sliceSepBy cond
{-# INLINE takeEitherSepBy #-}
takeEitherSepBy :: -- MonadCatch m =>
(a -> Bool) -> Fold m (Either a b) c -> Parser m a c
takeEitherSepBy _cond = undefined -- D.toParserK . D.takeEitherSepBy cond
-- | Collect stream elements until an elements passes the predicate, return the
-- last element on which the predicate succeeded back to the input stream. If
-- the predicate succeeds on the first element itself then the parser does not
-- terminate there. The succeeding element in the leading position
-- is treated as a prefix separator which is kept in the output segment.
-- | Parse a token that starts with an element chosen by the predicate. The
-- parser fails if the input does not start with the selected element.
--
-- * Stops - when the predicate succeeds in non-leading position.
-- * Fails - never.
-- * Fails - when the predicate fails in the leading position.
--
-- S.splitWithPrefix pred f = S.parseMany (PR.sliceBeginWith pred f)
-- >>> splitWithPrefix p f = Stream.parseMany (Parser.takeStartBy p f)
--
-- Examples: -
--
-- >>> :{
-- sliceBeginWithOdd ls = Stream.parse prsr (Stream.fromList ls)
-- where prsr = Parser.sliceBeginWith odd Fold.toList
-- :}
--
--
-- >>> sliceBeginWithOdd [2, 4, 6, 3]
-- *** Exception: sliceBeginWith : slice begins with an element which fails the predicate
-- >>> p = Parser.takeStartBy (== ',') Fold.toList
-- >>> leadingComma = Stream.parse p . Stream.fromList
-- >>> leadingComma "a,b,c,d"
-- *** Exception: takeStartBy : token begins with an element which fails the predicate
-- ...
--
-- >>> sliceBeginWithOdd [3, 5, 7, 4]
-- [3]
--
-- >>> sliceBeginWithOdd [3, 4, 6, 8, 5]
-- [3,4,6,8]
--
-- >>> sliceBeginWithOdd []
-- []
-- >>> leadingComma ",,"
-- ","
-- >>> leadingComma ",a,b,c,d"
-- ",a"
-- >>> leadingComma ""
-- ""
--
-- /Pre-release/
--
{-# INLINE sliceBeginWith #-}
sliceBeginWith ::
MonadCatch m =>
(a -> Bool) -> Fold m a b -> Parser m a b
sliceBeginWith cond = D.toParserK . D.sliceBeginWith cond
{-# INLINE takeStartBy #-}
takeStartBy :: MonadCatch m => (a -> Bool) -> Fold m a b -> Parser m a b
takeStartBy cond = D.toParserK . D.takeStartBy cond
-------------------------------------------------------------------------------
-- Quoting and Escaping
-------------------------------------------------------------------------------
-- | Like 'sliceSepBy' but the separator elements can be escaped using an
-- | Like 'takeEndBy' but the separator elements can be escaped using an
-- escape char determined by the second predicate.
--
-- /Unimplemented/
{-# INLINE escapedSliceSepBy #-}
escapedSliceSepBy :: -- MonadCatch m =>
{-# INLINE takeEndByEsc #-}
takeEndByEsc :: -- MonadCatch m =>
(a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser m a b
escapedSliceSepBy _cond _esc = undefined
-- D.toParserK . D.escapedSliceSepBy cond esc
takeEndByEsc _cond _esc = undefined
-- D.toParserK . D.takeEndByEsc cond esc
-- | @escapedFrameBy begin end escape@ parses a string framed using @begin@ and
-- | @takeFramedByEsc begin end escape@ parses a string framed using @begin@ and
-- @end@ as the frame begin and end marker elements and @escape@ as an escaping
-- element to escape the occurrence of the framing elements within the frame.
-- Nested frames are allowed, but nesting is removed when parsing.
@ -740,26 +734,26 @@ escapedSliceSepBy _cond _esc = undefined
-- For example,
--
-- @
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello}"
-- > Stream.parse (Parser.takeFramedByEsc (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello}"
-- "hello"
--
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello {world}}"
-- > Stream.parse (Parser.takeFramedByEsc (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello {world}}"
-- "hello world"
--
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello \\{world\\}}"
-- > Stream.parse (Parser.takeFramedByEsc (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello \\{world\\}}"
-- "hello {world}"
--
-- > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello {world}"
-- > Stream.parse (Parser.takeFramedByEsc (== '{') (== '}') (== '\\') Fold.toList) $ Stream.fromList "{hello {world}"
-- ParseError "Unterminated '{'"
--
-- @
--
-- /Unimplemented/
{-# INLINE escapedFrameBy #-}
escapedFrameBy :: -- MonadCatch m =>
{-# INLINE takeFramedByEsc #-}
takeFramedByEsc :: -- MonadCatch m =>
(a -> Bool) -> (a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser m a b
escapedFrameBy _begin _end _escape _p = undefined
-- D.toParserK . D.frameBy begin end escape p
takeFramedByEsc _begin _end _escape _p = undefined
-- D.toParserK . D.takeFramedByEsc begin end escape p
-------------------------------------------------------------------------------
-- Grouping and words

View File

@ -53,16 +53,16 @@ module Streamly.Internal.Data.Parser.ParserD
-- parsers but we can use Parsers instead of folds to make the composition
-- more powerful. For example, we can do:
--
-- sliceSepByMax cond n p = sliceBy cond (take n p)
-- sliceSepByBetween cond m n p = sliceBy cond (takeBetween m n p)
-- takeEndByOrMax cond n p = takeEndBy cond (take n p)
-- takeEndByBetween cond m n p = takeEndBy cond (takeBetween m n p)
-- takeWhileBetween cond m n p = takeWhile cond (takeBetween m n p)
-- Grab a sequence of input elements without inspecting them
, takeBetween
-- , take -- take -- takeBetween 0 n
-- , takeLE1 -- take1 -- takeBetween 1 n
, takeEQ -- takeBetween n n
, takeGE -- takeBetween n maxBound
-- , takeGE1 -- take1 -- takeBetween 1 n
, takeP
-- Grab a sequence of input elements by inspecting them
@ -72,10 +72,8 @@ module Streamly.Internal.Data.Parser.ParserD
, takeWhile1
-- Separators
, sliceSepByP
-- , sliceSepByBetween
, sliceBeginWith
-- , sliceSepWith
, takeEndBy_
, takeStartBy
-- Words and grouping
, wordBy
@ -670,13 +668,13 @@ takeWhile1 predicate (Fold fstep finitial fextract) =
-- Separators
-------------------------------------------------------------------------------
-- | See 'Streamly.Internal.Data.Parser.sliceSepByP'.
-- | See 'Streamly.Internal.Data.Parser.takeEndBy_'.
--
-- /Pre-release/
--
sliceSepByP :: MonadCatch m =>
takeEndBy_ :: MonadCatch m =>
(a -> Bool) -> Parser m a b -> Parser m a b
sliceSepByP cond (Parser pstep pinitial pextract) =
takeEndBy_ cond (Parser pstep pinitial pextract) =
Parser step initial pextract
@ -691,15 +689,15 @@ sliceSepByP cond (Parser pstep pinitial pextract) =
return $ Done 0 res
else pstep s a
-- | See 'Streamly.Internal.Data.Parser.sliceBeginWith'.
-- | See 'Streamly.Internal.Data.Parser.takeStartBy'.
--
-- /Pre-release/
--
data SliceBeginWithState s = Left' s | Right' s
{-# INLINE sliceBeginWith #-}
sliceBeginWith :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b
sliceBeginWith cond (Fold fstep finitial fextract) =
{-# INLINE takeStartBy #-}
takeStartBy :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b
takeStartBy cond (Fold fstep finitial fextract) =
Parser step initial extract
@ -710,7 +708,7 @@ sliceBeginWith cond (Fold fstep finitial fextract) =
return $
case res of
FL.Partial s -> IPartial (Left' s)
FL.Done _ -> IError "sliceBeginWith : bad finitial"
FL.Done _ -> IError "takeStartBy : bad finitial"
{-# INLINE process #-}
process s a = do
@ -723,7 +721,7 @@ sliceBeginWith cond (Fold fstep finitial fextract) =
step (Left' s) a =
if cond a
then process s a
else error $ "sliceBeginWith : slice begins with an element which "
else error $ "takeStartBy : token begins with an element which "
++ "fails the predicate"
step (Right' s) a =
if not (cond a)

View File

@ -324,10 +324,10 @@ takeProperties =
-- where
-- list_length = Prelude.length ls
sliceSepByP :: Property
sliceSepByP =
takeEndBy_ :: Property
takeEndBy_ =
forAll (listOf (chooseInt (min_value, max_value ))) $ \ls ->
case S.parse (P.sliceSepByP predicate prsr) (S.fromList ls) of
case S.parse (P.takeEndBy_ predicate prsr) (S.fromList ls) of
Right parsed_list ->
checkListEqual parsed_list (tkwhl ls)
Left _ -> property False
@ -336,8 +336,8 @@ sliceSepByP =
prsr = P.many (P.satisfy (const True)) FL.toList
tkwhl ls = Prelude.takeWhile (not . predicate) ls
sliceBeginWith :: Property
sliceBeginWith =
takeStartBy :: Property
takeStartBy =
forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
let ls1 = 1:ls
in
@ -354,7 +354,7 @@ sliceBeginWith =
Left _ -> property False
where
predicate = odd
parser = P.sliceBeginWith predicate FL.toList
parser = P.takeStartBy predicate FL.toList
takeWhile :: Property
takeWhile =
@ -779,9 +779,9 @@ main =
-- prop "lookAhead . take n >> lookAhead . take n = lookAhead . take n" lookAheadPass
-- prop "Fail when stream length exceeded" lookAheadFail
-- prop "lookAhead . take n >> lookAhead . take n = lookAhead . take n, else fail" lookAhead
prop "P.sliceSepByP test" Main.sliceSepByP
prop ("P.sliceBeginWith pred = head : Prelude.takeWhile (not . pred)"
++ " tail") sliceBeginWith
prop "P.takeEndBy_ test" Main.takeEndBy_
prop ("P.takeStartBy pred = head : Prelude.takeWhile (not . pred)"
++ " tail") takeStartBy
prop "P.takeWhile = Prelude.takeWhile" Main.takeWhile
prop ("P.takeWhile1 = Prelude.takeWhile if taken something,"
++ " else check why failed") takeWhile1