Skip to content

Commit

Permalink
Add Regex.Base.parseNext (#26)
Browse files Browse the repository at this point in the history
And examples for parseFoldr and parseNext.
  • Loading branch information
meooow25 authored Nov 14, 2024
1 parent c684894 commit 1899771
Show file tree
Hide file tree
Showing 3 changed files with 96 additions and 2 deletions.
2 changes: 2 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@
* Breaking changes
* Parsing fails more eagerly. This affects lazy list parsing and parsing via
the `Regex.Base` functions `prepareParser` and `stepParser`.
* Additions
* Added `Regex.Base.parseNext`.

### 0.1.0.0 -- 2024-03-04

Expand Down
5 changes: 3 additions & 2 deletions src/Regex/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module Regex.Base
, P.finishParser
, P.Foldr
, P.parseFoldr
, P.parseNext

-- * @RE@s and combinators
, R.token
Expand Down Expand Up @@ -67,8 +68,8 @@ import qualified Regex.Internal.Parser as P
-- a large amount of control over the parsing process, making it possible to
-- parse in a resumable or even branching manner.
--
-- As a simpler alternative to the trio of functions above, @parseFoldr@ can be
-- used on any sequence type that can be folded over.
-- @parseFoldr@ and @parseNext@ may be more convenient to use, depending on the
-- sequence to parse.
--

-- $strict
Expand Down
91 changes: 91 additions & 0 deletions src/Regex/Internal/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Regex.Internal.Parser
, finishParser
, Foldr
, parseFoldr
, parseNext
) where

import Control.Applicative
Expand Down Expand Up @@ -371,12 +372,102 @@ type Foldr f a = forall b. (a -> b -> b) -> b -> f -> b
-- | \(O(mn \log m)\). Run a parser given a sequence @f@ and a fold function.
--
-- Returns early on parse failure, if the fold can short circuit.
--
-- ==== __Examples__
--
-- @
-- import qualified Data.Vector.Generic as VG -- from vector
--
-- import Regex.Base (Parser)
-- import qualified Regex.Base as R
--
-- parseVector :: VG.Vector v c => Parser c a -> v c -> Maybe a
-- parseVector p v = R.'parseFoldr' VG.foldr p v
-- @
--
-- >>> import Control.Applicative (many)
-- >>> import qualified Data.Vector as V
-- >>> import Regex.Base (Parser)
-- >>> import qualified Regex.Base as R
-- >>>
-- >>> let p = R.compile $ many ((,) <$> R.satisfy even <*> R.satisfy odd) :: Parser Int [(Int, Int)]
-- >>> parseVector p (V.fromList [0..5])
-- Just [(0,1),(2,3),(4,5)]
-- >>> parseVector p (V.fromList [0,2..6])
-- Nothing
--
parseFoldr :: Foldr f c -> Parser c a -> f -> Maybe a
parseFoldr fr = \p xs -> prepareParser p >>= fr f finishParser xs
where
f c k = X.oneShot (\ps -> stepParser ps c >>= k)
{-# INLINE parseFoldr #-}

-- | \(O(mn \log m)\). Run a parser given a \"@next@\" action.
--
-- Calls @next@ repeatedly to yield elements. A @Nothing@ is interpreted as
-- end-of-sequence. May return without exhausting the input on parse failure.
--
-- ==== __Examples__
--
-- @
-- import Control.Monad.Trans.State.Strict (StateT(..)) -- from transformers
-- import qualified Streaming.Prelude as S -- from streaming
-- import Streaming.Prelude (Stream, Of)
--
-- import Regex.Base (Parser)
-- import qualified Regex.Base as R
--
-- parseStream
-- :: Monad m => Parser c a -> Stream (Of c) m r -> m (Maybe a, Stream (Of c) m r)
-- parseStream p s = runStateT (R.'parseNext' p next) s
-- where
-- next = StateT $ fmap f . S.next
-- f (Left r) = (Nothing, pure r)
-- f (Right (c, s')) = (Just c, s')
-- @
--
-- >>> import Control.Applicative (many)
-- >>> import Data.Foldable (traverse_)
-- >>> import qualified Streaming.Prelude as S
-- >>> import Regex.Base (Parser)
-- >>> import qualified Regex.Base as R
-- >>>
-- >>> let p = R.compile $ many ((,) <$> R.satisfy even <*> R.satisfy odd) :: Parser Int [(Int, Int)]
-- >>> let printEach = S.chain print . S.each
-- >>> (result, remaining) <- parseStream p (printEach [0..5])
-- 0
-- 1
-- 2
-- 3
-- 4
-- 5
-- >>> result
-- Just [(0,1),(2,3),(4,5)]
-- >>> S.toList remaining
-- [] :> ()
-- >>> (result, remaining) <- parseStream p (printEach [0,2..6])
-- 0
-- 2
-- >>> result
-- Nothing
-- >>> S.toList remaining
-- 4
-- 6
-- [4,6] :> ()
--
-- @since FIXME
parseNext :: Monad m => Parser c a -> m (Maybe c) -> m (Maybe a)
parseNext p next = case prepareParser p of
Nothing -> pure Nothing
Just ps -> loop ps
where
loop ps = next >>= \m -> case m of
Nothing -> pure (finishParser ps)
Just c -> case stepParser ps c of
Nothing -> pure Nothing
Just ps' -> loop ps'
{-# INLINE parseNext #-}

---------
-- Util
---------
Expand Down

0 comments on commit 1899771

Please sign in to comment.