@@ -274,30 +274,7 @@ toFold (Parser pstep pinitial pextract) = Fold step initial pextract
274274-------------------------------------------------------------------------------
275275-- Upgrade folds to parses
276276-------------------------------------------------------------------------------
277- --
278- -- | See 'Streamly.Internal.Data.Parser.fromFold'.
279- --
280- -- /Pre-release/
281- --
282- {-# INLINE fromFold #-}
283- fromFold :: Monad m => Fold m a b -> Parser m a b
284- fromFold (Fold fstep finitial fextract) = Parser step initial fextract
285-
286- where
287-
288- initial = do
289- res <- finitial
290- return
291- $ case res of
292- FL. Partial s1 -> IPartial s1
293- FL. Done b -> IDone b
294-
295- step s a = do
296- res <- fstep s a
297- return
298- $ case res of
299- FL. Partial s1 -> Partial 0 s1
300- FL. Done b -> Done 0 b
277+ -- XXX fromMaybeFold
301278
302279-- | Convert Maybe returning folds to error returning parsers.
303280--
@@ -369,18 +346,6 @@ eof = Parser step initial return
369346
370347 step () _ = return $ Error " eof: not at end of input"
371348
372- -- | See 'Streamly.Internal.Data.Parser.next'.
373- --
374- -- /Pre-release/
375- --
376- {-# INLINE next #-}
377- next :: Monad m => Parser m a (Maybe a )
378- next = Parser step initial extract
379- where
380- initial = pure $ IPartial ()
381- step _ a = pure $ Done 0 (Just a)
382- extract _ = pure Nothing
383-
384349-- | See 'Streamly.Internal.Data.Parser.either'.
385350--
386351-- /Pre-release/
@@ -654,33 +619,6 @@ takeWhileP predicate (Parser pstep pinitial pextract) =
654619 then pstep s a
655620 else Done 1 <$> pextract s
656621
657- -- | See 'Streamly.Internal.Data.Parser.takeWhile'.
658- --
659- -- /Pre-release/
660- --
661- {-# INLINE takeWhile #-}
662- takeWhile :: Monad m => (a -> Bool ) -> Fold m a b -> Parser m a b
663- takeWhile predicate (Fold fstep finitial fextract) =
664- Parser step initial fextract
665-
666- where
667-
668- initial = do
669- res <- finitial
670- return $ case res of
671- FL. Partial s -> IPartial s
672- FL. Done b -> IDone b
673-
674- step s a =
675- if predicate a
676- then do
677- fres <- fstep s a
678- return
679- $ case fres of
680- FL. Partial s1 -> Partial 0 s1
681- FL. Done b -> Done 0 b
682- else Done 1 <$> fextract s
683-
684622-- | See 'Streamly.Internal.Data.Parser.takeWhile1'.
685623--
686624-- /Pre-release/
@@ -1037,52 +975,6 @@ takeFramedBy_ isBegin isEnd (Fold fstep finitial fextract) =
1037975-- Grouping and words
1038976-------------------------------------------------------------------------------
1039977
1040- data WordByState s b = WBLeft ! s | WBWord ! s | WBRight ! b
1041-
1042- -- | See 'Streamly.Internal.Data.Parser.wordBy'.
1043- --
1044- --
1045- {-# INLINE wordBy #-}
1046- wordBy :: Monad m => (a -> Bool ) -> Fold m a b -> Parser m a b
1047- wordBy predicate (Fold fstep finitial fextract) = Parser step initial extract
1048-
1049- where
1050-
1051- {-# INLINE worder #-}
1052- worder s a = do
1053- res <- fstep s a
1054- return
1055- $ case res of
1056- FL. Partial s1 -> Partial 0 $ WBWord s1
1057- FL. Done b -> Done 0 b
1058-
1059- initial = do
1060- res <- finitial
1061- return
1062- $ case res of
1063- FL. Partial s -> IPartial $ WBLeft s
1064- FL. Done b -> IDone b
1065-
1066- step (WBLeft s) a =
1067- if not (predicate a)
1068- then worder s a
1069- else return $ Partial 0 $ WBLeft s
1070- step (WBWord s) a =
1071- if not (predicate a)
1072- then worder s a
1073- else do
1074- b <- fextract s
1075- return $ Partial 0 $ WBRight b
1076- step (WBRight b) a =
1077- return
1078- $ if not (predicate a)
1079- then Done 1 b
1080- else Partial 0 $ WBRight b
1081-
1082- extract (WBLeft s) = fextract s
1083- extract (WBWord s) = fextract s
1084- extract (WBRight b) = return b
1085-
1086978data WordFramedState s b =
1087979 WordFramedSkipPre ! s
1088980 | WordFramedWord ! s ! Int
@@ -1283,163 +1175,6 @@ wordQuotedBy keepQuotes isEsc isBegin isEnd toRight isSep
12831175 err " wordQuotedBy: trailing escape"
12841176 extract (WordQuotedSkipPost b) = return b
12851177
1286- {-# ANN type GroupByState Fuse #-}
1287- data GroupByState a s
1288- = GroupByInit ! s
1289- | GroupByGrouping ! a ! s
1290-
1291- -- | See 'Streamly.Internal.Data.Parser.groupBy'.
1292- --
1293- {-# INLINE groupBy #-}
1294- groupBy :: Monad m => (a -> a -> Bool ) -> Fold m a b -> Parser m a b
1295- groupBy eq (Fold fstep finitial fextract) = Parser step initial extract
1296-
1297- where
1298-
1299- {-# INLINE grouper #-}
1300- grouper s a0 a = do
1301- res <- fstep s a
1302- return
1303- $ case res of
1304- FL. Done b -> Done 0 b
1305- FL. Partial s1 -> Partial 0 (GroupByGrouping a0 s1)
1306-
1307- initial = do
1308- res <- finitial
1309- return
1310- $ case res of
1311- FL. Partial s -> IPartial $ GroupByInit s
1312- FL. Done b -> IDone b
1313-
1314- step (GroupByInit s) a = grouper s a a
1315- step (GroupByGrouping a0 s) a =
1316- if eq a0 a
1317- then grouper s a0 a
1318- else Done 1 <$> fextract s
1319-
1320- extract (GroupByInit s) = fextract s
1321- extract (GroupByGrouping _ s) = fextract s
1322-
1323- -- | See 'Streamly.Internal.Data.Parser.groupByRolling'.
1324- --
1325- {-# INLINE groupByRolling #-}
1326- groupByRolling :: Monad m => (a -> a -> Bool ) -> Fold m a b -> Parser m a b
1327- groupByRolling eq (Fold fstep finitial fextract) = Parser step initial extract
1328-
1329- where
1330-
1331- {-# INLINE grouper #-}
1332- grouper s a = do
1333- res <- fstep s a
1334- return
1335- $ case res of
1336- FL. Done b -> Done 0 b
1337- FL. Partial s1 -> Partial 0 (GroupByGrouping a s1)
1338-
1339- initial = do
1340- res <- finitial
1341- return
1342- $ case res of
1343- FL. Partial s -> IPartial $ GroupByInit s
1344- FL. Done b -> IDone b
1345-
1346- step (GroupByInit s) a = grouper s a
1347- step (GroupByGrouping a0 s) a =
1348- if eq a0 a
1349- then grouper s a
1350- else Done 1 <$> fextract s
1351-
1352- extract (GroupByInit s) = fextract s
1353- extract (GroupByGrouping _ s) = fextract s
1354-
1355- {-# ANN type GroupByStatePair Fuse #-}
1356- data GroupByStatePair a s1 s2
1357- = GroupByInitPair ! s1 ! s2
1358- | GroupByGroupingPair ! a ! s1 ! s2
1359- | GroupByGroupingPairL ! a ! s1 ! s2
1360- | GroupByGroupingPairR ! a ! s1 ! s2
1361-
1362- {-# INLINE groupByRollingEither #-}
1363- groupByRollingEither :: MonadCatch m =>
1364- (a -> a -> Bool ) -> Fold m a b -> Fold m a c -> Parser m a (Either b c )
1365- groupByRollingEither
1366- eq
1367- (Fold fstep1 finitial1 fextract1)
1368- (Fold fstep2 finitial2 fextract2) = Parser step initial extract
1369-
1370- where
1371-
1372- {-# INLINE grouper #-}
1373- grouper s1 s2 a = do
1374- return $ Continue 0 (GroupByGroupingPair a s1 s2)
1375-
1376- {-# INLINE grouperL2 #-}
1377- grouperL2 s1 s2 a = do
1378- res <- fstep1 s1 a
1379- return
1380- $ case res of
1381- FL. Done b -> Done 0 (Left b)
1382- FL. Partial s11 -> Partial 0 (GroupByGroupingPairL a s11 s2)
1383-
1384- {-# INLINE grouperL #-}
1385- grouperL s1 s2 a0 a = do
1386- res <- fstep1 s1 a0
1387- case res of
1388- FL. Done b -> return $ Done 0 (Left b)
1389- FL. Partial s11 -> grouperL2 s11 s2 a
1390-
1391- {-# INLINE grouperR2 #-}
1392- grouperR2 s1 s2 a = do
1393- res <- fstep2 s2 a
1394- return
1395- $ case res of
1396- FL. Done b -> Done 0 (Right b)
1397- FL. Partial s21 -> Partial 0 (GroupByGroupingPairR a s1 s21)
1398-
1399- {-# INLINE grouperR #-}
1400- grouperR s1 s2 a0 a = do
1401- res <- fstep2 s2 a0
1402- case res of
1403- FL. Done b -> return $ Done 0 (Right b)
1404- FL. Partial s21 -> grouperR2 s1 s21 a
1405-
1406- initial = do
1407- res1 <- finitial1
1408- res2 <- finitial2
1409- return
1410- $ case res1 of
1411- FL. Partial s1 ->
1412- case res2 of
1413- FL. Partial s2 -> IPartial $ GroupByInitPair s1 s2
1414- FL. Done b -> IDone (Right b)
1415- FL. Done b -> IDone (Left b)
1416-
1417- step (GroupByInitPair s1 s2) a = grouper s1 s2 a
1418-
1419- step (GroupByGroupingPair a0 s1 s2) a =
1420- if not (eq a0 a)
1421- then grouperL s1 s2 a0 a
1422- else grouperR s1 s2 a0 a
1423-
1424- step (GroupByGroupingPairL a0 s1 s2) a =
1425- if not (eq a0 a)
1426- then grouperL2 s1 s2 a
1427- else Done 1 . Left <$> fextract1 s1
1428-
1429- step (GroupByGroupingPairR a0 s1 s2) a =
1430- if eq a0 a
1431- then grouperR2 s1 s2 a
1432- else Done 1 . Right <$> fextract2 s2
1433-
1434- extract (GroupByInitPair s1 _) = Left <$> fextract1 s1
1435- extract (GroupByGroupingPairL _ s1 _) = Left <$> fextract1 s1
1436- extract (GroupByGroupingPairR _ _ s2) = Right <$> fextract2 s2
1437- extract (GroupByGroupingPair a s1 _) = do
1438- res <- fstep1 s1 a
1439- case res of
1440- FL. Done b -> return $ Left b
1441- FL. Partial s11 -> Left <$> fextract1 s11
1442-
14431178-- XXX use an Unfold instead of a list?
14441179-- XXX custom combinators for matching list, array and stream?
14451180-- XXX rename to listBy?
@@ -1534,6 +1269,8 @@ postscan :: -- Monad m =>
15341269 Fold m a b -> Parser m b c -> Parser m a c
15351270postscan = undefined
15361271
1272+ -- XXX More variants of this are possible based on how do we end the fold, when
1273+ -- the stream ends, when the fold ends, or when any ends.
15371274{-# INLINE zipWithM #-}
15381275zipWithM :: MonadThrow m =>
15391276 (a -> b -> m c ) -> D. Stream m a -> Fold m c x -> Parser m b x
@@ -1631,56 +1368,6 @@ sampleFromthen :: MonadThrow m => Int -> Int -> Fold m a b -> Parser m a b
16311368sampleFromthen offset size =
16321369 makeIndexFilter indexed FL. filter (\ (i, _) -> (i + offset) `mod` size == 0 )
16331370
1634- --------------------------------------------------------------------------------
1635- --- Spanning
1636- --------------------------------------------------------------------------------
1637-
1638- -- | @span p f1 f2@ composes folds @f1@ and @f2@ such that @f1@ consumes the
1639- -- input as long as the predicate @p@ is 'True'. @f2@ consumes the rest of the
1640- -- input.
1641- --
1642- -- @
1643- -- > let span_ p xs = Stream.parse (Parser.span p Fold.toList Fold.toList) $ Stream.fromList xs
1644- --
1645- -- > span_ (< 1) [1,2,3]
1646- -- ([],[1,2,3])
1647- --
1648- -- > span_ (< 2) [1,2,3]
1649- -- ([1],[2,3])
1650- --
1651- -- > span_ (< 4) [1,2,3]
1652- -- ([1,2,3],[])
1653- --
1654- -- @
1655- --
1656- -- /Pre-release/
1657- {-# INLINE span #-}
1658- span :: Monad m => (a -> Bool ) -> Fold m a b -> Fold m a c -> Parser m a (b , c )
1659- span p f1 f2 = noErrorUnsafeSplitWith (,) (takeWhile p f1) (fromFold f2)
1660-
1661- -- | Break the input stream into two groups, the first group takes the input as
1662- -- long as the predicate applied to the first element of the stream and next
1663- -- input element holds 'True', the second group takes the rest of the input.
1664- --
1665- -- /Pre-release/
1666- --
1667- {-# INLINE spanBy #-}
1668- spanBy ::
1669- Monad m
1670- => (a -> a -> Bool ) -> Fold m a b -> Fold m a c -> Parser m a (b , c )
1671- spanBy eq f1 f2 = noErrorUnsafeSplitWith (,) (groupBy eq f1) (fromFold f2)
1672-
1673- -- | Like 'spanBy' but applies the predicate in a rolling fashion i.e.
1674- -- predicate is applied to the previous and the next input elements.
1675- --
1676- -- /Pre-release/
1677- {-# INLINE spanByRolling #-}
1678- spanByRolling ::
1679- Monad m
1680- => (a -> a -> Bool ) -> Fold m a b -> Fold m a c -> Parser m a (b , c )
1681- spanByRolling eq f1 f2 =
1682- noErrorUnsafeSplitWith (,) (groupByRolling eq f1) (fromFold f2)
1683-
16841371-------------------------------------------------------------------------------
16851372-- nested parsers
16861373-------------------------------------------------------------------------------
0 commit comments