{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Replace.Megaparsec.Internal.ByteString
(
sepCapByteString
, anyTillByteString
)
where
import Control.Monad
import qualified Data.ByteString as B
import Text.Megaparsec
{-# INLINE [1] sepCapByteString #-}
sepCapByteString
:: forall e s m a. (MonadParsec e s m, s ~ B.ByteString)
=> m a
-> m [Either (Tokens s) a]
sepCapByteString sep = getInput >>= go
where
go restBegin = do
(<|>)
( do
restThis <- getInput
thisiter <- (<|>)
( do
x <- try sep
restAfter <- getInput
when (B.length restAfter >= B.length restThis) empty
pure $ Just (x, restAfter)
)
(anySingle >> pure Nothing)
case thisiter of
(Just (x, restAfter)) | B.length restThis < B.length restBegin -> do
let unmatched = B.take (B.length restBegin - B.length restThis) restBegin
(Left unmatched:) <$> (Right x:) <$> go restAfter
(Just (x, restAfter)) -> do
(Right x:) <$> go restAfter
Nothing -> go restBegin
)
( do
if B.length restBegin > 0 then
pure [Left restBegin]
else pure []
)
{-# INLINE [1] anyTillByteString #-}
anyTillByteString
:: forall e s m a. (MonadParsec e s m, s ~ B.ByteString)
=> m a
-> m (Tokens s, a)
anyTillByteString sep = do
begin <- getInput
(end, x) <- go
pure (B.take (B.length begin - B.length end) begin, x)
where
go = do
end <- getInput
r <- optional $ try sep
case r of
Nothing -> anySingle >> go
Just x -> pure (end, x)