{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Replace.Megaparsec.Internal.Text
(
sepCapText
, anyTillText
)
where
import Control.Monad
import qualified Data.Text as T
import Data.Text.Internal (Text(..))
import Text.Megaparsec
{-# INLINE [1] sepCapText #-}
sepCapText
:: forall e s m a. (MonadParsec e s m, s ~ T.Text)
=> m a
-> m [Either (Tokens s) a]
sepCapText :: m a -> m [Either (Tokens s) a]
sepCapText m a
sep = m Text
forall e s (m :: * -> *). MonadParsec e s m => m s
getInput m Text -> (Text -> m [Either Text a]) -> m [Either Text a]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> m [Either Text a]
go
where
go :: Text -> m [Either Text a]
go restBegin :: Text
restBegin@(Text Array
tarray Int
beginIndx Int
beginLen) = do
m [Either Text a] -> m [Either Text a] -> m [Either Text a]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
( do
(Text Array
_ Int
_ Int
thisLen) <- m Text
forall e s (m :: * -> *). MonadParsec e s m => m s
getInput
Maybe (a, Text)
thisiter <- m (Maybe (a, Text)) -> m (Maybe (a, Text)) -> m (Maybe (a, Text))
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
( do
a
x <- m a -> m a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try m a
sep
restAfter :: Text
restAfter@(Text Array
_ Int
_ Int
afterLen) <- m Text
forall e s (m :: * -> *). MonadParsec e s m => m s
getInput
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
afterLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
thisLen) m ()
forall (f :: * -> *) a. Alternative f => f a
empty
Maybe (a, Text) -> m (Maybe (a, Text))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (a, Text) -> m (Maybe (a, Text)))
-> Maybe (a, Text) -> m (Maybe (a, Text))
forall a b. (a -> b) -> a -> b
$ (a, Text) -> Maybe (a, Text)
forall a. a -> Maybe a
Just (a
x, Text
restAfter)
)
(m Char
forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle m Char -> m (Maybe (a, Text)) -> m (Maybe (a, Text))
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe (a, Text) -> m (Maybe (a, Text))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (a, Text)
forall a. Maybe a
Nothing)
case Maybe (a, Text)
thisiter of
(Just (a
x, Text
restAfter)) | Int
thisLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
beginLen -> do
let unmatched :: Text
unmatched = Array -> Int -> Int -> Text
Text Array
tarray Int
beginIndx (Int
beginLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
thisLen)
(Text -> Either Text a
forall a b. a -> Either a b
Left Text
unmatchedEither Text a -> [Either Text a] -> [Either Text a]
forall a. a -> [a] -> [a]
:) ([Either Text a] -> [Either Text a])
-> ([Either Text a] -> [Either Text a])
-> [Either Text a]
-> [Either Text a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> Either Text a
forall a b. b -> Either a b
Right a
xEither Text a -> [Either Text a] -> [Either Text a]
forall a. a -> [a] -> [a]
:) ([Either Text a] -> [Either Text a])
-> m [Either Text a] -> m [Either Text a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> m [Either Text a]
go Text
restAfter
(Just (a
x, Text
restAfter)) -> do
(a -> Either Text a
forall a b. b -> Either a b
Right a
xEither Text a -> [Either Text a] -> [Either Text a]
forall a. a -> [a] -> [a]
:) ([Either Text a] -> [Either Text a])
-> m [Either Text a] -> m [Either Text a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> m [Either Text a]
go Text
restAfter
Maybe (a, Text)
Nothing -> Text -> m [Either Text a]
go Text
restBegin
)
( do
if Int
beginLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then
[Either Text a] -> m [Either Text a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Text -> Either Text a
forall a b. a -> Either a b
Left Text
restBegin]
else [Either Text a] -> m [Either Text a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
)
{-# INLINE [1] anyTillText #-}
anyTillText
:: forall e s m a. (MonadParsec e s m, s ~ T.Text)
=> m a
-> m (Tokens s, a)
anyTillText :: m a -> m (Tokens s, a)
anyTillText m a
sep = do
(Text Array
tarray Int
beginIndx Int
beginLen) <- m Text
forall e s (m :: * -> *). MonadParsec e s m => m s
getInput
(Int
thisLen, a
x) <- m (Int, a)
go
(Text, a) -> m (Text, a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Array -> Int -> Int -> Text
Text Array
tarray Int
beginIndx (Int
beginLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
thisLen), a
x)
where
go :: m (Int, a)
go = do
(Text Array
_ Int
_ Int
thisLen) <- m Text
forall e s (m :: * -> *). MonadParsec e s m => m s
getInput
Maybe a
r <- m a -> m (Maybe a)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (m a -> m (Maybe a)) -> m a -> m (Maybe a)
forall a b. (a -> b) -> a -> b
$ m a -> m a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try m a
sep
case Maybe a
r of
Maybe a
Nothing -> m Char
forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
anySingle m Char -> m (Int, a) -> m (Int, a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m (Int, a)
go
Just a
x -> (Int, a) -> m (Int, a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int
thisLen, a
x)