{-# LANGUAGE CPP #-}
module Streamly.Internal.Data.Parser.ParserD
(
Parser (..)
, ParseError (..)
, Step (..)
, Initial (..)
, toFold
, fromFold
, fromFoldMaybe
, fromPure
, fromEffect
, die
, dieM
, lmap
, lmapM
, postscan
, filter
, rmapM
, peek
, one
, oneEq
, oneNotEq
, oneOf
, noneOf
, eof
, satisfy
, maybe
, either
, lookAhead
, takeBetween
, takeEQ
, takeGE
, takeP
, listEq
, listEqBy
, streamEqBy
, subsequenceBy
, takeWhile
, takeWhileP
, takeWhile1
, dropWhile
, takeEndBy
, takeEndBy_
, takeEndByEsc
, takeStartBy
, takeStartBy_
, takeEitherSepBy
, wordBy
, groupBy
, groupByRolling
, groupByRollingEither
, wordFramedBy
, wordWithQuotes
, wordKeepQuotes
, wordProcessQuotes
, takeFramedBy_
, takeFramedByEsc_
, takeFramedByGeneric
, blockWithQuotes
, span
, spanBy
, spanByRolling
, splitWith
, split_
, alt
, sequence
, concatMap
, count
, countBetween
, manyP
, many
, some
, deintercalate
, deintercalate1
, deintercalateAll
, sepBy1
, sepBy
, sepByAll
, manyTillP
, manyTill
, manyThen
, roundRobin
, retryMaxTotal
, retryMaxSuccessive
, retry
, zipWithM
, zip
, indexed
, makeIndexFilter
, sampleFromthen
, next
)
where
#include "inline.hs"
#include "assert.hs"
import Control.Monad (when)
import Data.Bifunctor (first)
import Fusion.Plugin.Types (Fuse(..))
import Streamly.Internal.Data.Fold.Type (Fold(..))
import Streamly.Internal.Data.SVar.Type (defState)
import Streamly.Internal.Data.Either.Strict (Either'(..))
import Streamly.Internal.Data.Maybe.Strict (Maybe'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
import Streamly.Internal.Data.Stream.StreamD.Type (Stream)
import qualified Data.Foldable as Foldable
import qualified Streamly.Internal.Data.Fold.Type as FL
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
import qualified Streamly.Internal.Data.Stream.StreamD.Generate as D
import Prelude hiding
(any, all, take, takeWhile, sequence, concatMap, maybe, either, span
, zip, filter, dropWhile)
import Streamly.Internal.Data.Parser.ParserD.Type
#include "DocTestDataParser.hs"
{-# INLINE toFold #-}
toFold :: Monad m => Parser a m b -> Fold m a b
toFold :: forall (m :: * -> *) a b. Monad m => Parser a m b -> Fold m a b
toFold (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinitial s -> m (Step s b)
pextract) = forall (m :: * -> *) a b s.
(s -> a -> m (Step s b))
-> m (Step s b) -> (s -> m b) -> Fold m a b
Fold s -> a -> m (Step s b)
step m (Step s b)
initial s -> m b
extract
where
initial :: m (Step s b)
initial = do
Initial s b
r <- m (Initial s b)
pinitial
case Initial s b
r of
IPartial s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Step s b
FL.Partial s
s
IDone b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Step s b
FL.Done b
b
IError String
err ->
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"toFold: parser throws error in initial" forall a. [a] -> [a] -> [a]
++ String
err
perror :: a -> a
perror a
n = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"toFold: parser backtracks in Partial: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
n
cerror :: a -> a
cerror a
n = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"toFold: parser backtracks in Continue: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
n
derror :: a -> a
derror a
n = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"toFold: parser backtracks in Done: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
n
eerror :: String -> a
eerror String
err = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"toFold: parser throws error: " forall a. [a] -> [a] -> [a]
++ String
err
step :: s -> a -> m (Step s b)
step s
st a
a = do
Step s b
r <- s -> a -> m (Step s b)
pstep s
st a
a
case Step s b
r of
Partial Int
0 s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Step s b
FL.Partial s
s
Continue Int
0 s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Step s b
FL.Partial s
s
Done Int
0 b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Step s b
FL.Done b
b
Partial Int
n s
_ -> forall {a} {a}. Show a => a -> a
perror Int
n
Continue Int
n s
_ -> forall {a} {a}. Show a => a -> a
cerror Int
n
Done Int
n b
_ -> forall {a} {a}. Show a => a -> a
derror Int
n
Error String
err -> forall {a}. String -> a
eerror String
err
extract :: s -> m b
extract s
st = do
Step s b
r <- s -> m (Step s b)
pextract s
st
case Step s b
r of
Done Int
0 b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return b
b
Partial Int
n s
_ -> forall {a} {a}. Show a => a -> a
perror Int
n
Continue Int
n s
_ -> forall {a} {a}. Show a => a -> a
cerror Int
n
Done Int
n b
_ -> forall {a} {a}. Show a => a -> a
derror Int
n
Error String
err -> forall {a}. String -> a
eerror String
err
{-# INLINE fromFold #-}
fromFold :: Monad m => Fold m a b -> Parser a m b
fromFold :: forall (m :: * -> *) a b. Monad m => Fold m a b -> Parser a m b
fromFold (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
step m (Initial s b)
initial forall {s}. s -> m (Step s b)
extract
where
initial :: m (Initial s b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. s -> Initial s b
IPartial s
s1
FL.Done b
b -> forall s b. b -> Initial s b
IDone b
b
step :: s -> a -> m (Step s b)
step s
s a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 s
s1
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
extract :: s -> m (Step s b)
extract = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> m b
fextract
{-# INLINE fromFoldMaybe #-}
fromFoldMaybe :: Monad m => String -> Fold m a (Maybe b) -> Parser a m b
fromFoldMaybe :: forall (m :: * -> *) a b.
Monad m =>
String -> Fold m a (Maybe b) -> Parser a m b
fromFoldMaybe String
errMsg (Fold s -> a -> m (Step s (Maybe b))
fstep m (Step s (Maybe b))
finitial s -> m (Maybe b)
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
step m (Initial s b)
initial forall {s}. s -> m (Step s b)
extract
where
initial :: m (Initial s b)
initial = do
Step s (Maybe b)
res <- m (Step s (Maybe b))
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s (Maybe b)
res of
FL.Partial s
s1 -> forall s b. s -> Initial s b
IPartial s
s1
FL.Done Maybe b
b ->
case Maybe b
b of
Just b
x -> forall s b. b -> Initial s b
IDone b
x
Maybe b
Nothing -> forall s b. String -> Initial s b
IError String
errMsg
step :: s -> a -> m (Step s b)
step s
s a
a = do
Step s (Maybe b)
res <- s -> a -> m (Step s (Maybe b))
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s (Maybe b)
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 s
s1
FL.Done Maybe b
b ->
case Maybe b
b of
Just b
x -> forall s b. Int -> b -> Step s b
Done Int
0 b
x
Maybe b
Nothing -> forall s b. String -> Step s b
Error String
errMsg
extract :: s -> m (Step s b)
extract s
s = do
Maybe b
res <- s -> m (Maybe b)
fextract s
s
case Maybe b
res of
Just b
x -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 b
x
Maybe b
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
errMsg
{-# INLINE peek #-}
peek :: Monad m => Parser a m a
peek :: forall (m :: * -> *) a. Monad m => Parser a m a
peek = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {m :: * -> *} {b} {s}. Monad m => () -> b -> m (Step s b)
step forall {b}. m (Initial () b)
initial forall {m :: * -> *} {s} {b}. Monad m => () -> m (Step s b)
extract
where
initial :: m (Initial () b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial ()
step :: () -> b -> m (Step s b)
step () b
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
1 b
a
extract :: () -> m (Step s b)
extract () = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"peek: end of input"
{-# INLINE eof #-}
eof :: Monad m => Parser a m ()
eof :: forall (m :: * -> *) a. Monad m => Parser a m ()
eof = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {m :: * -> *} {p} {s} {b}.
Monad m =>
() -> p -> m (Step s b)
step forall {b}. m (Initial () b)
initial forall {m :: * -> *} {s}. Monad m => () -> m (Step s ())
extract
where
initial :: m (Initial () b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial ()
step :: () -> p -> m (Step s b)
step () p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"eof: not at end of input"
extract :: () -> m (Step s ())
extract () = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 ()
{-# DEPRECATED next "Please use \"fromFold Fold.one\" instead" #-}
{-# INLINE next #-}
next :: Monad m => Parser a m (Maybe a)
next :: forall (m :: * -> *) a. Monad m => Parser a m (Maybe a)
next = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {f :: * -> *} {a} {s}.
Applicative f =>
() -> a -> f (Step s (Maybe a))
step forall {b}. m (Initial () b)
initial forall {f :: * -> *} {s} {a}.
Applicative f =>
() -> f (Step s (Maybe a))
extract
where
initial :: m (Initial () b)
initial = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial ()
step :: () -> a -> f (Step s (Maybe a))
step () a
a = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 (forall a. a -> Maybe a
Just a
a)
extract :: () -> f (Step s (Maybe a))
extract () = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 forall a. Maybe a
Nothing
{-# INLINE either #-}
either :: Monad m => (a -> Either String b) -> Parser a m b
either :: forall (m :: * -> *) a b.
Monad m =>
(a -> Either String b) -> Parser a m b
either a -> Either String b
f = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {m :: * -> *} {s}. Monad m => () -> a -> m (Step s b)
step forall {b}. m (Initial () b)
initial forall {m :: * -> *} {s} {b}. Monad m => () -> m (Step s b)
extract
where
initial :: m (Initial () b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial ()
step :: () -> a -> m (Step s b)
step () a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case a -> Either String b
f a
a of
Right b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
Left String
err -> forall s b. String -> Step s b
Error String
err
extract :: () -> m (Step s b)
extract () = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"end of input"
{-# INLINE maybe #-}
maybe :: Monad m => (a -> Maybe b) -> Parser a m b
maybe :: forall (m :: * -> *) a b. Monad m => (a -> Maybe b) -> Parser a m b
maybe a -> Maybe b
parserF = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {m :: * -> *} {s}. Monad m => () -> a -> m (Step s b)
step forall {b}. m (Initial () b)
initial forall {m :: * -> *} {s} {b}. Monad m => () -> m (Step s b)
extract
where
initial :: m (Initial () b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial ()
step :: () -> a -> m (Step s b)
step () a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case a -> Maybe b
parserF a
a of
Just b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
Maybe b
Nothing -> forall s b. String -> Step s b
Error String
"maybe: predicate failed"
extract :: () -> m (Step s b)
extract () = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"maybe: end of input"
{-# INLINE satisfy #-}
satisfy :: Monad m => (a -> Bool) -> Parser a m a
satisfy :: forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
satisfy a -> Bool
predicate = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {m :: * -> *} {s}. Monad m => () -> a -> m (Step s a)
step forall {b}. m (Initial () b)
initial forall {m :: * -> *} {s} {b}. Monad m => () -> m (Step s b)
extract
where
initial :: m (Initial () b)
initial = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial ()
step :: () -> a -> m (Step s a)
step () a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if a -> Bool
predicate a
a
then forall s b. Int -> b -> Step s b
Done Int
0 a
a
else forall s b. String -> Step s b
Error String
"satisfy: predicate failed"
extract :: () -> m (Step s b)
extract () = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"satisfy: end of input"
{-# INLINE one #-}
one :: Monad m => Parser a m a
one :: forall (m :: * -> *) a. Monad m => Parser a m a
one = forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
satisfy forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const Bool
True
{-# INLINE oneEq #-}
oneEq :: (Monad m, Eq a) => a -> Parser a m a
oneEq :: forall (m :: * -> *) a. (Monad m, Eq a) => a -> Parser a m a
oneEq a
x = forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
satisfy (forall a. Eq a => a -> a -> Bool
== a
x)
{-# INLINE oneNotEq #-}
oneNotEq :: (Monad m, Eq a) => a -> Parser a m a
oneNotEq :: forall (m :: * -> *) a. (Monad m, Eq a) => a -> Parser a m a
oneNotEq a
x = forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
satisfy (forall a. Eq a => a -> a -> Bool
/= a
x)
{-# INLINE oneOf #-}
oneOf :: (Monad m, Eq a, Foldable f) => f a -> Parser a m a
oneOf :: forall (m :: * -> *) a (f :: * -> *).
(Monad m, Eq a, Foldable f) =>
f a -> Parser a m a
oneOf f a
xs = forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
satisfy (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`Foldable.elem` f a
xs)
{-# INLINE noneOf #-}
noneOf :: (Monad m, Eq a, Foldable f) => f a -> Parser a m a
noneOf :: forall (m :: * -> *) a (f :: * -> *).
(Monad m, Eq a, Foldable f) =>
f a -> Parser a m a
noneOf f a
xs = forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m a
satisfy (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`Foldable.notElem` f a
xs)
{-# ANN type Tuple'Fused Fuse #-}
data Tuple'Fused a b = Tuple'Fused !a !b deriving Int -> Tuple'Fused a b -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> Tuple'Fused a b -> ShowS
forall a b. (Show a, Show b) => [Tuple'Fused a b] -> ShowS
forall a b. (Show a, Show b) => Tuple'Fused a b -> String
showList :: [Tuple'Fused a b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [Tuple'Fused a b] -> ShowS
show :: Tuple'Fused a b -> String
$cshow :: forall a b. (Show a, Show b) => Tuple'Fused a b -> String
showsPrec :: Int -> Tuple'Fused a b -> ShowS
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> Tuple'Fused a b -> ShowS
Show
{-# INLINE takeBetween #-}
takeBetween :: Monad m => Int -> Int -> Fold m a b -> Parser a m b
takeBetween :: forall (m :: * -> *) a b.
Monad m =>
Int -> Int -> Fold m a b -> Parser a m b
takeBetween Int
low Int
high (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser Tuple'Fused Int s -> a -> m (Step (Tuple'Fused Int s) b)
step m (Initial (Tuple'Fused Int s) b)
initial (forall {s}. (Int -> String) -> Tuple'Fused Int s -> m (Step s b)
extract forall a. Show a => a -> String
streamErr)
where
streamErr :: a -> String
streamErr a
i =
String
"takeBetween: Expecting alteast " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
low
forall a. [a] -> [a] -> [a]
++ String
" elements, got " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
i
invalidRange :: String
invalidRange =
String
"takeBetween: lower bound - " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
low
forall a. [a] -> [a] -> [a]
++ String
" is greater than higher bound - " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
high
foldErr :: Int -> String
foldErr :: Int -> String
foldErr Int
i =
String
"takeBetween: the collecting fold terminated after"
forall a. [a] -> [a] -> [a]
++ String
" consuming" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
i forall a. [a] -> [a] -> [a]
++ String
" elements"
forall a. [a] -> [a] -> [a]
++ String
" minimum" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
low forall a. [a] -> [a] -> [a]
++ String
" elements needed"
{-# INLINE inext #-}
inext :: Int -> Step s b -> m (Initial (Tuple'Fused Int s) b)
inext Int
i Step s b
res =
let i1 :: Int
i1 = Int
i forall a. Num a => a -> a -> a
+ Int
1
in case Step s b
res of
FL.Partial s
s -> do
let s1 :: Tuple'Fused Int s
s1 = forall a b. a -> b -> Tuple'Fused a b
Tuple'Fused Int
i1 s
s
if Int
i1 forall a. Ord a => a -> a -> Bool
< Int
high
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial Tuple'Fused Int s
s1
else forall {s}. (Int -> String) -> Tuple'Fused Int s -> m (Initial s b)
iextract Int -> String
foldErr Tuple'Fused Int s
s1
FL.Done b
b ->
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ if Int
i1 forall a. Ord a => a -> a -> Bool
>= Int
low
then forall s b. b -> Initial s b
IDone b
b
else forall s b. String -> Initial s b
IError (Int -> String
foldErr Int
i1)
initial :: m (Initial (Tuple'Fused Int s) b)
initial = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
low forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
high forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
low forall a. Ord a => a -> a -> Bool
> Int
high)
forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => String -> a
error String
invalidRange
m (Step s b)
finitial forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Step s b -> m (Initial (Tuple'Fused Int s) b)
inext (-Int
1)
{-# INLINE snext #-}
snext :: Int -> Step s b -> m (Step (Tuple'Fused Int s) b)
snext Int
i Step s b
res =
let i1 :: Int
i1 = Int
i forall a. Num a => a -> a -> a
+ Int
1
in case Step s b
res of
FL.Partial s
s -> do
let s1 :: Tuple'Fused Int s
s1 = forall a b. a -> b -> Tuple'Fused a b
Tuple'Fused Int
i1 s
s
if Int
i1 forall a. Ord a => a -> a -> Bool
< Int
high
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 Tuple'Fused Int s
s1
else forall {s}. (Int -> String) -> Tuple'Fused Int s -> m (Step s b)
extract Int -> String
foldErr Tuple'Fused Int s
s1
FL.Done b
b ->
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ if Int
i1 forall a. Ord a => a -> a -> Bool
>= Int
low
then forall s b. Int -> b -> Step s b
Done Int
0 b
b
else forall s b. String -> Step s b
Error (Int -> String
foldErr Int
i1)
step :: Tuple'Fused Int s -> a -> m (Step (Tuple'Fused Int s) b)
step (Tuple'Fused Int
i s
s) a
a = s -> a -> m (Step s b)
fstep s
s a
a forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> Step s b -> m (Step (Tuple'Fused Int s) b)
snext Int
i
extract :: (Int -> String) -> Tuple'Fused Int s -> m (Step s b)
extract Int -> String
f (Tuple'Fused Int
i s
s)
| Int
i forall a. Ord a => a -> a -> Bool
>= Int
low Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
<= Int
high = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) (s -> m b
fextract s
s)
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error (Int -> String
f Int
i)
iextract :: (Int -> String) -> Tuple'Fused Int s -> m (Initial s b)
iextract Int -> String
f (Tuple'Fused Int
i s
s)
| Int
i forall a. Ord a => a -> a -> Bool
>= Int
low Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
<= Int
high = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall s b. b -> Initial s b
IDone (s -> m b
fextract s
s)
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Initial s b
IError (Int -> String
f Int
i)
{-# INLINE takeEQ #-}
takeEQ :: Monad m => Int -> Fold m a b -> Parser a m b
takeEQ :: forall (m :: * -> *) a b.
Monad m =>
Int -> Fold m a b -> Parser a m b
takeEQ Int
n (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser Tuple'Fused Int s -> a -> m (Step (Tuple'Fused Int s) b)
step m (Initial (Tuple'Fused Int s) b)
initial forall {m :: * -> *} {a} {b} {s} {b}.
(Monad m, Show a, Num a) =>
Tuple'Fused a b -> m (Step s b)
extract
where
initial :: m (Initial (Tuple'Fused Int s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
case Step s b
res of
FL.Partial s
s ->
if Int
n forall a. Ord a => a -> a -> Bool
> Int
0
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple'Fused a b
Tuple'Fused Int
1 s
s
else forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall s b. b -> Initial s b
IDone (s -> m b
fextract s
s)
FL.Done b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if Int
n forall a. Ord a => a -> a -> Bool
> Int
0
then forall s b. String -> Initial s b
IError
forall a b. (a -> b) -> a -> b
$ String
"takeEQ: Expecting exactly " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
forall a. [a] -> [a] -> [a]
++ String
" elements, fold terminated without"
forall a. [a] -> [a] -> [a]
++ String
" consuming any elements"
else forall s b. b -> Initial s b
IDone b
b
step :: Tuple'Fused Int s -> a -> m (Step (Tuple'Fused Int s) b)
step (Tuple'Fused Int
i1 s
r) a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
r a
a
if Int
n forall a. Ord a => a -> a -> Bool
> Int
i1
then
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple'Fused a b
Tuple'Fused (Int
i1 forall a. Num a => a -> a -> a
+ Int
1) s
s
FL.Done b
_ ->
forall s b. String -> Step s b
Error
forall a b. (a -> b) -> a -> b
$ String
"takeEQ: Expecting exactly " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
forall a. [a] -> [a] -> [a]
++ String
" elements, fold terminated on " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
i1
else
forall s b. Int -> b -> Step s b
Done Int
0
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case Step s b
res of
FL.Partial s
s -> s -> m b
fextract s
s
FL.Done b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return b
b
extract :: Tuple'Fused a b -> m (Step s b)
extract (Tuple'Fused a
i b
_) =
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error
forall a b. (a -> b) -> a -> b
$ String
"takeEQ: Expecting exactly " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
forall a. [a] -> [a] -> [a]
++ String
" elements, input terminated on " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (a
i forall a. Num a => a -> a -> a
- a
1)
{-# ANN type TakeGEState Fuse #-}
data TakeGEState s =
TakeGELT !Int !s
| TakeGEGE !s
{-# INLINE takeGE #-}
takeGE :: Monad m => Int -> Fold m a b -> Parser a m b
takeGE :: forall (m :: * -> *) a b.
Monad m =>
Int -> Fold m a b -> Parser a m b
takeGE Int
n (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser TakeGEState s -> a -> m (Step (TakeGEState s) b)
step m (Initial (TakeGEState s) b)
initial forall {s}. TakeGEState s -> m (Step s b)
extract
where
initial :: m (Initial (TakeGEState s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
case Step s b
res of
FL.Partial s
s ->
if Int
n forall a. Ord a => a -> a -> Bool
> Int
0
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall s. Int -> s -> TakeGEState s
TakeGELT Int
1 s
s
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall s. s -> TakeGEState s
TakeGEGE s
s
FL.Done b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if Int
n forall a. Ord a => a -> a -> Bool
> Int
0
then forall s b. String -> Initial s b
IError
forall a b. (a -> b) -> a -> b
$ String
"takeGE: Expecting at least " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
forall a. [a] -> [a] -> [a]
++ String
" elements, fold terminated without"
forall a. [a] -> [a] -> [a]
++ String
" consuming any elements"
else forall s b. b -> Initial s b
IDone b
b
step :: TakeGEState s -> a -> m (Step (TakeGEState s) b)
step (TakeGELT Int
i1 s
r) a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
r a
a
if Int
n forall a. Ord a => a -> a -> Bool
> Int
i1
then
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s. Int -> s -> TakeGEState s
TakeGELT (Int
i1 forall a. Num a => a -> a -> a
+ Int
1) s
s
FL.Done b
_ ->
forall s b. String -> Step s b
Error
forall a b. (a -> b) -> a -> b
$ String
"takeGE: Expecting at least " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
forall a. [a] -> [a] -> [a]
++ String
" elements, fold terminated on " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
i1
else
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s. s -> TakeGEState s
TakeGEGE s
s
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step (TakeGEGE s
r) a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
r a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s. s -> TakeGEState s
TakeGEGE s
s
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
extract :: TakeGEState s -> m (Step s b)
extract (TakeGELT Int
i s
_) =
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error
forall a b. (a -> b) -> a -> b
$ String
"takeGE: Expecting at least " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
forall a. [a] -> [a] -> [a]
++ String
" elements, input terminated on " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Int
i forall a. Num a => a -> a -> a
- Int
1)
extract (TakeGEGE s
r) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
r
{-# INLINE takeWhileP #-}
takeWhileP :: Monad m => (a -> Bool) -> Parser a m b -> Parser a m b
takeWhileP :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Parser a m b -> Parser a m b
takeWhileP a -> Bool
predicate (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinitial s -> m (Step s b)
pextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
step m (Initial s b)
pinitial s -> m (Step s b)
pextract
where
step :: s -> a -> m (Step s b)
step s
s a
a =
if a -> Bool
predicate a
a
then s -> a -> m (Step s b)
pstep s
s a
a
else do
Step s b
r <- s -> m (Step s b)
pextract s
s
case Step s b
r of
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
Done Int
n b
s1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done (Int
n forall a. Num a => a -> a -> a
+ Int
1) b
s1
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Bug: takeWhileP: Partial in extract"
Continue Int
n s
s1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue (Int
n forall a. Num a => a -> a -> a
+ Int
1) s
s1
{-# INLINE takeWhile #-}
takeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Parser a m b
takeWhile :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Parser a m b
takeWhile a -> Bool
predicate (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
step m (Initial s b)
initial forall {s}. s -> m (Step s b)
extract
where
initial :: m (Initial s b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial s
s
FL.Done b
b -> forall s b. b -> Initial s b
IDone b
b
step :: s -> a -> m (Step s b)
step s
s a
a =
if a -> Bool
predicate a
a
then do
Step s b
fres <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
fres of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 s
s1
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
else forall s b. Int -> b -> Step s b
Done Int
1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
extract :: s -> m (Step s b)
extract s
s = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) (s -> m b
fextract s
s)
{-# INLINE takeWhile1 #-}
takeWhile1 :: Monad m => (a -> Bool) -> Fold m a b -> Parser a m b
takeWhile1 :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Parser a m b
takeWhile1 a -> Bool
predicate (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {a}. Either' s s -> a -> m (Step (Either' a s) b)
step forall {b} {b}. m (Initial (Either' s b) b)
initial forall {a} {s}. Either' a s -> m (Step s b)
extract
where
initial :: m (Initial (Either' s b) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall a b. a -> Either' a b
Left' s
s)
FL.Done b
_ ->
forall s b. String -> Initial s b
IError
forall a b. (a -> b) -> a -> b
$ String
"takeWhile1: fold terminated without consuming:"
forall a. [a] -> [a] -> [a]
++ String
" any element"
{-# INLINE process #-}
process :: s -> a -> m (Step (Either' a s) b)
process s
s a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 (forall a b. b -> Either' a b
Right' s
s1)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step :: Either' s s -> a -> m (Step (Either' a s) b)
step (Left' s
s) a
a =
if a -> Bool
predicate a
a
then forall {a}. s -> a -> m (Step (Either' a s) b)
process s
s a
a
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"takeWhile1: predicate failed on first element"
step (Right' s
s) a
a =
if a -> Bool
predicate a
a
then forall {a}. s -> a -> m (Step (Either' a s) b)
process s
s a
a
else do
b
b <- s -> m b
fextract s
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
1 b
b
extract :: Either' a s -> m (Step s b)
extract (Left' a
_) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"takeWhile1: end of input"
extract (Right' s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) (s -> m b
fextract s
s)
{-# INLINE dropWhile #-}
dropWhile :: Monad m => (a -> Bool) -> Parser a m ()
dropWhile :: forall (m :: * -> *) a. Monad m => (a -> Bool) -> Parser a m ()
dropWhile a -> Bool
p = forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Parser a m b
takeWhile a -> Bool
p forall (m :: * -> *) a. Monad m => Fold m a ()
FL.drain
{-# ANN type FramedEscState Fuse #-}
data FramedEscState s =
FrameEscInit !s | FrameEscGo !s !Int | FrameEscEsc !s !Int
{-# INLINE takeFramedByGeneric #-}
takeFramedByGeneric :: Monad m =>
Maybe (a -> Bool)
-> Maybe (a -> Bool)
-> Maybe (a -> Bool)
-> Fold m a b
-> Parser a m b
takeFramedByGeneric :: forall (m :: * -> *) a b.
Monad m =>
Maybe (a -> Bool)
-> Maybe (a -> Bool)
-> Maybe (a -> Bool)
-> Fold m a b
-> Parser a m b
takeFramedByGeneric Maybe (a -> Bool)
esc Maybe (a -> Bool)
begin Maybe (a -> Bool)
end (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser FramedEscState s -> a -> m (Step (FramedEscState s) b)
step forall {b}. m (Initial (FramedEscState s) b)
initial forall {s}. FramedEscState s -> m (Step s b)
extract
where
initial :: m (Initial (FramedEscState s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall s. s -> FramedEscState s
FrameEscInit s
s)
FL.Done b
_ ->
forall a. HasCallStack => String -> a
error String
"takeFramedByGeneric: fold done without input"
{-# INLINE process #-}
process :: s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
0 (forall s. s -> Int -> FramedEscState s
FrameEscGo s
s1 Int
n)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
{-# INLINE processNoEsc #-}
processNoEsc :: s -> a -> Int -> m (Step (FramedEscState s) b)
processNoEsc s
s a
a Int
n =
case Maybe (a -> Bool)
end of
Just a -> Bool
isEnd ->
case Maybe (a -> Bool)
begin of
Just a -> Bool
isBegin ->
if a -> Bool
isEnd a
a
then
if Int
n forall a. Eq a => a -> a -> Bool
== Int
0
then forall s b. Int -> b -> Step s b
Done Int
0 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
else s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a (Int
n forall a. Num a => a -> a -> a
- Int
1)
else
let n1 :: Int
n1 = if a -> Bool
isBegin a
a then Int
n forall a. Num a => a -> a -> a
+ Int
1 else Int
n
in s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n1
Maybe (a -> Bool)
Nothing ->
if a -> Bool
isEnd a
a
then forall s b. Int -> b -> Step s b
Done Int
0 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
else s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n
Maybe (a -> Bool)
Nothing ->
case Maybe (a -> Bool)
begin of
Just a -> Bool
isBegin ->
if a -> Bool
isBegin a
a
then forall s b. Int -> b -> Step s b
Done Int
0 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
else s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n
Maybe (a -> Bool)
Nothing ->
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"takeFramedByGeneric: "
forall a. [a] -> [a] -> [a]
++ String
"Both begin and end frame predicate missing"
{-# INLINE processCheckEsc #-}
processCheckEsc :: s -> a -> Int -> m (Step (FramedEscState s) b)
processCheckEsc s
s a
a Int
n =
case Maybe (a -> Bool)
esc of
Just a -> Bool
isEsc ->
if a -> Bool
isEsc a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s. s -> Int -> FramedEscState s
FrameEscEsc s
s Int
n
else s -> a -> Int -> m (Step (FramedEscState s) b)
processNoEsc s
s a
a Int
n
Maybe (a -> Bool)
Nothing -> s -> a -> Int -> m (Step (FramedEscState s) b)
processNoEsc s
s a
a Int
n
step :: FramedEscState s -> a -> m (Step (FramedEscState s) b)
step (FrameEscInit s
s) a
a =
case Maybe (a -> Bool)
begin of
Just a -> Bool
isBegin ->
if a -> Bool
isBegin a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 (forall s. s -> Int -> FramedEscState s
FrameEscGo s
s Int
0)
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"takeFramedByGeneric: missing frame start"
Maybe (a -> Bool)
Nothing ->
case Maybe (a -> Bool)
end of
Just a -> Bool
isEnd ->
if a -> Bool
isEnd a
a
then forall s b. Int -> b -> Step s b
Done Int
0 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
else s -> a -> Int -> m (Step (FramedEscState s) b)
processCheckEsc s
s a
a Int
0
Maybe (a -> Bool)
Nothing ->
forall a. HasCallStack => String -> a
error String
"Both begin and end frame predicate missing"
step (FrameEscGo s
s Int
n) a
a = s -> a -> Int -> m (Step (FramedEscState s) b)
processCheckEsc s
s a
a Int
n
step (FrameEscEsc s
s Int
n) a
a = s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n
err :: String -> m (Step s b)
err = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s b. String -> Step s b
Error
extract :: FramedEscState s -> m (Step s b)
extract (FrameEscInit s
_) =
forall {s} {b}. String -> m (Step s b)
err String
"takeFramedByGeneric: empty token"
extract (FrameEscGo s
s Int
_) =
case Maybe (a -> Bool)
begin of
Just a -> Bool
_ ->
case Maybe (a -> Bool)
end of
Maybe (a -> Bool)
Nothing -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
Just a -> Bool
_ -> forall {s} {b}. String -> m (Step s b)
err String
"takeFramedByGeneric: missing frame end"
Maybe (a -> Bool)
Nothing -> forall {s} {b}. String -> m (Step s b)
err String
"takeFramedByGeneric: missing closing frame"
extract (FrameEscEsc s
_ Int
_) = forall {s} {b}. String -> m (Step s b)
err String
"takeFramedByGeneric: trailing escape"
data BlockParseState s =
BlockInit !s
| BlockUnquoted !Int !s
| BlockQuoted !Int !s
| BlockQuotedEsc !Int !s
{-# INLINE blockWithQuotes #-}
blockWithQuotes :: (Monad m, Eq a) =>
(a -> Bool)
-> (a -> Bool)
-> a
-> a
-> Fold m a b
-> Parser a m b
blockWithQuotes :: forall (m :: * -> *) a b.
(Monad m, Eq a) =>
(a -> Bool) -> (a -> Bool) -> a -> a -> Fold m a b -> Parser a m b
blockWithQuotes a -> Bool
isEsc a -> Bool
isQuote a
bopen a
bclose
(Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser BlockParseState s -> a -> m (Step (BlockParseState s) b)
step forall {b}. m (Initial (BlockParseState s) b)
initial forall {s}. BlockParseState s -> m (Step s b)
extract
where
initial :: m (Initial (BlockParseState s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall s. s -> BlockParseState s
BlockInit s
s)
FL.Done b
_ ->
forall a. HasCallStack => String -> a
error String
"blockWithQuotes: fold finished without input"
{-# INLINE process #-}
process :: s -> a -> (s -> s) -> m (Step s b)
process s
s a
a s -> s
nextState = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
0 (s -> s
nextState s
s1)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step :: BlockParseState s -> a -> m (Step (BlockParseState s) b)
step (BlockInit s
s) a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ if a
a forall a. Eq a => a -> a -> Bool
== a
bopen
then forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s. Int -> s -> BlockParseState s
BlockUnquoted Int
1 s
s
else forall s b. String -> Step s b
Error String
"blockWithQuotes: missing block start"
step (BlockUnquoted Int
level s
s) a
a
| a
a forall a. Eq a => a -> a -> Bool
== a
bopen = forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockUnquoted (Int
level forall a. Num a => a -> a -> a
+ Int
1))
| a
a forall a. Eq a => a -> a -> Bool
== a
bclose =
if Int
level forall a. Eq a => a -> a -> Bool
== Int
1
then forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) (s -> m b
fextract s
s)
else forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockUnquoted (Int
level forall a. Num a => a -> a -> a
- Int
1))
| a -> Bool
isQuote a
a = forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockQuoted Int
level)
| Bool
otherwise = forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockUnquoted Int
level)
step (BlockQuoted Int
level s
s) a
a
| a -> Bool
isEsc a
a = forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockQuotedEsc Int
level)
| Bool
otherwise =
if a -> Bool
isQuote a
a
then forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockUnquoted Int
level)
else forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockQuoted Int
level)
step (BlockQuotedEsc Int
level s
s) a
a = forall {s}. s -> a -> (s -> s) -> m (Step s b)
process s
s a
a (forall s. Int -> s -> BlockParseState s
BlockQuoted Int
level)
err :: String -> m (Step s b)
err = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s b. String -> Step s b
Error
extract :: BlockParseState s -> m (Step s b)
extract (BlockInit s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (BlockUnquoted Int
level s
_) =
forall {s} {b}. String -> m (Step s b)
err forall a b. (a -> b) -> a -> b
$ String
"blockWithQuotes: finished at block nest level " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
level
extract (BlockQuoted Int
level s
_) =
forall {s} {b}. String -> m (Step s b)
err forall a b. (a -> b) -> a -> b
$ String
"blockWithQuotes: finished, inside an unfinished quote, "
forall a. [a] -> [a] -> [a]
++ String
"at block nest level " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
level
extract (BlockQuotedEsc Int
level s
_) =
forall {s} {b}. String -> m (Step s b)
err forall a b. (a -> b) -> a -> b
$ String
"blockWithQuotes: finished, inside an unfinished quote, "
forall a. [a] -> [a] -> [a]
++ String
"after an escape char, at block nest level " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
level
{-# INLINE takeEndBy #-}
takeEndBy :: Monad m => (a -> Bool) -> Parser a m b -> Parser a m b
takeEndBy :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Parser a m b -> Parser a m b
takeEndBy a -> Bool
cond (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinitial s -> m (Step s b)
pextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
step m (Initial s b)
initial s -> m (Step s b)
pextract
where
initial :: m (Initial s b)
initial = m (Initial s b)
pinitial
step :: s -> a -> m (Step s b)
step s
s a
a = do
Step s b
res <- s -> a -> m (Step s b)
pstep s
s a
a
if Bool -> Bool
not (a -> Bool
cond a
a)
then forall (m :: * -> *) a. Monad m => a -> m a
return Step s b
res
else forall (m :: * -> *) s s1 b.
Monad m =>
(s -> m (Step s1 b)) -> Step s b -> m (Step s1 b)
extractStep s -> m (Step s b)
pextract Step s b
res
{-# INLINE takeEndByEsc #-}
takeEndByEsc :: Monad m =>
(a -> Bool) -> (a -> Bool) -> Parser a m b -> Parser a m b
takeEndByEsc :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> (a -> Bool) -> Parser a m b -> Parser a m b
takeEndByEsc a -> Bool
isEsc a -> Bool
isSep (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinitial s -> m (Step s b)
pextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser Either' s s -> a -> m (Step (Either' s s) b)
step forall {b}. m (Initial (Either' s b) b)
initial forall {b} {b}. Either' s b -> m (Step (Either' s b) b)
extract
where
initial :: m (Initial (Either' s b) b)
initial = forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first forall a b. a -> Either' a b
Left' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Initial s b)
pinitial
step :: Either' s s -> a -> m (Step (Either' s s) b)
step (Left' s
s) a
a = do
if a -> Bool
isEsc a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either' a b
Right' s
s
else do
Step s b
res <- s -> a -> m (Step s b)
pstep s
s a
a
if Bool -> Bool
not (a -> Bool
isSep a
a)
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first forall a b. a -> Either' a b
Left' Step s b
res
else forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first forall a b. a -> Either' a b
Left') forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s s1 b.
Monad m =>
(s -> m (Step s1 b)) -> Step s b -> m (Step s1 b)
extractStep s -> m (Step s b)
pextract Step s b
res
step (Right' s
s) a
a = do
Step s b
res <- s -> a -> m (Step s b)
pstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first forall a b. a -> Either' a b
Left' Step s b
res
extract :: Either' s b -> m (Step (Either' s b) b)
extract (Left' s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first forall a b. a -> Either' a b
Left') forall a b. (a -> b) -> a -> b
$ s -> m (Step s b)
pextract s
s
extract (Right' b
_) =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"takeEndByEsc: trailing escape"
{-# INLINE takeEndBy_ #-}
takeEndBy_ :: (a -> Bool) -> Parser a m b -> Parser a m b
takeEndBy_ :: forall a (m :: * -> *) b.
(a -> Bool) -> Parser a m b -> Parser a m b
takeEndBy_ a -> Bool
cond (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinitial s -> m (Step s b)
pextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
step m (Initial s b)
pinitial s -> m (Step s b)
pextract
where
step :: s -> a -> m (Step s b)
step s
s a
a =
if a -> Bool
cond a
a
then s -> m (Step s b)
pextract s
s
else s -> a -> m (Step s b)
pstep s
s a
a
{-# INLINE takeEitherSepBy #-}
takeEitherSepBy ::
(a -> Bool) -> Fold m (Either a b) c -> Parser a m c
takeEitherSepBy :: forall a (m :: * -> *) b c.
(a -> Bool) -> Fold m (Either a b) c -> Parser a m c
takeEitherSepBy a -> Bool
_cond = forall a. HasCallStack => a
undefined
{-# INLINE takeStartBy #-}
takeStartBy :: Monad m => (a -> Bool) -> Fold m a b -> Parser a m b
takeStartBy :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Parser a m b
takeStartBy a -> Bool
cond (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser forall {a}. Either' s s -> a -> m (Step (Either' a s) b)
step forall {b} {b}. m (Initial (Either' s b) b)
initial forall {s}. Either' s s -> m (Step s b)
extract
where
initial :: m (Initial (Either' s b) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall a b. a -> Either' a b
Left' s
s)
FL.Done b
_ -> forall s b. String -> Initial s b
IError String
"takeStartBy: fold done without input"
{-# INLINE process #-}
process :: s -> a -> m (Step (Either' a s) b)
process s
s a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 (forall a b. b -> Either' a b
Right' s
s1)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step :: Either' s s -> a -> m (Step (Either' a s) b)
step (Left' s
s) a
a =
if a -> Bool
cond a
a
then forall {a}. s -> a -> m (Step (Either' a s) b)
process s
s a
a
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"takeStartBy: missing frame start"
step (Right' s
s) a
a =
if Bool -> Bool
not (a -> Bool
cond a
a)
then forall {a}. s -> a -> m (Step (Either' a s) b)
process s
s a
a
else forall s b. Int -> b -> Step s b
Done Int
1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
extract :: Either' s s -> m (Step s b)
extract (Left' s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (Right' s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
{-# INLINE takeStartBy_ #-}
takeStartBy_ :: Monad m => (a -> Bool) -> Fold m a b -> Parser a m b
takeStartBy_ :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Parser a m b
takeStartBy_ a -> Bool
isBegin = forall (m :: * -> *) a b.
Monad m =>
Maybe (a -> Bool)
-> Maybe (a -> Bool)
-> Maybe (a -> Bool)
-> Fold m a b
-> Parser a m b
takeFramedByGeneric forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just a -> Bool
isBegin) forall a. Maybe a
Nothing
{-# INLINE takeFramedByEsc_ #-}
takeFramedByEsc_ :: Monad m =>
(a -> Bool) -> (a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser a m b
takeFramedByEsc_ :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool)
-> (a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser a m b
takeFramedByEsc_ a -> Bool
isEsc a -> Bool
isBegin a -> Bool
isEnd (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser FramedEscState s -> a -> m (Step (FramedEscState s) b)
step forall {b}. m (Initial (FramedEscState s) b)
initial forall {s} {s} {b}. FramedEscState s -> m (Step s b)
extract
where
initial :: m (Initial (FramedEscState s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall s. s -> FramedEscState s
FrameEscInit s
s)
FL.Done b
_ ->
forall a. HasCallStack => String -> a
error String
"takeFramedByEsc_: fold done without input"
{-# INLINE process #-}
process :: s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
0 (forall s. s -> Int -> FramedEscState s
FrameEscGo s
s1 Int
n)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step :: FramedEscState s -> a -> m (Step (FramedEscState s) b)
step (FrameEscInit s
s) a
a =
if a -> Bool
isBegin a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 (forall s. s -> Int -> FramedEscState s
FrameEscGo s
s Int
0)
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"takeFramedByEsc_: missing frame start"
step (FrameEscGo s
s Int
n) a
a =
if a -> Bool
isEsc a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s. s -> Int -> FramedEscState s
FrameEscEsc s
s Int
n
else do
if Bool -> Bool
not (a -> Bool
isEnd a
a)
then
let n1 :: Int
n1 = if a -> Bool
isBegin a
a then Int
n forall a. Num a => a -> a -> a
+ Int
1 else Int
n
in s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n1
else
if Int
n forall a. Eq a => a -> a -> Bool
== Int
0
then forall s b. Int -> b -> Step s b
Done Int
0 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
else s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a (Int
n forall a. Num a => a -> a -> a
- Int
1)
step (FrameEscEsc s
s Int
n) a
a = s -> a -> Int -> m (Step (FramedEscState s) b)
process s
s a
a Int
n
err :: String -> m (Step s b)
err = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s b. String -> Step s b
Error
extract :: FramedEscState s -> m (Step s b)
extract (FrameEscInit s
_) = forall {s} {b}. String -> m (Step s b)
err String
"takeFramedByEsc_: empty token"
extract (FrameEscGo s
_ Int
_) = forall {s} {b}. String -> m (Step s b)
err String
"takeFramedByEsc_: missing frame end"
extract (FrameEscEsc s
_ Int
_) = forall {s} {b}. String -> m (Step s b)
err String
"takeFramedByEsc_: trailing escape"
data FramedState s = FrameInit !s | FrameGo !s Int
{-# INLINE takeFramedBy_ #-}
takeFramedBy_ :: Monad m =>
(a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser a m b
takeFramedBy_ :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser a m b
takeFramedBy_ a -> Bool
isBegin a -> Bool
isEnd (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser FramedState s -> a -> m (Step (FramedState s) b)
step forall {b}. m (Initial (FramedState s) b)
initial forall {s} {s} {b}. FramedState s -> m (Step s b)
extract
where
initial :: m (Initial (FramedState s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall s. s -> FramedState s
FrameInit s
s)
FL.Done b
_ ->
forall a. HasCallStack => String -> a
error String
"takeFramedBy_: fold done without input"
{-# INLINE process #-}
process :: s -> a -> Int -> m (Step (FramedState s) b)
process s
s a
a Int
n = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
0 (forall s. s -> Int -> FramedState s
FrameGo s
s1 Int
n)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step :: FramedState s -> a -> m (Step (FramedState s) b)
step (FrameInit s
s) a
a =
if a -> Bool
isBegin a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 (forall s. s -> Int -> FramedState s
FrameGo s
s Int
0)
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"takeFramedBy_: missing frame start"
step (FrameGo s
s Int
n) a
a
| Bool -> Bool
not (a -> Bool
isEnd a
a) =
let n1 :: Int
n1 = if a -> Bool
isBegin a
a then Int
n forall a. Num a => a -> a -> a
+ Int
1 else Int
n
in s -> a -> Int -> m (Step (FramedState s) b)
process s
s a
a Int
n1
| Int
n forall a. Eq a => a -> a -> Bool
== Int
0 = forall s b. Int -> b -> Step s b
Done Int
0 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
| Bool
otherwise = s -> a -> Int -> m (Step (FramedState s) b)
process s
s a
a (Int
n forall a. Num a => a -> a -> a
- Int
1)
err :: String -> m (Step s b)
err = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s b. String -> Step s b
Error
extract :: FramedState s -> m (Step s b)
extract (FrameInit s
_) = forall {s} {b}. String -> m (Step s b)
err String
"takeFramedBy_: empty token"
extract (FrameGo s
_ Int
_) = forall {s} {b}. String -> m (Step s b)
err String
"takeFramedBy_: missing frame end"
data WordByState s b = WBLeft !s | WBWord !s | WBRight !b
{-# INLINE wordBy #-}
wordBy :: Monad m => (a -> Bool) -> Fold m a b -> Parser a m b
wordBy :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Parser a m b
wordBy a -> Bool
predicate (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser WordByState s b -> a -> m (Step (WordByState s b) b)
step forall {b}. m (Initial (WordByState s b) b)
initial forall {s}. WordByState s b -> m (Step s b)
extract
where
{-# INLINE worder #-}
worder :: s -> a -> m (Step (WordByState s b) b)
worder s
s a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> WordByState s b
WBWord s
s1
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
initial :: m (Initial (WordByState s b) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall s b. s -> WordByState s b
WBLeft s
s
FL.Done b
b -> forall s b. b -> Initial s b
IDone b
b
step :: WordByState s b -> a -> m (Step (WordByState s b) b)
step (WBLeft s
s) a
a =
if Bool -> Bool
not (a -> Bool
predicate a
a)
then forall {b}. s -> a -> m (Step (WordByState s b) b)
worder s
s a
a
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> WordByState s b
WBLeft s
s
step (WBWord s
s) a
a =
if Bool -> Bool
not (a -> Bool
predicate a
a)
then forall {b}. s -> a -> m (Step (WordByState s b) b)
worder s
s a
a
else do
b
b <- s -> m b
fextract s
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. b -> WordByState s b
WBRight b
b
step (WBRight b
b) a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ if Bool -> Bool
not (a -> Bool
predicate a
a)
then forall s b. Int -> b -> Step s b
Done Int
1 b
b
else forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. b -> WordByState s b
WBRight b
b
extract :: WordByState s b -> m (Step s b)
extract (WBLeft s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (WBWord s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (WBRight b
b) = forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
0 b
b)
data WordFramedState s b =
WordFramedSkipPre !s
| WordFramedWord !s !Int
| WordFramedEsc !s !Int
| WordFramedSkipPost !b
{-# INLINE wordFramedBy #-}
wordFramedBy :: Monad m =>
(a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordFramedBy :: forall (m :: * -> *) a b.
Monad m =>
(a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordFramedBy a -> Bool
isEsc a -> Bool
isBegin a -> Bool
isEnd a -> Bool
isSep
(Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser WordFramedState s b -> a -> m (Step (WordFramedState s b) b)
step forall {b} {b}. m (Initial (WordFramedState s b) b)
initial forall {s}. WordFramedState s b -> m (Step s b)
extract
where
initial :: m (Initial (WordFramedState s b) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall s b. s -> WordFramedState s b
WordFramedSkipPre s
s)
FL.Done b
_ ->
forall a. HasCallStack => String -> a
error String
"wordFramedBy: fold done without input"
{-# INLINE process #-}
process :: s -> a -> Int -> m (Step (WordFramedState s b) b)
process s
s a
a Int
n = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
0 (forall s b. s -> Int -> WordFramedState s b
WordFramedWord s
s1 Int
n)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step :: WordFramedState s b -> a -> m (Step (WordFramedState s b) b)
step (WordFramedSkipPre s
s) a
a
| a -> Bool
isEsc a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> Int -> WordFramedState s b
WordFramedEsc s
s Int
0
| a -> Bool
isSep a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> WordFramedState s b
WordFramedSkipPre s
s
| a -> Bool
isBegin a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> Int -> WordFramedState s b
WordFramedWord s
s Int
1
| a -> Bool
isEnd a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"wordFramedBy: missing frame start"
| Bool
otherwise = forall {b}. s -> a -> Int -> m (Step (WordFramedState s b) b)
process s
s a
a Int
0
step (WordFramedWord s
s Int
n) a
a
| a -> Bool
isEsc a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> Int -> WordFramedState s b
WordFramedEsc s
s Int
n
| Int
n forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& a -> Bool
isSep a
a = do
b
b <- s -> m b
fextract s
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. b -> WordFramedState s b
WordFramedSkipPost b
b
| Bool
otherwise = do
if Int
n forall a. Eq a => a -> a -> Bool
== Int
0
then
if a -> Bool
isBegin a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> Int -> WordFramedState s b
WordFramedWord s
s Int
1
else if a -> Bool
isEnd a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"wordFramedBy: missing frame start"
else forall {b}. s -> a -> Int -> m (Step (WordFramedState s b) b)
process s
s a
a Int
n
else
if a -> Bool
isEnd a
a
then
if Int
n forall a. Eq a => a -> a -> Bool
== Int
1
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. s -> Int -> WordFramedState s b
WordFramedWord s
s Int
0
else forall {b}. s -> a -> Int -> m (Step (WordFramedState s b) b)
process s
s a
a (Int
n forall a. Num a => a -> a -> a
- Int
1)
else if a -> Bool
isBegin a
a
then forall {b}. s -> a -> Int -> m (Step (WordFramedState s b) b)
process s
s a
a (Int
n forall a. Num a => a -> a -> a
+ Int
1)
else forall {b}. s -> a -> Int -> m (Step (WordFramedState s b) b)
process s
s a
a Int
n
step (WordFramedEsc s
s Int
n) a
a = forall {b}. s -> a -> Int -> m (Step (WordFramedState s b) b)
process s
s a
a Int
n
step (WordFramedSkipPost b
b) a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ if Bool -> Bool
not (a -> Bool
isSep a
a)
then forall s b. Int -> b -> Step s b
Done Int
1 b
b
else forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b. b -> WordFramedState s b
WordFramedSkipPost b
b
err :: String -> m (Step s b)
err = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s b. String -> Step s b
Error
extract :: WordFramedState s b -> m (Step s b)
extract (WordFramedSkipPre s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (WordFramedWord s
s Int
n) =
if Int
n forall a. Eq a => a -> a -> Bool
== Int
0
then forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
else forall {s} {b}. String -> m (Step s b)
err String
"wordFramedBy: missing frame end"
extract (WordFramedEsc s
_ Int
_) =
forall {s} {b}. String -> m (Step s b)
err String
"wordFramedBy: trailing escape"
extract (WordFramedSkipPost b
b) = forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
0 b
b)
data WordQuotedState s b a =
WordQuotedSkipPre !s
| WordUnquotedWord !s
| WordQuotedWord !s !Int !a !a
| WordUnquotedEsc !s
| WordQuotedEsc !s !Int !a !a
| WordQuotedSkipPost !b
{-# INLINE wordWithQuotes #-}
wordWithQuotes :: (Monad m, Eq a) =>
Bool
-> (a -> a -> Maybe a)
-> a
-> (a -> Maybe a)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordWithQuotes :: forall (m :: * -> *) a b.
(Monad m, Eq a) =>
Bool
-> (a -> a -> Maybe a)
-> a
-> (a -> Maybe a)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordWithQuotes Bool
keepQuotes a -> a -> Maybe a
tr a
escChar a -> Maybe a
toRight a -> Bool
isSep
(Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser WordQuotedState s b a -> a -> m (Step (WordQuotedState s b a) b)
step forall {b} {a} {b}. m (Initial (WordQuotedState s b a) b)
initial forall {a} {s}. WordQuotedState s b a -> m (Step s b)
extract
where
isInvalid :: b -> Bool
isInvalid = forall a b. a -> b -> a
const Bool
False
isEsc :: a -> Bool
isEsc = (forall a. Eq a => a -> a -> Bool
== a
escChar)
initial :: m (Initial (WordQuotedState s b a) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial (forall s b a. s -> WordQuotedState s b a
WordQuotedSkipPre s
s)
FL.Done b
_ ->
forall a. HasCallStack => String -> a
error String
"wordKeepQuotes: fold done without input"
{-# INLINE processQuoted #-}
processQuoted :: s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s a
a Int
n a
ql a
qr = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
0 (forall s b a. s -> Int -> a -> a -> WordQuotedState s b a
WordQuotedWord s
s1 Int
n a
ql a
qr)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
{-# INLINE processUnquoted #-}
processUnquoted :: s -> a -> m (Step (WordQuotedState s b a) b)
processUnquoted s
s a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
0 (forall s b a. s -> WordQuotedState s b a
WordUnquotedWord s
s1)
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
step :: WordQuotedState s b a -> a -> m (Step (WordQuotedState s b a) b)
step (WordQuotedSkipPre s
s) a
a
| a -> Bool
isEsc a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. s -> WordQuotedState s b a
WordUnquotedEsc s
s
| a -> Bool
isSep a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. s -> WordQuotedState s b a
WordQuotedSkipPre s
s
| Bool
otherwise =
case a -> Maybe a
toRight a
a of
Just a
qr ->
if Bool
keepQuotes
then forall {a} {b}.
s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s a
a Int
1 a
a a
qr
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. s -> Int -> a -> a -> WordQuotedState s b a
WordQuotedWord s
s Int
1 a
a a
qr
Maybe a
Nothing
| forall {b}. b -> Bool
isInvalid a
a ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"wordKeepQuotes: invalid unquoted char"
| Bool
otherwise -> forall {b} {a}. s -> a -> m (Step (WordQuotedState s b a) b)
processUnquoted s
s a
a
step (WordUnquotedWord s
s) a
a
| a -> Bool
isEsc a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. s -> WordQuotedState s b a
WordUnquotedEsc s
s
| a -> Bool
isSep a
a = do
b
b <- s -> m b
fextract s
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. b -> WordQuotedState s b a
WordQuotedSkipPost b
b
| Bool
otherwise = do
case a -> Maybe a
toRight a
a of
Just a
qr ->
if Bool
keepQuotes
then forall {a} {b}.
s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s a
a Int
1 a
a a
qr
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. s -> Int -> a -> a -> WordQuotedState s b a
WordQuotedWord s
s Int
1 a
a a
qr
Maybe a
Nothing ->
if forall {b}. b -> Bool
isInvalid a
a
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"wordKeepQuotes: invalid unquoted char"
else forall {b} {a}. s -> a -> m (Step (WordQuotedState s b a) b)
processUnquoted s
s a
a
step (WordQuotedWord s
s Int
n a
ql a
qr) a
a
| a -> Bool
isEsc a
a = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. s -> Int -> a -> a -> WordQuotedState s b a
WordQuotedEsc s
s Int
n a
ql a
qr
| Bool
otherwise = do
if a
a forall a. Eq a => a -> a -> Bool
== a
qr
then
if Int
n forall a. Eq a => a -> a -> Bool
== Int
1
then if Bool
keepQuotes
then forall {b} {a}. s -> a -> m (Step (WordQuotedState s b a) b)
processUnquoted s
s a
a
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. s -> WordQuotedState s b a
WordUnquotedWord s
s
else forall {a} {b}.
s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s a
a (Int
n forall a. Num a => a -> a -> a
- Int
1) a
ql a
qr
else if a
a forall a. Eq a => a -> a -> Bool
== a
ql
then forall {a} {b}.
s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s a
a (Int
n forall a. Num a => a -> a -> a
+ Int
1) a
ql a
qr
else forall {a} {b}.
s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s a
a Int
n a
ql a
qr
step (WordUnquotedEsc s
s) a
a = forall {b} {a}. s -> a -> m (Step (WordQuotedState s b a) b)
processUnquoted s
s a
a
step (WordQuotedEsc s
s Int
n a
ql a
qr) a
a =
case a -> a -> Maybe a
tr a
ql a
a of
Maybe a
Nothing -> do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
escChar
case Step s b
res of
FL.Partial s
s1 -> forall {a} {b}.
s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s1 a
a Int
n a
ql a
qr
FL.Done b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 b
b
Just a
x -> forall {a} {b}.
s -> a -> Int -> a -> a -> m (Step (WordQuotedState s b a) b)
processQuoted s
s a
x Int
n a
ql a
qr
step (WordQuotedSkipPost b
b) a
a =
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ if Bool -> Bool
not (a -> Bool
isSep a
a)
then forall s b. Int -> b -> Step s b
Done Int
1 b
b
else forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall s b a. b -> WordQuotedState s b a
WordQuotedSkipPost b
b
err :: String -> m (Step s b)
err = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s b. String -> Step s b
Error
extract :: WordQuotedState s b a -> m (Step s b)
extract (WordQuotedSkipPre s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (WordUnquotedWord s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (WordQuotedWord s
s Int
n a
_ a
_) =
if Int
n forall a. Eq a => a -> a -> Bool
== Int
0
then forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
else forall {s} {b}. String -> m (Step s b)
err String
"wordWithQuotes: missing frame end"
extract WordQuotedEsc {} =
forall {s} {b}. String -> m (Step s b)
err String
"wordWithQuotes: trailing escape"
extract (WordUnquotedEsc s
_) =
forall {s} {b}. String -> m (Step s b)
err String
"wordWithQuotes: trailing escape"
extract (WordQuotedSkipPost b
b) = forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
0 b
b)
{-# INLINE wordKeepQuotes #-}
wordKeepQuotes :: (Monad m, Eq a) =>
a
-> (a -> Maybe a)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordKeepQuotes :: forall (m :: * -> *) a b.
(Monad m, Eq a) =>
a -> (a -> Maybe a) -> (a -> Bool) -> Fold m a b -> Parser a m b
wordKeepQuotes =
forall (m :: * -> *) a b.
(Monad m, Eq a) =>
Bool
-> (a -> a -> Maybe a)
-> a
-> (a -> Maybe a)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordWithQuotes Bool
True (\a
q a
x -> if a
q forall a. Eq a => a -> a -> Bool
== a
x then forall a. a -> Maybe a
Just a
x else forall a. Maybe a
Nothing)
{-# INLINE wordProcessQuotes #-}
wordProcessQuotes :: (Monad m, Eq a) =>
a
-> (a -> Maybe a)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordProcessQuotes :: forall (m :: * -> *) a b.
(Monad m, Eq a) =>
a -> (a -> Maybe a) -> (a -> Bool) -> Fold m a b -> Parser a m b
wordProcessQuotes =
forall (m :: * -> *) a b.
(Monad m, Eq a) =>
Bool
-> (a -> a -> Maybe a)
-> a
-> (a -> Maybe a)
-> (a -> Bool)
-> Fold m a b
-> Parser a m b
wordWithQuotes Bool
False (\a
q a
x -> if a
q forall a. Eq a => a -> a -> Bool
== a
x then forall a. a -> Maybe a
Just a
x else forall a. Maybe a
Nothing)
{-# ANN type GroupByState Fuse #-}
data GroupByState a s
= GroupByInit !s
| GroupByGrouping !a !s
{-# INLINE groupBy #-}
groupBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser a m b
groupBy :: forall (m :: * -> *) a b.
Monad m =>
(a -> a -> Bool) -> Fold m a b -> Parser a m b
groupBy a -> a -> Bool
eq (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser GroupByState a s -> a -> m (Step (GroupByState a s) b)
step forall {a}. m (Initial (GroupByState a s) b)
initial forall {a} {s}. GroupByState a s -> m (Step s b)
extract
where
{-# INLINE grouper #-}
grouper :: s -> a -> a -> m (Step (GroupByState a s) b)
grouper s
s a
a0 a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 (forall a s. a -> s -> GroupByState a s
GroupByGrouping a
a0 s
s1)
initial :: m (Initial (GroupByState a s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall a s. s -> GroupByState a s
GroupByInit s
s
FL.Done b
b -> forall s b. b -> Initial s b
IDone b
b
step :: GroupByState a s -> a -> m (Step (GroupByState a s) b)
step (GroupByInit s
s) a
a = forall {a}. s -> a -> a -> m (Step (GroupByState a s) b)
grouper s
s a
a a
a
step (GroupByGrouping a
a0 s
s) a
a =
if a -> a -> Bool
eq a
a0 a
a
then forall {a}. s -> a -> a -> m (Step (GroupByState a s) b)
grouper s
s a
a0 a
a
else forall s b. Int -> b -> Step s b
Done Int
1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
extract :: GroupByState a s -> m (Step s b)
extract (GroupByInit s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (GroupByGrouping a
_ s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
{-# INLINE groupByRolling #-}
groupByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser a m b
groupByRolling :: forall (m :: * -> *) a b.
Monad m =>
(a -> a -> Bool) -> Fold m a b -> Parser a m b
groupByRolling a -> a -> Bool
eq (Fold s -> a -> m (Step s b)
fstep m (Step s b)
finitial s -> m b
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser GroupByState a s -> a -> m (Step (GroupByState a s) b)
step forall {a}. m (Initial (GroupByState a s) b)
initial forall {a} {s}. GroupByState a s -> m (Step s b)
extract
where
{-# INLINE grouper #-}
grouper :: s -> a -> m (Step (GroupByState a s) b)
grouper s
s a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep s
s a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 b
b
FL.Partial s
s1 -> forall s b. Int -> s -> Step s b
Partial Int
0 (forall a s. a -> s -> GroupByState a s
GroupByGrouping a
a s
s1)
initial :: m (Initial (GroupByState a s) b)
initial = do
Step s b
res <- m (Step s b)
finitial
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Partial s
s -> forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall a s. s -> GroupByState a s
GroupByInit s
s
FL.Done b
b -> forall s b. b -> Initial s b
IDone b
b
step :: GroupByState a s -> a -> m (Step (GroupByState a s) b)
step (GroupByInit s
s) a
a = s -> a -> m (Step (GroupByState a s) b)
grouper s
s a
a
step (GroupByGrouping a
a0 s
s) a
a =
if a -> a -> Bool
eq a
a0 a
a
then s -> a -> m (Step (GroupByState a s) b)
grouper s
s a
a
else forall s b. Int -> b -> Step s b
Done Int
1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract s
s
extract :: GroupByState a s -> m (Step s b)
extract (GroupByInit s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
extract (GroupByGrouping a
_ s
s) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m b
fextract s
s
{-# ANN type GroupByStatePair Fuse #-}
data GroupByStatePair a s1 s2
= GroupByInitPair !s1 !s2
| GroupByGroupingPair !a !s1 !s2
| GroupByGroupingPairL !a !s1 !s2
| GroupByGroupingPairR !a !s1 !s2
{-# INLINE groupByRollingEither #-}
groupByRollingEither :: Monad m =>
(a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser a m (Either b c)
groupByRollingEither :: forall (m :: * -> *) a b c.
Monad m =>
(a -> a -> Bool)
-> Fold m a b -> Fold m a c -> Parser a m (Either b c)
groupByRollingEither
a -> a -> Bool
eq
(Fold s -> a -> m (Step s b)
fstep1 m (Step s b)
finitial1 s -> m b
fextract1)
(Fold s -> a -> m (Step s c)
fstep2 m (Step s c)
finitial2 s -> m c
fextract2) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser GroupByStatePair a s s
-> a -> m (Step (GroupByStatePair a s s) (Either b c))
step forall {a}. m (Initial (GroupByStatePair a s s) (Either b c))
initial forall {s}. GroupByStatePair a s s -> m (Step s (Either b c))
extract
where
{-# INLINE grouper #-}
grouper :: s1 -> s2 -> a -> m (Step (GroupByStatePair a s1 s2) b)
grouper s1
s1 s2
s2 a
a = do
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 (forall a s1 s2. a -> s1 -> s2 -> GroupByStatePair a s1 s2
GroupByGroupingPair a
a s1
s1 s2
s2)
{-# INLINE grouperL2 #-}
grouperL2 :: s -> s2 -> a -> m (Step (GroupByStatePair a s s2) (Either b b))
grouperL2 s
s1 s2
s2 a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep1 s
s1 a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res of
FL.Done b
b -> forall s b. Int -> b -> Step s b
Done Int
0 (forall a b. a -> Either a b
Left b
b)
FL.Partial s
s11 -> forall s b. Int -> s -> Step s b
Partial Int
0 (forall a s1 s2. a -> s1 -> s2 -> GroupByStatePair a s1 s2
GroupByGroupingPairL a
a s
s11 s2
s2)
{-# INLINE grouperL #-}
grouperL :: s
-> s2 -> a -> a -> m (Step (GroupByStatePair a s s2) (Either b b))
grouperL s
s1 s2
s2 a
a0 a
a = do
Step s b
res <- s -> a -> m (Step s b)
fstep1 s
s1 a
a0
case Step s b
res of
FL.Done b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 (forall a b. a -> Either a b
Left b
b)
FL.Partial s
s11 -> forall {s2} {b}.
s -> s2 -> a -> m (Step (GroupByStatePair a s s2) (Either b b))
grouperL2 s
s11 s2
s2 a
a
{-# INLINE grouperR2 #-}
grouperR2 :: s1 -> s -> a -> m (Step (GroupByStatePair a s1 s) (Either a c))
grouperR2 s1
s1 s
s2 a
a = do
Step s c
res <- s -> a -> m (Step s c)
fstep2 s
s2 a
a
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s c
res of
FL.Done c
b -> forall s b. Int -> b -> Step s b
Done Int
0 (forall a b. b -> Either a b
Right c
b)
FL.Partial s
s21 -> forall s b. Int -> s -> Step s b
Partial Int
0 (forall a s1 s2. a -> s1 -> s2 -> GroupByStatePair a s1 s2
GroupByGroupingPairR a
a s1
s1 s
s21)
{-# INLINE grouperR #-}
grouperR :: s1
-> s -> a -> a -> m (Step (GroupByStatePair a s1 s) (Either a c))
grouperR s1
s1 s
s2 a
a0 a
a = do
Step s c
res <- s -> a -> m (Step s c)
fstep2 s
s2 a
a0
case Step s c
res of
FL.Done c
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 (forall a b. b -> Either a b
Right c
b)
FL.Partial s
s21 -> forall {s1} {a}.
s1 -> s -> a -> m (Step (GroupByStatePair a s1 s) (Either a c))
grouperR2 s1
s1 s
s21 a
a
initial :: m (Initial (GroupByStatePair a s s) (Either b c))
initial = do
Step s b
res1 <- m (Step s b)
finitial1
Step s c
res2 <- m (Step s c)
finitial2
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
res1 of
FL.Partial s
s1 ->
case Step s c
res2 of
FL.Partial s
s2 -> forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall a s1 s2. s1 -> s2 -> GroupByStatePair a s1 s2
GroupByInitPair s
s1 s
s2
FL.Done c
b -> forall s b. b -> Initial s b
IDone (forall a b. b -> Either a b
Right c
b)
FL.Done b
b -> forall s b. b -> Initial s b
IDone (forall a b. a -> Either a b
Left b
b)
step :: GroupByStatePair a s s
-> a -> m (Step (GroupByStatePair a s s) (Either b c))
step (GroupByInitPair s
s1 s
s2) a
a = forall {m :: * -> *} {s1} {s2} {a} {b}.
Monad m =>
s1 -> s2 -> a -> m (Step (GroupByStatePair a s1 s2) b)
grouper s
s1 s
s2 a
a
step (GroupByGroupingPair a
a0 s
s1 s
s2) a
a =
if Bool -> Bool
not (a -> a -> Bool
eq a
a0 a
a)
then forall {s2} {b}.
s
-> s2 -> a -> a -> m (Step (GroupByStatePair a s s2) (Either b b))
grouperL s
s1 s
s2 a
a0 a
a
else forall {s1} {a}.
s1
-> s -> a -> a -> m (Step (GroupByStatePair a s1 s) (Either a c))
grouperR s
s1 s
s2 a
a0 a
a
step (GroupByGroupingPairL a
a0 s
s1 s
s2) a
a =
if Bool -> Bool
not (a -> a -> Bool
eq a
a0 a
a)
then forall {s2} {b}.
s -> s2 -> a -> m (Step (GroupByStatePair a s s2) (Either b b))
grouperL2 s
s1 s
s2 a
a
else forall s b. Int -> b -> Step s b
Done Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract1 s
s1
step (GroupByGroupingPairR a
a0 s
s1 s
s2) a
a =
if a -> a -> Bool
eq a
a0 a
a
then forall {s1} {a}.
s1 -> s -> a -> m (Step (GroupByStatePair a s1 s) (Either a c))
grouperR2 s
s1 s
s2 a
a
else forall s b. Int -> b -> Step s b
Done Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m c
fextract2 s
s2
extract :: GroupByStatePair a s s -> m (Step s (Either b c))
extract (GroupByInitPair s
s1 s
_) = forall s b. Int -> b -> Step s b
Done Int
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract1 s
s1
extract (GroupByGroupingPairL a
_ s
s1 s
_) = forall s b. Int -> b -> Step s b
Done Int
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract1 s
s1
extract (GroupByGroupingPairR a
_ s
_ s
s2) = forall s b. Int -> b -> Step s b
Done Int
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m c
fextract2 s
s2
extract (GroupByGroupingPair a
a s
s1 s
_) = do
Step s b
res <- s -> a -> m (Step s b)
fstep1 s
s1 a
a
case Step s b
res of
FL.Done b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 (forall a b. a -> Either a b
Left b
b)
FL.Partial s
s11 -> forall s b. Int -> b -> Step s b
Done Int
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m b
fextract1 s
s11
{-# INLINE listEqBy #-}
listEqBy :: Monad m => (a -> a -> Bool) -> [a] -> Parser a m [a]
listEqBy :: forall (m :: * -> *) a.
Monad m =>
(a -> a -> Bool) -> [a] -> Parser a m [a]
listEqBy a -> a -> Bool
cmp [a]
xs = forall (m :: * -> *) a.
Monad m =>
(a -> a -> Bool) -> Stream m a -> Parser a m ()
streamEqByInternal a -> a -> Bool
cmp (forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
D.fromList [a]
xs) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *) b a. Monad m => b -> Parser a m b
fromPure [a]
xs
{-# INLINE streamEqByInternal #-}
streamEqByInternal :: Monad m => (a -> a -> Bool) -> D.Stream m a -> Parser a m ()
streamEqByInternal :: forall (m :: * -> *) a.
Monad m =>
(a -> a -> Bool) -> Stream m a -> Parser a m ()
streamEqByInternal a -> a -> Bool
cmp (D.Stream State StreamK m a -> s -> m (Step s a)
sstep s
state) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser (Maybe' a, s) -> a -> m (Step (Maybe' a, s) ())
step m (Initial (Maybe' a, s) ())
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Maybe' a, s) ())
initial = do
Step s a
r <- State StreamK m a -> s -> m (Step s a)
sstep forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
state
case Step s a
r of
D.Yield a
x s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial (forall a. a -> Maybe' a
Just' a
x, s
s)
Step s a
D.Stop -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone ()
D.Skip s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial (forall a. Maybe' a
Nothing', s
s)
step :: (Maybe' a, s) -> a -> m (Step (Maybe' a, s) ())
step (Just' a
x, s
st) a
a =
if a
x a -> a -> Bool
`cmp` a
a
then do
Step s a
r <- State StreamK m a -> s -> m (Step s a)
sstep forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
st
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s a
r of
D.Yield a
x1 s
s -> forall s b. Int -> s -> Step s b
Continue Int
0 (forall a. a -> Maybe' a
Just' a
x1, s
s)
Step s a
D.Stop -> forall s b. Int -> b -> Step s b
Done Int
0 ()
D.Skip s
s -> forall s b. Int -> s -> Step s b
Continue Int
1 (forall a. Maybe' a
Nothing', s
s)
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"streamEqBy: mismtach occurred"
step (Maybe' a
Nothing', s
st) a
a = do
Step s a
r <- State StreamK m a -> s -> m (Step s a)
sstep forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
st
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s a
r of
D.Yield a
x s
s -> do
if a
x a -> a -> Bool
`cmp` a
a
then forall s b. Int -> s -> Step s b
Continue Int
0 (forall a. Maybe' a
Nothing', s
s)
else forall s b. String -> Step s b
Error String
"streamEqBy: mismatch occurred"
Step s a
D.Stop -> forall s b. Int -> b -> Step s b
Done Int
1 ()
D.Skip s
s -> forall s b. Int -> s -> Step s b
Continue Int
1 (forall a. Maybe' a
Nothing', s
s)
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"streamEqBy: end of input"
{-# INLINE streamEqBy #-}
streamEqBy :: Monad m => (a -> a -> Bool) -> D.Stream m a -> Parser a m ()
streamEqBy :: forall (m :: * -> *) a.
Monad m =>
(a -> a -> Bool) -> Stream m a -> Parser a m ()
streamEqBy a -> a -> Bool
cmp Stream m a
stream = forall (m :: * -> *) a.
Monad m =>
(a -> a -> Bool) -> Stream m a -> Parser a m ()
streamEqByInternal a -> a -> Bool
cmp Stream m a
stream forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall (m :: * -> *) b a. Monad m => b -> Parser a m b
fromPure ()
{-# INLINE listEq #-}
listEq :: (Monad m, Eq a) => [a] -> Parser a m [a]
listEq :: forall (m :: * -> *) a. (Monad m, Eq a) => [a] -> Parser a m [a]
listEq = forall (m :: * -> *) a.
Monad m =>
(a -> a -> Bool) -> [a] -> Parser a m [a]
listEqBy forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE subsequenceBy #-}
subsequenceBy ::
(a -> a -> Bool) -> Stream m a -> Parser a m ()
subsequenceBy :: forall a (m :: * -> *).
(a -> a -> Bool) -> Stream m a -> Parser a m ()
subsequenceBy = forall a. HasCallStack => a
undefined
{-# INLINE postscan #-}
postscan ::
Fold m a b -> Parser b m c -> Parser a m c
postscan :: forall (m :: * -> *) a b c.
Fold m a b -> Parser b m c -> Parser a m c
postscan = forall a. HasCallStack => a
undefined
{-# INLINE zipWithM #-}
zipWithM :: Monad m =>
(a -> b -> m c) -> D.Stream m a -> Fold m c x -> Parser b m x
zipWithM :: forall (m :: * -> *) a b c x.
Monad m =>
(a -> b -> m c) -> Stream m a -> Fold m c x -> Parser b m x
zipWithM a -> b -> m c
zf (D.Stream State StreamK m a -> s -> m (Step s a)
sstep s
state) (Fold s -> c -> m (Step s x)
fstep m (Step s x)
finitial s -> m x
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser (Maybe' a, s, s) -> b -> m (Step (Maybe' a, s, s) x)
step m (Initial (Maybe' a, s, s) x)
initial forall {m :: * -> *} {p} {s} {b}. Monad m => p -> m (Step s b)
extract
where
initial :: m (Initial (Maybe' a, s, s) x)
initial = do
Step s x
fres <- m (Step s x)
finitial
case Step s x
fres of
FL.Partial s
fs -> do
Step s a
r <- State StreamK m a -> s -> m (Step s a)
sstep forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
state
case Step s a
r of
D.Yield a
x s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial (forall a. a -> Maybe' a
Just' a
x, s
s, s
fs)
Step s a
D.Stop -> do
x
x <- s -> m x
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone x
x
D.Skip s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial (forall a. Maybe' a
Nothing', s
s, s
fs)
FL.Done x
x -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone x
x
step :: (Maybe' a, s, s) -> b -> m (Step (Maybe' a, s, s) x)
step (Just' a
a, s
st, s
fs) b
b = do
c
c <- a -> b -> m c
zf a
a b
b
Step s x
fres <- s -> c -> m (Step s x)
fstep s
fs c
c
case Step s x
fres of
FL.Partial s
fs1 -> do
Step s a
r <- State StreamK m a -> s -> m (Step s a)
sstep forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
st
case Step s a
r of
D.Yield a
x1 s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 (forall a. a -> Maybe' a
Just' a
x1, s
s, s
fs1)
Step s a
D.Stop -> do
x
x <- s -> m x
fextract s
fs1
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 x
x
D.Skip s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
1 (forall a. Maybe' a
Nothing', s
s, s
fs1)
FL.Done x
x -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 x
x
step (Maybe' a
Nothing', s
st, s
fs) b
b = do
Step s a
r <- State StreamK m a -> s -> m (Step s a)
sstep forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
st
case Step s a
r of
D.Yield a
a s
s -> do
c
c <- a -> b -> m c
zf a
a b
b
Step s x
fres <- s -> c -> m (Step s x)
fstep s
fs c
c
case Step s x
fres of
FL.Partial s
fs1 ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 (forall a. Maybe' a
Nothing', s
s, s
fs1)
FL.Done x
x -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
0 x
x
Step s a
D.Stop -> do
x
x <- s -> m x
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
1 x
x
D.Skip s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
1 (forall a. Maybe' a
Nothing', s
s, s
fs)
extract :: p -> m (Step s b)
extract p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"zipWithM: end of input"
{-# INLINE zip #-}
zip :: Monad m => D.Stream m a -> Fold m (a, b) x -> Parser b m x
zip :: forall (m :: * -> *) a b x.
Monad m =>
Stream m a -> Fold m (a, b) x -> Parser b m x
zip = forall (m :: * -> *) a b c x.
Monad m =>
(a -> b -> m c) -> Stream m a -> Fold m c x -> Parser b m x
zipWithM (forall a b c. ((a, b) -> c) -> a -> b -> c
curry forall (m :: * -> *) a. Monad m => a -> m a
return)
{-# INLINE indexed #-}
indexed :: forall m a b. Monad m => Fold m (Int, a) b -> Parser a m b
indexed :: forall (m :: * -> *) a b.
Monad m =>
Fold m (Int, a) b -> Parser a m b
indexed = forall (m :: * -> *) a b x.
Monad m =>
Stream m a -> Fold m (a, b) x -> Parser b m x
zip (forall (m :: * -> *) a.
(Monad m, Integral a, Bounded a) =>
a -> Stream m a
D.enumerateFromIntegral Int
0 :: D.Stream m Int)
{-# INLINE makeIndexFilter #-}
makeIndexFilter ::
(Fold m (s, a) b -> Parser a m b)
-> (((s, a) -> Bool) -> Fold m (s, a) b -> Fold m (s, a) b)
-> (((s, a) -> Bool) -> Fold m a b -> Parser a m b)
makeIndexFilter :: forall (m :: * -> *) s a b.
(Fold m (s, a) b -> Parser a m b)
-> (((s, a) -> Bool) -> Fold m (s, a) b -> Fold m (s, a) b)
-> ((s, a) -> Bool)
-> Fold m a b
-> Parser a m b
makeIndexFilter Fold m (s, a) b -> Parser a m b
f ((s, a) -> Bool) -> Fold m (s, a) b -> Fold m (s, a) b
comb (s, a) -> Bool
g = Fold m (s, a) b -> Parser a m b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((s, a) -> Bool) -> Fold m (s, a) b -> Fold m (s, a) b
comb (s, a) -> Bool
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b (m :: * -> *) r. (a -> b) -> Fold m b r -> Fold m a r
FL.lmap forall a b. (a, b) -> b
snd
{-# INLINE sampleFromthen #-}
sampleFromthen :: Monad m => Int -> Int -> Fold m a b -> Parser a m b
sampleFromthen :: forall (m :: * -> *) a b.
Monad m =>
Int -> Int -> Fold m a b -> Parser a m b
sampleFromthen Int
offset Int
size =
forall (m :: * -> *) s a b.
(Fold m (s, a) b -> Parser a m b)
-> (((s, a) -> Bool) -> Fold m (s, a) b -> Fold m (s, a) b)
-> ((s, a) -> Bool)
-> Fold m a b
-> Parser a m b
makeIndexFilter forall (m :: * -> *) a b.
Monad m =>
Fold m (Int, a) b -> Parser a m b
indexed forall (m :: * -> *) a r.
Monad m =>
(a -> Bool) -> Fold m a r -> Fold m a r
FL.filter (\(Int
i, a
_) -> (Int
i forall a. Num a => a -> a -> a
+ Int
offset) forall a. Integral a => a -> a -> a
`mod` Int
size forall a. Eq a => a -> a -> Bool
== Int
0)
{-# INLINE span #-}
span :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a c -> Parser a m (b, c)
span :: forall (m :: * -> *) a b c.
Monad m =>
(a -> Bool) -> Fold m a b -> Fold m a c -> Parser a m (b, c)
span a -> Bool
p Fold m a b
f1 Fold m a c
f2 = forall (m :: * -> *) a b c x.
Monad m =>
(a -> b -> c) -> Parser x m a -> Parser x m b -> Parser x m c
noErrorUnsafeSplitWith (,) (forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Parser a m b
takeWhile a -> Bool
p Fold m a b
f1) (forall (m :: * -> *) a b. Monad m => Fold m a b -> Parser a m b
fromFold Fold m a c
f2)
{-# INLINE spanBy #-}
spanBy ::
Monad m
=> (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser a m (b, c)
spanBy :: forall (m :: * -> *) a b c.
Monad m =>
(a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser a m (b, c)
spanBy a -> a -> Bool
eq Fold m a b
f1 Fold m a c
f2 = forall (m :: * -> *) a b c x.
Monad m =>
(a -> b -> c) -> Parser x m a -> Parser x m b -> Parser x m c
noErrorUnsafeSplitWith (,) (forall (m :: * -> *) a b.
Monad m =>
(a -> a -> Bool) -> Fold m a b -> Parser a m b
groupBy a -> a -> Bool
eq Fold m a b
f1) (forall (m :: * -> *) a b. Monad m => Fold m a b -> Parser a m b
fromFold Fold m a c
f2)
{-# INLINE spanByRolling #-}
spanByRolling ::
Monad m
=> (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser a m (b, c)
spanByRolling :: forall (m :: * -> *) a b c.
Monad m =>
(a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser a m (b, c)
spanByRolling a -> a -> Bool
eq Fold m a b
f1 Fold m a c
f2 =
forall (m :: * -> *) a b c x.
Monad m =>
(a -> b -> c) -> Parser x m a -> Parser x m b -> Parser x m c
noErrorUnsafeSplitWith (,) (forall (m :: * -> *) a b.
Monad m =>
(a -> a -> Bool) -> Fold m a b -> Parser a m b
groupByRolling a -> a -> Bool
eq Fold m a b
f1) (forall (m :: * -> *) a b. Monad m => Fold m a b -> Parser a m b
fromFold Fold m a c
f2)
{-# INLINE takeP #-}
takeP :: Monad m => Int -> Parser a m b -> Parser a m b
takeP :: forall (m :: * -> *) a b.
Monad m =>
Int -> Parser a m b -> Parser a m b
takeP Int
lim (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinitial s -> m (Step s b)
pextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser Tuple' Int s -> a -> m (Step (Tuple' Int s) b)
step m (Initial (Tuple' Int s) b)
initial Tuple' Int s -> m (Step (Tuple' Int s) b)
extract
where
initial :: m (Initial (Tuple' Int s) b)
initial = do
Initial s b
res <- m (Initial s b)
pinitial
case Initial s b
res of
IPartial s
s ->
if Int
lim forall a. Ord a => a -> a -> Bool
> Int
0
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple' a b
Tuple' Int
0 s
s
else forall {s}. s -> m (Initial s b)
iextract s
s
IDone b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone b
b
IError String
e -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Initial s b
IError String
e
step :: Tuple' Int s -> a -> m (Step (Tuple' Int s) b)
step (Tuple' Int
cnt s
r) a
a = do
assertM(Int
cnt forall a. Ord a => a -> a -> Bool
< Int
lim)
Step s b
res <- s -> a -> m (Step s b)
pstep s
r a
a
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
case Step s b
res of
Partial Int
0 s
s -> do
assertM(Int
cnt1 forall a. Ord a => a -> a -> Bool
>= Int
0)
if Int
cnt1 forall a. Ord a => a -> a -> Bool
< Int
lim
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
0 forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple' a b
Tuple' Int
cnt1 s
s
else do
Step s b
r1 <- s -> m (Step s b)
pextract s
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Step s b
r1 of
Done Int
n b
b -> forall s b. Int -> b -> Step s b
Done Int
n b
b
Continue Int
n s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
n (forall a b. a -> b -> Tuple' a b
Tuple' (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
s1)
Error String
err -> forall s b. String -> Step s b
Error String
err
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"takeP: Partial in extract"
Continue Int
0 s
s -> do
assertM(Int
cnt1 forall a. Ord a => a -> a -> Bool
>= Int
0)
if Int
cnt1 forall a. Ord a => a -> a -> Bool
< Int
lim
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
0 forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple' a b
Tuple' Int
cnt1 s
s
else do
Step s b
r1 <- s -> m (Step s b)
pextract s
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Step s b
r1 of
Done Int
n b
b -> forall s b. Int -> b -> Step s b
Done Int
n b
b
Continue Int
n s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
n (forall a b. a -> b -> Tuple' a b
Tuple' (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
s1)
Error String
err -> forall s b. String -> Step s b
Error String
err
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"takeP: Partial in extract"
Partial Int
n s
s -> do
let taken :: Int
taken = Int
cnt1 forall a. Num a => a -> a -> a
- Int
n
assertM(Int
taken forall a. Ord a => a -> a -> Bool
>= Int
0)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple' a b
Tuple' Int
taken s
s
Continue Int
n s
s -> do
let taken :: Int
taken = Int
cnt1 forall a. Num a => a -> a -> a
- Int
n
assertM(Int
taken forall a. Ord a => a -> a -> Bool
>= Int
0)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> Tuple' a b
Tuple' Int
taken s
s
Done Int
n b
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n b
b
Error String
str -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
str
extract :: Tuple' Int s -> m (Step (Tuple' Int s) b)
extract (Tuple' Int
cnt s
r) = do
Step s b
r1 <- s -> m (Step s b)
pextract s
r
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Step s b
r1 of
Done Int
n b
b -> forall s b. Int -> b -> Step s b
Done Int
n b
b
Continue Int
n s
s1 -> forall s b. Int -> s -> Step s b
Continue Int
n (forall a b. a -> b -> Tuple' a b
Tuple' (Int
cnt forall a. Num a => a -> a -> a
- Int
n) s
s1)
Error String
err -> forall s b. String -> Step s b
Error String
err
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"takeP: Partial in extract"
iextract :: s -> m (Initial s b)
iextract s
s = do
Step s b
r <- s -> m (Step s b)
pextract s
s
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Step s b
r of
Done Int
_ b
b -> forall s b. b -> Initial s b
IDone b
b
Error String
err -> forall s b. String -> Initial s b
IError String
err
Step s b
_ -> forall a. HasCallStack => String -> a
error String
"Bug: takeP invalid state in initial"
{-# INLINE lookAhead #-}
lookAhead :: Monad m => Parser a m b -> Parser a m b
lookAhead :: forall (m :: * -> *) a b. Monad m => Parser a m b -> Parser a m b
lookAhead (Parser s -> a -> m (Step s b)
step1 m (Initial s b)
initial1 s -> m (Step s b)
_) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser Tuple'Fused Int s -> a -> m (Step (Tuple'Fused Int s) b)
step m (Initial (Tuple'Fused Int s) b)
initial forall {m :: * -> *} {a} {b} {s} {b}.
(Monad m, Show a) =>
Tuple'Fused a b -> m (Step s b)
extract
where
initial :: m (Initial (Tuple'Fused Int s) b)
initial = do
Initial s b
res <- m (Initial s b)
initial1
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Initial s b
res of
IPartial s
s -> forall s b. s -> Initial s b
IPartial (forall a b. a -> b -> Tuple'Fused a b
Tuple'Fused Int
0 s
s)
IDone b
b -> forall s b. b -> Initial s b
IDone b
b
IError String
e -> forall s b. String -> Initial s b
IError String
e
step :: Tuple'Fused Int s -> a -> m (Step (Tuple'Fused Int s) b)
step (Tuple'Fused Int
cnt s
st) a
a = do
Step s b
r <- s -> a -> m (Step s b)
step1 s
st a
a
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ case Step s b
r of
Partial Int
n s
s -> forall s b. Int -> s -> Step s b
Continue Int
n (forall a b. a -> b -> Tuple'Fused a b
Tuple'Fused (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
s)
Continue Int
n s
s -> forall s b. Int -> s -> Step s b
Continue Int
n (forall a b. a -> b -> Tuple'Fused a b
Tuple'Fused (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
s)
Done Int
_ b
b -> forall s b. Int -> b -> Step s b
Done Int
cnt1 b
b
Error String
err -> forall s b. String -> Step s b
Error String
err
extract :: Tuple'Fused a b -> m (Step s b)
extract (Tuple'Fused a
n b
_) =
forall (m :: * -> *) a. Monad m => a -> m a
return
forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error
forall a b. (a -> b) -> a -> b
$ String
"lookAhead: end of input after consuming "
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
n forall a. [a] -> [a] -> [a]
++ String
" elements"
{-# ANN type DeintercalateAllState Fuse #-}
data DeintercalateAllState fs sp ss =
DeintercalateAllInitL !fs
| DeintercalateAllL !fs !sp
| DeintercalateAllInitR !fs
| DeintercalateAllR !fs !ss
{-# INLINE deintercalateAll #-}
deintercalateAll :: Monad m =>
Parser a m x
-> Parser a m y
-> Fold m (Either x y) z
-> Parser a m z
deintercalateAll :: forall (m :: * -> *) a x y z.
Monad m =>
Parser a m x
-> Parser a m y -> Fold m (Either x y) z -> Parser a m z
deintercalateAll
(Parser s -> a -> m (Step s x)
stepL m (Initial s x)
initialL s -> m (Step s x)
extractL)
(Parser s -> a -> m (Step s y)
stepR m (Initial s y)
initialR s -> m (Step s y)
_)
(Fold s -> Either x y -> m (Step s z)
fstep m (Step s z)
finitial s -> m z
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser DeintercalateAllState s s s
-> a -> m (Step (DeintercalateAllState s s s) z)
step forall {sp} {ss}. m (Initial (DeintercalateAllState s sp ss) z)
initial forall {ss} {ss}.
DeintercalateAllState s s ss
-> m (Step (DeintercalateAllState s s ss) z)
extract
where
errMsg :: String -> String -> a
errMsg String
p String
status =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"deintercalate: " forall a. [a] -> [a] -> [a]
++ String
p forall a. [a] -> [a] -> [a]
++ String
" parser cannot "
forall a. [a] -> [a] -> [a]
++ String
status forall a. [a] -> [a] -> [a]
++ String
" without input"
initial :: m (Initial (DeintercalateAllState s sp ss) z)
initial = do
Step s z
res <- m (Step s z)
finitial
case Step s z
res of
FL.Partial s
fs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall fs sp ss. fs -> DeintercalateAllState fs sp ss
DeintercalateAllInitL s
fs
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone z
c
{-# INLINE processL #-}
processL :: m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL m (Step t b)
foldAction Int
n t -> s
nextState = do
Step t b
fres <- m (Step t b)
foldAction
case Step t b
fres of
FL.Partial t
fs1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (t -> s
nextState t
fs1)
FL.Done b
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n b
c
{-# INLINE runStepL #-}
runStepL :: s -> s -> a -> m (Step (DeintercalateAllState s s ss) z)
runStepL s
fs s
sL a
a = do
Step s x
r <- s -> a -> m (Step s x)
stepL s
sL a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall fs sp ss. fs -> sp -> DeintercalateAllState fs sp ss
DeintercalateAllL s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. fs -> sp -> DeintercalateAllState fs sp ss
DeintercalateAllL s
fs s
s)
Done Int
n x
b ->
forall {m :: * -> *} {t} {b} {s}.
Monad m =>
m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL (s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. a -> Either a b
Left x
b)) Int
n forall fs sp ss. fs -> DeintercalateAllState fs sp ss
DeintercalateAllInitR
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
{-# INLINE processR #-}
processR :: m (Step fs b) -> Int -> m (Step (DeintercalateAllState fs s ss) b)
processR m (Step fs b)
foldAction Int
n = do
Step fs b
fres <- m (Step fs b)
foldAction
case Step fs b
fres of
FL.Partial fs
fs1 -> do
Initial s x
res <- m (Initial s x)
initialL
case Initial s x
res of
IPartial s
ps -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall fs sp ss. fs -> sp -> DeintercalateAllState fs sp ss
DeintercalateAllL fs
fs1 s
ps)
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
FL.Done b
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n b
c
{-# INLINE runStepR #-}
runStepR :: s -> s -> a -> m (Step (DeintercalateAllState s s s) z)
runStepR s
fs s
sR a
a = do
Step s y
r <- s -> a -> m (Step s y)
stepR s
sR a
a
case Step s y
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall fs sp ss. fs -> ss -> DeintercalateAllState fs sp ss
DeintercalateAllR s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. fs -> ss -> DeintercalateAllState fs sp ss
DeintercalateAllR s
fs s
s)
Done Int
n y
b -> forall {fs} {b} {ss}.
m (Step fs b) -> Int -> m (Step (DeintercalateAllState fs s ss) b)
processR (s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. b -> Either a b
Right y
b)) Int
n
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
step :: DeintercalateAllState s s s
-> a -> m (Step (DeintercalateAllState s s s) z)
step (DeintercalateAllInitL s
fs) a
a = do
Initial s x
res <- m (Initial s x)
initialL
case Initial s x
res of
IPartial s
s -> forall {ss}.
s -> s -> a -> m (Step (DeintercalateAllState s s ss) z)
runStepL s
fs s
s a
a
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
step (DeintercalateAllL s
fs s
sL) a
a = forall {ss}.
s -> s -> a -> m (Step (DeintercalateAllState s s ss) z)
runStepL s
fs s
sL a
a
step (DeintercalateAllInitR s
fs) a
a = do
Initial s y
res <- m (Initial s y)
initialR
case Initial s y
res of
IPartial s
s -> s -> s -> a -> m (Step (DeintercalateAllState s s s) z)
runStepR s
fs s
s a
a
IDone y
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"fail"
step (DeintercalateAllR s
fs s
sR) a
a = s -> s -> a -> m (Step (DeintercalateAllState s s s) z)
runStepR s
fs s
sR a
a
{-# INLINE extractResult #-}
extractResult :: Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs Either x y
r = do
Step s z
res <- s -> Either x y -> m (Step s z)
fstep s
fs Either x y
r
case Step s z
res of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
n) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs1
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
n z
c)
extract :: DeintercalateAllState s s ss
-> m (Step (DeintercalateAllState s s ss) z)
extract (DeintercalateAllInitL s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs
extract (DeintercalateAllL s
fs s
sL) = do
Step s x
r <- s -> m (Step s x)
extractL s
sL
case Step s x
r of
Done Int
n x
b -> forall {s}. Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs (forall a b. a -> Either a b
Left x
b)
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. fs -> sp -> DeintercalateAllState fs sp ss
DeintercalateAllL s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
extract (DeintercalateAllInitR s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs
extract (DeintercalateAllR s
_ ss
_) =
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
"deintercalateAll: input ended at 'Right' value"
{-# ANN type DeintercalateState Fuse #-}
data DeintercalateState b fs sp ss =
DeintercalateInitL !fs
| DeintercalateL !Int !fs !sp
| DeintercalateInitR !fs
| DeintercalateR !Int !fs !ss
| DeintercalateRL !Int !b !fs !sp
{-# INLINE deintercalate #-}
deintercalate :: Monad m =>
Parser a m x
-> Parser a m y
-> Fold m (Either x y) z
-> Parser a m z
deintercalate :: forall (m :: * -> *) a x y z.
Monad m =>
Parser a m x
-> Parser a m y -> Fold m (Either x y) z -> Parser a m z
deintercalate
(Parser s -> a -> m (Step s x)
stepL m (Initial s x)
initialL s -> m (Step s x)
extractL)
(Parser s -> a -> m (Step s y)
stepR m (Initial s y)
initialR s -> m (Step s y)
_)
(Fold s -> Either x y -> m (Step s z)
fstep m (Step s z)
finitial s -> m z
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser DeintercalateState y s s s
-> a -> m (Step (DeintercalateState y s s s) z)
step forall {b} {sp} {ss}. m (Initial (DeintercalateState b s sp ss) z)
initial forall {ss} {ss}.
DeintercalateState y s s ss
-> m (Step (DeintercalateState y s s ss) z)
extract
where
errMsg :: String -> String -> a
errMsg String
p String
status =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"deintercalate: " forall a. [a] -> [a] -> [a]
++ String
p forall a. [a] -> [a] -> [a]
++ String
" parser cannot "
forall a. [a] -> [a] -> [a]
++ String
status forall a. [a] -> [a] -> [a]
++ String
" without input"
initial :: m (Initial (DeintercalateState b s sp ss) z)
initial = do
Step s z
res <- m (Step s z)
finitial
case Step s z
res of
FL.Partial s
fs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall b fs sp ss. fs -> DeintercalateState b fs sp ss
DeintercalateInitL s
fs
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone z
c
{-# INLINE processL #-}
processL :: m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL m (Step t b)
foldAction Int
n t -> s
nextState = do
Step t b
fres <- m (Step t b)
foldAction
case Step t b
fres of
FL.Partial t
fs1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (t -> s
nextState t
fs1)
FL.Done b
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n b
c
{-# INLINE runStepL #-}
runStepL :: Int -> s -> s -> a -> m (Step (DeintercalateState b s s ss) z)
runStepL Int
cnt s
fs s
sL a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s x
r <- s -> a -> m (Step s x)
stepL s
sL a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss. Int -> fs -> sp -> DeintercalateState b fs sp ss
DeintercalateL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss. Int -> fs -> sp -> DeintercalateState b fs sp ss
DeintercalateL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n x
b ->
forall {m :: * -> *} {t} {b} {s}.
Monad m =>
m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL (s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. a -> Either a b
Left x
b)) Int
n forall b fs sp ss. fs -> DeintercalateState b fs sp ss
DeintercalateInitR
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 z
xs
{-# INLINE processR #-}
processR :: Int -> b -> fs -> Int -> m (Step (DeintercalateState b fs s ss) b)
processR Int
cnt b
b fs
fs Int
n = do
Initial s x
res <- m (Initial s x)
initialL
case Initial s x
res of
IPartial s
ps -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> DeintercalateState b fs sp ss
DeintercalateRL Int
cnt b
b fs
fs s
ps)
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
{-# INLINE runStepR #-}
runStepR :: Int -> s -> s -> a -> m (Step (DeintercalateState y s s s) z)
runStepR Int
cnt s
fs s
sR a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s y
r <- s -> a -> m (Step s y)
stepR s
sR a
a
case Step s y
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss. Int -> fs -> ss -> DeintercalateState b fs sp ss
DeintercalateR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss. Int -> fs -> ss -> DeintercalateState b fs sp ss
DeintercalateR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n y
b -> forall {b} {fs} {ss} {b}.
Int -> b -> fs -> Int -> m (Step (DeintercalateState b fs s ss) b)
processR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) y
b s
fs Int
n
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 z
xs
step :: DeintercalateState y s s s
-> a -> m (Step (DeintercalateState y s s s) z)
step (DeintercalateInitL s
fs) a
a = do
Initial s x
res <- m (Initial s x)
initialL
case Initial s x
res of
IPartial s
s -> forall {b} {ss}.
Int -> s -> s -> a -> m (Step (DeintercalateState b s s ss) z)
runStepL Int
0 s
fs s
s a
a
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
step (DeintercalateL Int
cnt s
fs s
sL) a
a = forall {b} {ss}.
Int -> s -> s -> a -> m (Step (DeintercalateState b s s ss) z)
runStepL Int
cnt s
fs s
sL a
a
step (DeintercalateInitR s
fs) a
a = do
Initial s y
res <- m (Initial s y)
initialR
case Initial s y
res of
IPartial s
s -> Int -> s -> s -> a -> m (Step (DeintercalateState y s s s) z)
runStepR Int
0 s
fs s
s a
a
IDone y
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"fail"
step (DeintercalateR Int
cnt s
fs s
sR) a
a = Int -> s -> s -> a -> m (Step (DeintercalateState y s s s) z)
runStepR Int
cnt s
fs s
sR a
a
step (DeintercalateRL Int
cnt y
bR s
fs s
sL) a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s x
r <- s -> a -> m (Step s x)
stepL s
sL a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> DeintercalateState b fs sp ss
DeintercalateRL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) y
bR s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> DeintercalateState b fs sp ss
DeintercalateRL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) y
bR s
fs s
s)
Done Int
n x
bL -> do
Step s z
res <- s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. b -> Either a b
Right y
bR)
case Step s z
res of
FL.Partial s
fs1 -> do
Step s z
fres <- s -> Either x y -> m (Step s z)
fstep s
fs1 (forall a b. a -> Either a b
Left x
bL)
case Step s z
fres of
FL.Partial s
fs2 ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall b fs sp ss. fs -> DeintercalateState b fs sp ss
DeintercalateInitR s
fs2)
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n z
c
FL.Done z
_ -> forall a. HasCallStack => String -> a
error String
"Fold terminated consuming partial input"
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 z
xs
{-# INLINE extractResult #-}
extractResult :: Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs Either x y
r = do
Step s z
res <- s -> Either x y -> m (Step s z)
fstep s
fs Either x y
r
case Step s z
res of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
n) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs1
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
n z
c)
extract :: DeintercalateState y s s ss
-> m (Step (DeintercalateState y s s ss) z)
extract (DeintercalateInitL s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs
extract (DeintercalateL Int
cnt s
fs s
sL) = do
Step s x
r <- s -> m (Step s x)
extractL s
sL
case Step s x
r of
Done Int
n x
b -> forall {s}. Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs (forall a b. a -> Either a b
Left x
b)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss. Int -> fs -> sp -> DeintercalateState b fs sp ss
DeintercalateL (Int
cnt forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt z
xs
extract (DeintercalateInitR s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs
extract (DeintercalateR Int
cnt s
fs ss
_) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
cnt) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs
extract (DeintercalateRL Int
cnt y
bR s
fs s
sL) = do
Step s x
r <- s -> m (Step s x)
extractL s
sL
case Step s x
r of
Done Int
n x
bL -> do
Step s z
res <- s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. b -> Either a b
Right y
bR)
case Step s z
res of
FL.Partial s
fs1 -> forall {s}. Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs1 (forall a b. a -> Either a b
Left x
bL)
FL.Done z
_ -> forall a. HasCallStack => String -> a
error String
"Fold terminated consuming partial input"
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> DeintercalateState b fs sp ss
DeintercalateRL (Int
cnt forall a. Num a => a -> a -> a
- Int
n) y
bR s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt z
xs
{-# ANN type Deintercalate1State Fuse #-}
data Deintercalate1State b fs sp ss =
Deintercalate1InitL !Int !fs !sp
| Deintercalate1InitR !fs
| Deintercalate1R !Int !fs !ss
| Deintercalate1RL !Int !b !fs !sp
{-# INLINE deintercalate1 #-}
deintercalate1 :: Monad m =>
Parser a m x
-> Parser a m y
-> Fold m (Either x y) z
-> Parser a m z
deintercalate1 :: forall (m :: * -> *) a x y z.
Monad m =>
Parser a m x
-> Parser a m y -> Fold m (Either x y) z -> Parser a m z
deintercalate1
(Parser s -> a -> m (Step s x)
stepL m (Initial s x)
initialL s -> m (Step s x)
extractL)
(Parser s -> a -> m (Step s y)
stepR m (Initial s y)
initialR s -> m (Step s y)
_)
(Fold s -> Either x y -> m (Step s z)
fstep m (Step s z)
finitial s -> m z
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser Deintercalate1State y s s s
-> a -> m (Step (Deintercalate1State y s s s) z)
step forall {b} {ss}. m (Initial (Deintercalate1State b s s ss) z)
initial forall {ss} {ss}.
Deintercalate1State y s s ss
-> m (Step (Deintercalate1State y s s ss) z)
extract
where
errMsg :: String -> String -> a
errMsg String
p String
status =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"deintercalate: " forall a. [a] -> [a] -> [a]
++ String
p forall a. [a] -> [a] -> [a]
++ String
" parser cannot "
forall a. [a] -> [a] -> [a]
++ String
status forall a. [a] -> [a] -> [a]
++ String
" without input"
initial :: m (Initial (Deintercalate1State b s s ss) z)
initial = do
Step s z
res <- m (Step s z)
finitial
case Step s z
res of
FL.Partial s
fs -> do
Initial s x
pres <- m (Initial s x)
initialL
case Initial s x
pres of
IPartial s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall b fs sp ss.
Int -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1InitL Int
0 s
fs s
s
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone z
c
{-# INLINE processL #-}
processL :: m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL m (Step t b)
foldAction Int
n t -> s
nextState = do
Step t b
fres <- m (Step t b)
foldAction
case Step t b
fres of
FL.Partial t
fs1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (t -> s
nextState t
fs1)
FL.Done b
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n b
c
{-# INLINE runStepInitL #-}
runStepInitL :: Int -> s -> s -> a -> m (Step (Deintercalate1State b s s ss) z)
runStepInitL Int
cnt s
fs s
sL a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s x
r <- s -> a -> m (Step s x)
stepL s
sL a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1InitL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1InitL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n x
b ->
forall {m :: * -> *} {t} {b} {s}.
Monad m =>
m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL (s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. a -> Either a b
Left x
b)) Int
n forall b fs sp ss. fs -> Deintercalate1State b fs sp ss
Deintercalate1InitR
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
{-# INLINE processR #-}
processR :: Int -> b -> fs -> Int -> m (Step (Deintercalate1State b fs s ss) b)
processR Int
cnt b
b fs
fs Int
n = do
Initial s x
res <- m (Initial s x)
initialL
case Initial s x
res of
IPartial s
ps -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1RL Int
cnt b
b fs
fs s
ps)
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
{-# INLINE runStepR #-}
runStepR :: Int -> s -> s -> a -> m (Step (Deintercalate1State y s s s) z)
runStepR Int
cnt s
fs s
sR a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s y
r <- s -> a -> m (Step s y)
stepR s
sR a
a
case Step s y
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> fs -> ss -> Deintercalate1State b fs sp ss
Deintercalate1R (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> fs -> ss -> Deintercalate1State b fs sp ss
Deintercalate1R (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n y
b -> forall {b} {fs} {ss} {b}.
Int -> b -> fs -> Int -> m (Step (Deintercalate1State b fs s ss) b)
processR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) y
b s
fs Int
n
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 z
xs
step :: Deintercalate1State y s s s
-> a -> m (Step (Deintercalate1State y s s s) z)
step (Deintercalate1InitL Int
cnt s
fs s
sL) a
a = forall {b} {ss}.
Int -> s -> s -> a -> m (Step (Deintercalate1State b s s ss) z)
runStepInitL Int
cnt s
fs s
sL a
a
step (Deintercalate1InitR s
fs) a
a = do
Initial s y
res <- m (Initial s y)
initialR
case Initial s y
res of
IPartial s
s -> Int -> s -> s -> a -> m (Step (Deintercalate1State y s s s) z)
runStepR Int
0 s
fs s
s a
a
IDone y
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"fail"
step (Deintercalate1R Int
cnt s
fs s
sR) a
a = Int -> s -> s -> a -> m (Step (Deintercalate1State y s s s) z)
runStepR Int
cnt s
fs s
sR a
a
step (Deintercalate1RL Int
cnt y
bR s
fs s
sL) a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s x
r <- s -> a -> m (Step s x)
stepL s
sL a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1RL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) y
bR s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1RL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) y
bR s
fs s
s)
Done Int
n x
bL -> do
Step s z
res <- s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. b -> Either a b
Right y
bR)
case Step s z
res of
FL.Partial s
fs1 -> do
Step s z
fres <- s -> Either x y -> m (Step s z)
fstep s
fs1 (forall a b. a -> Either a b
Left x
bL)
case Step s z
fres of
FL.Partial s
fs2 ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall b fs sp ss. fs -> Deintercalate1State b fs sp ss
Deintercalate1InitR s
fs2)
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n z
c
FL.Done z
_ -> forall a. HasCallStack => String -> a
error String
"Fold terminated consuming partial input"
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 z
xs
{-# INLINE extractResult #-}
extractResult :: Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs Either x y
r = do
Step s z
res <- s -> Either x y -> m (Step s z)
fstep s
fs Either x y
r
case Step s z
res of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
n) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs1
FL.Done z
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
n z
c)
extract :: Deintercalate1State y s s ss
-> m (Step (Deintercalate1State y s s ss) z)
extract (Deintercalate1InitL Int
cnt s
fs s
sL) = do
Step s x
r <- s -> m (Step s x)
extractL s
sL
case Step s x
r of
Done Int
n x
b -> forall {s}. Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs (forall a b. a -> Either a b
Left x
b)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1InitL (Int
cnt forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
extract (Deintercalate1InitR s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs
extract (Deintercalate1R Int
cnt s
fs ss
_) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
cnt) forall a b. (a -> b) -> a -> b
$ s -> m z
fextract s
fs
extract (Deintercalate1RL Int
cnt y
bR s
fs s
sL) = do
Step s x
r <- s -> m (Step s x)
extractL s
sL
case Step s x
r of
Done Int
n x
bL -> do
Step s z
res <- s -> Either x y -> m (Step s z)
fstep s
fs (forall a b. b -> Either a b
Right y
bR)
case Step s z
res of
FL.Partial s
fs1 -> forall {s}. Int -> s -> Either x y -> m (Step s z)
extractResult Int
n s
fs1 (forall a b. a -> Either a b
Left x
bL)
FL.Done z
_ -> forall a. HasCallStack => String -> a
error String
"Fold terminated consuming partial input"
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall b fs sp ss.
Int -> b -> fs -> sp -> Deintercalate1State b fs sp ss
Deintercalate1RL (Int
cnt forall a. Num a => a -> a -> a
- Int
n) y
bR s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
Error String
_ -> do
z
xs <- s -> m z
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt z
xs
{-# ANN type SepByState Fuse #-}
data SepByState fs sp ss =
SepByInitL !fs
| SepByL !Int !fs !sp
| SepByInitR !fs
| SepByR !Int !fs !ss
{-# INLINE sepBy #-}
sepBy :: Monad m =>
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
sepBy :: forall (m :: * -> *) a b x c.
Monad m =>
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
sepBy
(Parser s -> a -> m (Step s b)
stepL m (Initial s b)
initialL s -> m (Step s b)
extractL)
(Parser s -> a -> m (Step s x)
stepR m (Initial s x)
initialR s -> m (Step s x)
_)
(Fold s -> b -> m (Step s c)
fstep m (Step s c)
finitial s -> m c
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser SepByState s s s -> a -> m (Step (SepByState s s s) c)
step forall {sp} {ss}. m (Initial (SepByState s sp ss) c)
initial forall {ss} {ss}.
SepByState s s ss -> m (Step (SepByState s s ss) c)
extract
where
errMsg :: String -> String -> a
errMsg String
p String
status =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"sepBy: " forall a. [a] -> [a] -> [a]
++ String
p forall a. [a] -> [a] -> [a]
++ String
" parser cannot "
forall a. [a] -> [a] -> [a]
++ String
status forall a. [a] -> [a] -> [a]
++ String
" without input"
initial :: m (Initial (SepByState s sp ss) c)
initial = do
Step s c
res <- m (Step s c)
finitial
case Step s c
res of
FL.Partial s
fs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall fs sp ss. fs -> SepByState fs sp ss
SepByInitL s
fs
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone c
c
{-# INLINE processL #-}
processL :: m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL m (Step t b)
foldAction Int
n t -> s
nextState = do
Step t b
fres <- m (Step t b)
foldAction
case Step t b
fres of
FL.Partial t
fs1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (t -> s
nextState t
fs1)
FL.Done b
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n b
c
{-# INLINE runStepL #-}
runStepL :: Int -> s -> s -> a -> m (Step (SepByState s s ss) c)
runStepL Int
cnt s
fs s
sL a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s b
r <- s -> a -> m (Step s b)
stepL s
sL a
a
case Step s b
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepByState fs sp ss
SepByL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepByState fs sp ss
SepByL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n b
b ->
forall {m :: * -> *} {t} {b} {s}.
Monad m =>
m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL (s -> b -> m (Step s c)
fstep s
fs b
b) Int
n forall fs sp ss. fs -> SepByState fs sp ss
SepByInitR
Error String
_ -> do
c
xs <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 c
xs
{-# INLINE processR #-}
processR :: Int -> fs -> Int -> m (Step (SepByState fs s ss) b)
processR Int
cnt fs
fs Int
n = do
Initial s b
res <- m (Initial s b)
initialL
case Initial s b
res of
IPartial s
ps -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepByState fs sp ss
SepByL Int
cnt fs
fs s
ps)
IDone b
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
{-# INLINE runStepR #-}
runStepR :: Int -> s -> s -> a -> m (Step (SepByState s s s) c)
runStepR Int
cnt s
fs s
sR a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s x
r <- s -> a -> m (Step s x)
stepR s
sR a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> ss -> SepByState fs sp ss
SepByR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> ss -> SepByState fs sp ss
SepByR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n x
_ -> forall {fs} {ss} {b}.
Int -> fs -> Int -> m (Step (SepByState fs s ss) b)
processR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs Int
n
Error String
_ -> do
c
xs <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 c
xs
step :: SepByState s s s -> a -> m (Step (SepByState s s s) c)
step (SepByInitL s
fs) a
a = do
Initial s b
res <- m (Initial s b)
initialL
case Initial s b
res of
IPartial s
s -> forall {ss}. Int -> s -> s -> a -> m (Step (SepByState s s ss) c)
runStepL Int
0 s
fs s
s a
a
IDone b
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
step (SepByL Int
cnt s
fs s
sL) a
a = forall {ss}. Int -> s -> s -> a -> m (Step (SepByState s s ss) c)
runStepL Int
cnt s
fs s
sL a
a
step (SepByInitR s
fs) a
a = do
Initial s x
res <- m (Initial s x)
initialR
case Initial s x
res of
IPartial s
s -> Int -> s -> s -> a -> m (Step (SepByState s s s) c)
runStepR Int
0 s
fs s
s a
a
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"fail"
step (SepByR Int
cnt s
fs s
sR) a
a = Int -> s -> s -> a -> m (Step (SepByState s s s) c)
runStepR Int
cnt s
fs s
sR a
a
{-# INLINE extractResult #-}
extractResult :: Int -> s -> b -> m (Step s c)
extractResult Int
n s
fs b
r = do
Step s c
res <- s -> b -> m (Step s c)
fstep s
fs b
r
case Step s c
res of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
n) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs1
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
n c
c)
extract :: SepByState s s ss -> m (Step (SepByState s s ss) c)
extract (SepByInitL s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs
extract (SepByL Int
cnt s
fs s
sL) = do
Step s b
r <- s -> m (Step s b)
extractL s
sL
case Step s b
r of
Done Int
n b
b -> forall {s}. Int -> s -> b -> m (Step s c)
extractResult Int
n s
fs b
b
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepByState fs sp ss
SepByL (Int
cnt forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
Error String
_ -> do
c
xs <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt c
xs
extract (SepByInitR s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs
extract (SepByR Int
cnt s
fs ss
_) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
cnt) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs
{-# INLINE sepByAll #-}
sepByAll :: Monad m =>
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
sepByAll :: forall (m :: * -> *) a b x c.
Monad m =>
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
sepByAll Parser a m b
p1 Parser a m x
p2 Fold m b c
f = forall (m :: * -> *) a x y z.
Monad m =>
Parser a m x
-> Parser a m y -> Fold m (Either x y) z -> Parser a m z
deintercalateAll Parser a m b
p1 Parser a m x
p2 (forall (m :: * -> *) a c b.
Monad m =>
Fold m a c -> Fold m (Either a b) c
FL.catLefts Fold m b c
f)
{-# ANN type SepBy1State Fuse #-}
data SepBy1State fs sp ss =
SepBy1InitL !Int !fs sp
| SepBy1L !Int !fs !sp
| SepBy1InitR !fs
| SepBy1R !Int !fs !ss
{-# INLINE sepBy1 #-}
sepBy1 :: Monad m =>
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
sepBy1 :: forall (m :: * -> *) a b x c.
Monad m =>
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
sepBy1
(Parser s -> a -> m (Step s b)
stepL m (Initial s b)
initialL s -> m (Step s b)
extractL)
(Parser s -> a -> m (Step s x)
stepR m (Initial s x)
initialR s -> m (Step s x)
_)
(Fold s -> b -> m (Step s c)
fstep m (Step s c)
finitial s -> m c
fextract) = forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser SepBy1State s s s -> a -> m (Step (SepBy1State s s s) c)
step forall {ss}. m (Initial (SepBy1State s s ss) c)
initial forall {ss} {ss}.
SepBy1State s s ss -> m (Step (SepBy1State s s ss) c)
extract
where
errMsg :: String -> String -> a
errMsg String
p String
status =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"sepBy: " forall a. [a] -> [a] -> [a]
++ String
p forall a. [a] -> [a] -> [a]
++ String
" parser cannot "
forall a. [a] -> [a] -> [a]
++ String
status forall a. [a] -> [a] -> [a]
++ String
" without input"
initial :: m (Initial (SepBy1State s s ss) c)
initial = do
Step s c
res <- m (Step s c)
finitial
case Step s c
res of
FL.Partial s
fs -> do
Initial s b
pres <- m (Initial s b)
initialL
case Initial s b
pres of
IPartial s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial forall a b. (a -> b) -> a -> b
$ forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1InitL Int
0 s
fs s
s
IDone b
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone c
c
{-# INLINE processL #-}
processL :: m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL m (Step t b)
foldAction Int
n t -> s
nextState = do
Step t b
fres <- m (Step t b)
foldAction
case Step t b
fres of
FL.Partial t
fs1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (t -> s
nextState t
fs1)
FL.Done b
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n b
c
{-# INLINE runStepInitL #-}
runStepInitL :: Int -> s -> s -> a -> m (Step (SepBy1State s s ss) c)
runStepInitL Int
cnt s
fs s
sL a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s b
r <- s -> a -> m (Step s b)
stepL s
sL a
a
case Step s b
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1InitL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1InitL (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n b
b ->
forall {m :: * -> *} {t} {b} {s}.
Monad m =>
m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL (s -> b -> m (Step s c)
fstep s
fs b
b) Int
n forall fs sp ss. fs -> SepBy1State fs sp ss
SepBy1InitR
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
{-# INLINE runStepL #-}
runStepL :: Int -> s -> s -> a -> m (Step (SepBy1State s s ss) c)
runStepL Int
cnt s
fs s
sL a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s b
r <- s -> a -> m (Step s b)
stepL s
sL a
a
case Step s b
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1L (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1L (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n b
b ->
forall {m :: * -> *} {t} {b} {s}.
Monad m =>
m (Step t b) -> Int -> (t -> s) -> m (Step s b)
processL (s -> b -> m (Step s c)
fstep s
fs b
b) Int
n forall fs sp ss. fs -> SepBy1State fs sp ss
SepBy1InitR
Error String
_ -> do
c
xs <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 c
xs
{-# INLINE processR #-}
processR :: Int -> fs -> Int -> m (Step (SepBy1State fs s ss) b)
processR Int
cnt fs
fs Int
n = do
Initial s b
res <- m (Initial s b)
initialL
case Initial s b
res of
IPartial s
ps -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1L Int
cnt fs
fs s
ps)
IDone b
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"left" String
"fail"
{-# INLINE runStepR #-}
runStepR :: Int -> s -> s -> a -> m (Step (SepBy1State s s s) c)
runStepR Int
cnt s
fs s
sR a
a = do
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
Step s x
r <- s -> a -> m (Step s x)
stepR s
sR a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> ss -> SepBy1State fs sp ss
SepBy1R (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> ss -> SepBy1State fs sp ss
SepBy1R (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n x
_ -> forall {fs} {ss} {b}.
Int -> fs -> Int -> m (Step (SepBy1State fs s ss) b)
processR (Int
cnt1 forall a. Num a => a -> a -> a
- Int
n) s
fs Int
n
Error String
_ -> do
c
xs <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 c
xs
step :: SepBy1State s s s -> a -> m (Step (SepBy1State s s s) c)
step (SepBy1InitL Int
cnt s
fs s
sL) a
a = forall {ss}. Int -> s -> s -> a -> m (Step (SepBy1State s s ss) c)
runStepInitL Int
cnt s
fs s
sL a
a
step (SepBy1L Int
cnt s
fs s
sL) a
a = forall {ss}. Int -> s -> s -> a -> m (Step (SepBy1State s s ss) c)
runStepL Int
cnt s
fs s
sL a
a
step (SepBy1InitR s
fs) a
a = do
Initial s x
res <- m (Initial s x)
initialR
case Initial s x
res of
IPartial s
s -> Int -> s -> s -> a -> m (Step (SepBy1State s s s) c)
runStepR Int
0 s
fs s
s a
a
IDone x
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"succeed"
IError String
_ -> forall {a}. String -> String -> a
errMsg String
"right" String
"fail"
step (SepBy1R Int
cnt s
fs s
sR) a
a = Int -> s -> s -> a -> m (Step (SepBy1State s s s) c)
runStepR Int
cnt s
fs s
sR a
a
{-# INLINE extractResult #-}
extractResult :: Int -> s -> b -> m (Step s c)
extractResult Int
n s
fs b
r = do
Step s c
res <- s -> b -> m (Step s c)
fstep s
fs b
r
case Step s c
res of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
n) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs1
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
n c
c)
extract :: SepBy1State s s ss -> m (Step (SepBy1State s s ss) c)
extract (SepBy1InitL Int
cnt s
fs s
sL) = do
Step s b
r <- s -> m (Step s b)
extractL s
sL
case Step s b
r of
Done Int
n b
b -> forall {s}. Int -> s -> b -> m (Step s c)
extractResult Int
n s
fs b
b
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1InitL (Int
cnt forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
extract (SepBy1L Int
cnt s
fs s
sL) = do
Step s b
r <- s -> m (Step s b)
extractL s
sL
case Step s b
r of
Done Int
n b
b -> forall {s}. Int -> s -> b -> m (Step s c)
extractResult Int
n s
fs b
b
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sp ss. Int -> fs -> sp -> SepBy1State fs sp ss
SepBy1L (Int
cnt forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
Error String
_ -> do
c
xs <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt c
xs
extract (SepBy1InitR s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs
extract (SepBy1R Int
cnt s
fs ss
_) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
cnt) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs
{-# INLINE roundRobin #-}
roundRobin ::
t (Parser a m b) -> Fold m b c -> Parser a m c
roundRobin :: forall (t :: * -> *) a (m :: * -> *) b c.
t (Parser a m b) -> Fold m b c -> Parser a m c
roundRobin t (Parser a m b)
_ps Fold m b c
_f = forall a. HasCallStack => a
undefined
{-# INLINE sequence #-}
sequence :: Monad m =>
D.Stream m (Parser a m b) -> Fold m b c -> Parser a m c
sequence :: forall (m :: * -> *) a b c.
Monad m =>
Stream m (Parser a m b) -> Fold m b c -> Parser a m c
sequence (D.Stream State StreamK m (Parser a m b) -> s -> m (Step s (Parser a m b))
sstep s
sstate) (Fold s -> b -> m (Step s c)
fstep m (Step s c)
finitial s -> m c
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser (Maybe' (Parser a m b), s, s)
-> a -> m (Step (Maybe' (Parser a m b), s, s) c)
step forall {a}. m (Initial (Maybe' a, s, s) c)
initial forall {a} {b}.
(Maybe' (Parser a m b), b, s)
-> m (Step (Maybe' (Parser a m b), b, s) c)
extract
where
initial :: m (Initial (Maybe' a, s, s) c)
initial = do
Step s c
fres <- m (Step s c)
finitial
case Step s c
fres of
FL.Partial s
fs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial (forall a. Maybe' a
Nothing', s
sstate, s
fs)
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone c
c
step :: (Maybe' (Parser a m b), s, s)
-> a -> m (Step (Maybe' (Parser a m b), s, s) c)
step (Maybe' (Parser a m b)
Nothing', s
ss, s
fs) a
_ = do
Step s (Parser a m b)
sres <- State StreamK m (Parser a m b) -> s -> m (Step s (Parser a m b))
sstep forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. State t m a
defState s
ss
case Step s (Parser a m b)
sres of
D.Yield Parser a m b
p s
ss1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
1 (forall a. a -> Maybe' a
Just' Parser a m b
p, s
ss1, s
fs)
Step s (Parser a m b)
D.Stop -> do
c
c <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
1 c
c
D.Skip s
ss1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
1 (forall a. Maybe' a
Nothing', s
ss1, s
fs)
step (Just' (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinit s -> m (Step s b)
pextr), s
ss, s
fs) a
a = do
Initial s b
ps <- m (Initial s b)
pinit
case Initial s b
ps of
IPartial s
ps1 -> do
Step s b
pres <- s -> a -> m (Step s b)
pstep s
ps1 a
a
case Step s b
pres of
Partial Int
n s
ps2 ->
let newP :: Maybe' (Parser a m b)
newP =
forall a. a -> Maybe' a
Just' forall a b. (a -> b) -> a -> b
$ forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
pstep (forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial s
ps2) s -> m (Step s b)
pextr
in forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (Maybe' (Parser a m b)
newP, s
ss, s
fs)
Continue Int
n s
ps2 ->
let newP :: Maybe' (Parser a m b)
newP =
forall a. a -> Maybe' a
Just' forall a b. (a -> b) -> a -> b
$ forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
pstep (forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. s -> Initial s b
IPartial s
ps2) s -> m (Step s b)
pextr
in forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (Maybe' (Parser a m b)
newP, s
ss, s
fs)
Done Int
n b
b -> do
Step s c
fres <- s -> b -> m (Step s c)
fstep s
fs b
b
case Step s c
fres of
FL.Partial s
fs1 ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall a. Maybe' a
Nothing', s
ss, s
fs1)
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n c
c
Error String
msg -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
msg
IDone b
b -> do
Step s c
fres <- s -> b -> m (Step s c)
fstep s
fs b
b
case Step s c
fres of
FL.Partial s
fs1 ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
1 (forall a. Maybe' a
Nothing', s
ss, s
fs1)
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
1 c
c
IError String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
extract :: (Maybe' (Parser a m b), b, s)
-> m (Step (Maybe' (Parser a m b), b, s) c)
extract (Maybe' (Parser a m b)
Nothing', b
_, s
fs) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs
extract (Just' (Parser s -> a -> m (Step s b)
pstep m (Initial s b)
pinit s -> m (Step s b)
pextr), b
ss, s
fs) = do
Initial s b
ps <- m (Initial s b)
pinit
case Initial s b
ps of
IPartial s
ps1 -> do
Step s b
r <- s -> m (Step s b)
pextr s
ps1
case Step s b
r of
Done Int
n b
b -> do
Step s c
res <- s -> b -> m (Step s c)
fstep s
fs b
b
case Step s c
res of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
n) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs1
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
n c
c)
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall a. a -> Maybe' a
Just' (forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser s -> a -> m (Step s b)
pstep (forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. s -> Initial s b
IPartial s
s)) s -> m (Step s b)
pextr), b
ss, s
fs)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
IDone b
b -> do
Step s c
fres <- s -> b -> m (Step s c)
fstep s
fs b
b
case Step s c
fres of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs1
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
0 c
c)
IError String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
{-# INLINE manyP #-}
manyP ::
Parser a m b -> Parser b m c -> Parser a m c
manyP :: forall a (m :: * -> *) b c.
Parser a m b -> Parser b m c -> Parser a m c
manyP Parser a m b
_p Parser b m c
_f = forall a. HasCallStack => a
undefined
{-# INLINE many #-}
many :: Monad m => Parser a m b -> Fold m b c -> Parser a m c
many :: forall (m :: * -> *) a b c.
Monad m =>
Parser a m b -> Fold m b c -> Parser a m c
many = forall (m :: * -> *) a b c.
Monad m =>
Parser a m b -> Fold m b c -> Parser a m c
splitMany
{-# INLINE some #-}
some :: Monad m => Parser a m b -> Fold m b c -> Parser a m c
some :: forall (m :: * -> *) a b c.
Monad m =>
Parser a m b -> Fold m b c -> Parser a m c
some = forall (m :: * -> *) a b c.
Monad m =>
Parser a m b -> Fold m b c -> Parser a m c
splitSome
{-# INLINE countBetween #-}
countBetween ::
Int -> Int -> Parser a m b -> Fold m b c -> Parser a m c
countBetween :: forall a (m :: * -> *) b c.
Int -> Int -> Parser a m b -> Fold m b c -> Parser a m c
countBetween Int
_m Int
_n Parser a m b
_p = forall a. HasCallStack => a
undefined
{-# INLINE count #-}
count ::
Int -> Parser a m b -> Fold m b c -> Parser a m c
count :: forall a (m :: * -> *) b c.
Int -> Parser a m b -> Fold m b c -> Parser a m c
count Int
n = forall a (m :: * -> *) b c.
Int -> Int -> Parser a m b -> Fold m b c -> Parser a m c
countBetween Int
n Int
n
{-# INLINE manyTillP #-}
manyTillP ::
Parser a m b -> Parser a m x -> Parser b m c -> Parser a m c
manyTillP :: forall a (m :: * -> *) b x c.
Parser a m b -> Parser a m x -> Parser b m c -> Parser a m c
manyTillP Parser a m b
_p1 Parser a m x
_p2 Parser b m c
_f = forall a. HasCallStack => a
undefined
{-# ANN type ManyTillState Fuse #-}
data ManyTillState fs sr sl
= ManyTillR !Int !fs !sr
| ManyTillL !fs !sl
{-# INLINE manyTill #-}
manyTill :: Monad m
=> Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
manyTill :: forall (m :: * -> *) a b x c.
Monad m =>
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
manyTill (Parser s -> a -> m (Step s b)
stepL m (Initial s b)
initialL s -> m (Step s b)
extractL)
(Parser s -> a -> m (Step s x)
stepR m (Initial s x)
initialR s -> m (Step s x)
_)
(Fold s -> b -> m (Step s c)
fstep m (Step s c)
finitial s -> m c
fextract) =
forall a (m :: * -> *) b s.
(s -> a -> m (Step s b))
-> m (Initial s b) -> (s -> m (Step s b)) -> Parser a m b
Parser ManyTillState s s s -> a -> m (Step (ManyTillState s s s) c)
step m (Initial (ManyTillState s s s) c)
initial forall {sr} {sr}.
ManyTillState s sr s -> m (Step (ManyTillState s sr s) c)
extract
where
scrutL :: s
-> (ManyTillState s s sl -> b)
-> (ManyTillState s sr s -> b)
-> (c -> b)
-> (String -> b)
-> m b
scrutL s
fs ManyTillState s s sl -> b
p ManyTillState s sr s -> b
c c -> b
d String -> b
e = do
Initial s b
resL <- m (Initial s b)
initialL
case Initial s b
resL of
IPartial s
sl -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ManyTillState s sr s -> b
c (forall fs sr sl. fs -> sl -> ManyTillState fs sr sl
ManyTillL s
fs s
sl)
IDone b
bl -> do
Step s c
fr <- s -> b -> m (Step s c)
fstep s
fs b
bl
case Step s c
fr of
FL.Partial s
fs1 -> s
-> (ManyTillState s s sl -> b)
-> (ManyTillState s sr s -> b)
-> (c -> b)
-> (String -> b)
-> m b
scrutR s
fs1 ManyTillState s s sl -> b
p ManyTillState s sr s -> b
c c -> b
d String -> b
e
FL.Done c
fb -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ c -> b
d c
fb
IError String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> b
e String
err
scrutR :: s
-> (ManyTillState s s sl -> b)
-> (ManyTillState s sr s -> b)
-> (c -> b)
-> (String -> b)
-> m b
scrutR s
fs ManyTillState s s sl -> b
p ManyTillState s sr s -> b
c c -> b
d String -> b
e = do
Initial s x
resR <- m (Initial s x)
initialR
case Initial s x
resR of
IPartial s
sr -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ManyTillState s s sl -> b
p (forall fs sr sl. Int -> fs -> sr -> ManyTillState fs sr sl
ManyTillR Int
0 s
fs s
sr)
IDone x
_ -> c -> b
d forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> s -> m c
fextract s
fs
IError String
_ -> s
-> (ManyTillState s s sl -> b)
-> (ManyTillState s sr s -> b)
-> (c -> b)
-> (String -> b)
-> m b
scrutL s
fs ManyTillState s s sl -> b
p ManyTillState s sr s -> b
c c -> b
d String -> b
e
initial :: m (Initial (ManyTillState s s s) c)
initial = do
Step s c
res <- m (Step s c)
finitial
case Step s c
res of
FL.Partial s
fs -> forall {sl} {b} {sr}.
s
-> (ManyTillState s s sl -> b)
-> (ManyTillState s sr s -> b)
-> (c -> b)
-> (String -> b)
-> m b
scrutR s
fs forall s b. s -> Initial s b
IPartial forall s b. s -> Initial s b
IPartial forall s b. b -> Initial s b
IDone forall s b. String -> Initial s b
IError
FL.Done c
b -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. b -> Initial s b
IDone c
b
step :: ManyTillState s s s -> a -> m (Step (ManyTillState s s s) c)
step (ManyTillR Int
cnt s
fs s
st) a
a = do
Step s x
r <- s -> a -> m (Step s x)
stepR s
st a
a
case Step s x
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall fs sr sl. Int -> fs -> sr -> ManyTillState fs sr sl
ManyTillR Int
0 s
fs s
s)
Continue Int
n s
s -> do
assertM(Int
cnt forall a. Num a => a -> a -> a
+ Int
1 forall a. Num a => a -> a -> a
- Int
n forall a. Ord a => a -> a -> Bool
>= Int
0)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sr sl. Int -> fs -> sr -> ManyTillState fs sr sl
ManyTillR (Int
cnt forall a. Num a => a -> a -> a
+ Int
1 forall a. Num a => a -> a -> a
- Int
n) s
fs s
s)
Done Int
n x
_ -> do
c
b <- s -> m c
fextract s
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n c
b
Error String
_ -> do
Initial s b
resL <- m (Initial s b)
initialL
case Initial s b
resL of
IPartial s
sl ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue (Int
cnt forall a. Num a => a -> a -> a
+ Int
1) (forall fs sr sl. fs -> sl -> ManyTillState fs sr sl
ManyTillL s
fs s
sl)
IDone b
bl -> do
Step s c
fr <- s -> b -> m (Step s c)
fstep s
fs b
bl
let cnt1 :: Int
cnt1 = Int
cnt forall a. Num a => a -> a -> a
+ Int
1
case Step s c
fr of
FL.Partial s
fs1 ->
forall {sl} {b} {sr}.
s
-> (ManyTillState s s sl -> b)
-> (ManyTillState s sr s -> b)
-> (c -> b)
-> (String -> b)
-> m b
scrutR
s
fs1
(forall s b. Int -> s -> Step s b
Partial Int
cnt1)
(forall s b. Int -> s -> Step s b
Continue Int
cnt1)
(forall s b. Int -> b -> Step s b
Done Int
cnt1)
forall s b. String -> Step s b
Error
FL.Done c
fb -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
cnt1 c
fb
IError String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
step (ManyTillL s
fs s
st) a
a = do
Step s b
r <- s -> a -> m (Step s b)
stepL s
st a
a
case Step s b
r of
Partial Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Partial Int
n (forall fs sr sl. fs -> sl -> ManyTillState fs sr sl
ManyTillL s
fs s
s)
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sr sl. fs -> sl -> ManyTillState fs sr sl
ManyTillL s
fs s
s)
Done Int
n b
b -> do
Step s c
fs1 <- s -> b -> m (Step s c)
fstep s
fs b
b
case Step s c
fs1 of
FL.Partial s
s ->
forall {sl} {b} {sr}.
s
-> (ManyTillState s s sl -> b)
-> (ManyTillState s sr s -> b)
-> (c -> b)
-> (String -> b)
-> m b
scrutR s
s (forall s b. Int -> s -> Step s b
Partial Int
n) (forall s b. Int -> s -> Step s b
Continue Int
n) (forall s b. Int -> b -> Step s b
Done Int
n) forall s b. String -> Step s b
Error
FL.Done c
b1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> b -> Step s b
Done Int
n c
b1
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
extract :: ManyTillState s sr s -> m (Step (ManyTillState s sr s) c)
extract (ManyTillL s
fs s
sR) = do
Step s b
res <- s -> m (Step s b)
extractL s
sR
case Step s b
res of
Done Int
n b
b -> do
Step s c
r <- s -> b -> m (Step s c)
fstep s
fs b
b
case Step s c
r of
FL.Partial s
fs1 -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
n) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs1
FL.Done c
c -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s b. Int -> b -> Step s b
Done Int
n c
c)
Error String
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. String -> Step s b
Error String
err
Continue Int
n s
s -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall s b. Int -> s -> Step s b
Continue Int
n (forall fs sr sl. fs -> sl -> ManyTillState fs sr sl
ManyTillL s
fs s
s)
Partial Int
_ s
_ -> forall a. HasCallStack => String -> a
error String
"Partial in extract"
extract (ManyTillR Int
_ s
fs sr
_) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s b. Int -> b -> Step s b
Done Int
0) forall a b. (a -> b) -> a -> b
$ s -> m c
fextract s
fs
{-# INLINE manyThen #-}
manyThen ::
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
manyThen :: forall a (m :: * -> *) b x c.
Parser a m b -> Parser a m x -> Fold m b c -> Parser a m c
manyThen Parser a m b
_parser Parser a m x
_recover Fold m b c
_f = forall a. HasCallStack => a
undefined
{-# INLINE retryMaxTotal #-}
retryMaxTotal ::
Int -> Parser a m b -> Fold m b c -> Parser a m c
retryMaxTotal :: forall a (m :: * -> *) b c.
Int -> Parser a m b -> Fold m b c -> Parser a m c
retryMaxTotal Int
_n Parser a m b
_p Fold m b c
_f = forall a. HasCallStack => a
undefined
{-# INLINE retryMaxSuccessive #-}
retryMaxSuccessive ::
Int -> Parser a m b -> Fold m b c -> Parser a m c
retryMaxSuccessive :: forall a (m :: * -> *) b c.
Int -> Parser a m b -> Fold m b c -> Parser a m c
retryMaxSuccessive Int
_n Parser a m b
_p Fold m b c
_f = forall a. HasCallStack => a
undefined
{-# INLINE retry #-}
retry ::
Parser a m b -> Parser a m b
retry :: forall a (m :: * -> *) b. Parser a m b -> Parser a m b
retry Parser a m b
_p = forall a. HasCallStack => a
undefined