{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Pipes.Text
(
fromLazy,
map,
concatMap,
take,
takeWhile,
filter,
toCaseFold,
toLower,
toUpper,
stripStart,
scan,
toLazy,
toLazyM,
foldChars,
head,
last,
null,
length,
any,
all,
maximum,
minimum,
find,
index,
nextChar,
drawChar,
unDrawChar,
peekChar,
isEndOfChars,
splitAt,
span,
break,
groupBy,
group,
word,
line,
drop,
dropWhile,
pack,
unpack,
intersperse,
chunksOf,
splitsWith,
splits,
groupsBy,
groups,
lines,
unlines,
words,
unwords,
intercalate,
module Data.ByteString,
module Data.Text,
module Pipes.Parse,
module Pipes.Group,
)
where
import Control.Monad (join)
import Control.Monad.Trans.State.Strict (modify)
import Data.Bits (shiftL)
import Data.ByteString (ByteString)
import Data.Char (isSpace)
import Data.Foldable (traverse_)
import Data.Functor.Constant (Constant (..))
import Data.Functor.Identity (Identity)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Foreign.Storable (sizeOf)
import Pipes
import Pipes.Group (FreeF (..), FreeT (..), concats, folds, intercalates, maps)
import qualified Pipes.Group as PG
import Pipes.Parse (Parser)
import qualified Pipes.Parse as PP
import qualified Pipes.Prelude as P
import Prelude hiding
( all,
any,
break,
concat,
concatMap,
drop,
dropWhile,
elem,
filter,
head,
last,
length,
lines,
map,
maximum,
minimum,
notElem,
null,
readFile,
span,
splitAt,
take,
takeWhile,
unlines,
unwords,
words,
writeFile,
)
fromLazy :: (Monad m) => TL.Text -> Producer' Text m ()
fromLazy :: Text -> Producer' Text m ()
fromLazy Text
str = (Text -> Proxy x' x () Text m () -> Proxy x' x () Text m ())
-> Proxy x' x () Text m () -> Text -> Proxy x' x () Text m ()
forall a. (Text -> a -> a) -> a -> Text -> a
TL.foldrChunks (\Text
e Proxy x' x () Text m ()
a -> Text -> Proxy x' x () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
e Proxy x' x () Text m ()
-> Proxy x' x () Text m () -> Proxy x' x () Text m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Proxy x' x () Text m ()
a) (() -> Proxy x' x () Text m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) Text
str
{-# INLINE fromLazy #-}
(^.) :: a -> ((b -> Constant b b) -> (a -> Constant b a)) -> b
a
a ^. :: a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (b -> Constant b b) -> a -> Constant b a
lens = Constant b a -> b
forall a k (b :: k). Constant a b -> a
getConstant ((b -> Constant b b) -> a -> Constant b a
lens b -> Constant b b
forall k a (b :: k). a -> Constant a b
Constant a
a)
map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
map :: (Char -> Char) -> Pipe Text Text m r
map Char -> Char
f = (Text -> Text) -> Pipe Text Text m r
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map ((Char -> Char) -> Text -> Text
T.map Char -> Char
f)
{-# INLINEABLE map #-}
concatMap ::
(Monad m) => (Char -> Text) -> Pipe Text Text m r
concatMap :: (Char -> Text) -> Pipe Text Text m r
concatMap Char -> Text
f = (Text -> Text) -> Pipe Text Text m r
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map ((Char -> Text) -> Text -> Text
T.concatMap Char -> Text
f)
{-# INLINEABLE concatMap #-}
take :: (Monad m, Integral a) => a -> Pipe Text Text m ()
take :: a -> Pipe Text Text m ()
take = a -> Pipe Text Text m ()
forall t (m :: * -> *).
(Functor m, Integral t) =>
t -> Proxy () Text () Text m ()
go
where
go :: t -> Proxy () Text () Text m ()
go t
n
| t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
<= t
0 = () -> Proxy () Text () Text m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
Text
txt <- Proxy () Text () Text m Text
forall (m :: * -> *) a. Functor m => Consumer' a m a
await
let len :: t
len = Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Text -> Int
T.length Text
txt)
if t
len t -> t -> Bool
forall a. Ord a => a -> a -> Bool
> t
n
then Text -> Proxy () Text () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Int -> Text -> Text
T.take (t -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral t
n) Text
txt)
else do
Text -> Proxy () Text () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt
t -> Proxy () Text () Text m ()
go (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
len)
{-# INLINEABLE take #-}
takeWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m ()
takeWhile :: (Char -> Bool) -> Pipe Text Text m ()
takeWhile Char -> Bool
predicate = Pipe Text Text m ()
go
where
go :: Pipe Text Text m ()
go = do
Text
txt <- Proxy () Text () Text m Text
forall (m :: * -> *) a. Functor m => Consumer' a m a
await
let (Text
prefix, Text
suffix) = (Char -> Bool) -> Text -> (Text, Text)
T.span Char -> Bool
predicate Text
txt
if Text -> Bool
T.null Text
suffix
then do
Text -> Pipe Text Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt
Pipe Text Text m ()
go
else Text -> Pipe Text Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
prefix
{-# INLINEABLE takeWhile #-}
filter :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
filter :: (Char -> Bool) -> Pipe Text Text m r
filter Char -> Bool
predicate = (Text -> Text) -> Pipe Text Text m r
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map ((Char -> Bool) -> Text -> Text
T.filter Char -> Bool
predicate)
{-# INLINEABLE filter #-}
scan ::
(Monad m) =>
(Char -> Char -> Char) ->
Char ->
Pipe Text Text m r
scan :: (Char -> Char -> Char) -> Char -> Pipe Text Text m r
scan Char -> Char -> Char
step Char
begin = do
Text -> Proxy () Text () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Char -> Text
T.singleton Char
begin)
Char -> Pipe Text Text m r
go Char
begin
where
go :: Char -> Pipe Text Text m r
go Char
c = do
Text
txt <- Proxy () Text () Text m Text
forall (m :: * -> *) a. Functor m => Consumer' a m a
await
let txt' :: Text
txt' = (Char -> Char -> Char) -> Char -> Text -> Text
T.scanl Char -> Char -> Char
step Char
c Text
txt
c' :: Char
c' = Text -> Char
T.last Text
txt'
Text -> Proxy () Text () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Text -> Text
T.tail Text
txt')
Char -> Pipe Text Text m r
go Char
c'
{-# INLINEABLE scan #-}
toCaseFold :: Monad m => Pipe Text Text m r
toCaseFold :: Pipe Text Text m r
toCaseFold = (Text -> Text) -> Pipe Text Text m r
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map Text -> Text
T.toCaseFold
{-# INLINEABLE toCaseFold #-}
toLower :: Monad m => Pipe Text Text m r
toLower :: Pipe Text Text m r
toLower = (Text -> Text) -> Pipe Text Text m r
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map Text -> Text
T.toLower
{-# INLINEABLE toLower #-}
toUpper :: Monad m => Pipe Text Text m r
toUpper :: Pipe Text Text m r
toUpper = (Text -> Text) -> Pipe Text Text m r
forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map Text -> Text
T.toUpper
{-# INLINEABLE toUpper #-}
stripStart :: Monad m => Pipe Text Text m r
stripStart :: Pipe Text Text m r
stripStart = do
Text
chunk <- Proxy () Text () Text m Text
forall (m :: * -> *) a. Functor m => Consumer' a m a
await
let text :: Text
text = Text -> Text
T.stripStart Text
chunk
if Text -> Bool
T.null Text
text
then Pipe Text Text m r
forall (m :: * -> *) r. Monad m => Pipe Text Text m r
stripStart
else do
Text -> Proxy () Text () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
text
Pipe Text Text m r
forall (m :: * -> *) a r. Functor m => Pipe a a m r
cat
{-# INLINEABLE stripStart #-}
toLazy :: Producer Text Identity () -> TL.Text
toLazy :: Producer Text Identity () -> Text
toLazy = [Text] -> Text
TL.fromChunks ([Text] -> Text)
-> (Producer Text Identity () -> [Text])
-> Producer Text Identity ()
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Producer Text Identity () -> [Text]
forall a. Producer a Identity () -> [a]
P.toList
{-# INLINEABLE toLazy #-}
toLazyM :: (Monad m) => Producer Text m () -> m TL.Text
toLazyM :: Producer Text m () -> m Text
toLazyM = ([Text] -> Text) -> m [Text] -> m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Text] -> Text
TL.fromChunks (m [Text] -> m Text)
-> (Producer Text m () -> m [Text]) -> Producer Text m () -> m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Producer Text m () -> m [Text]
forall (m :: * -> *) a. Monad m => Producer a m () -> m [a]
P.toListM
{-# INLINEABLE toLazyM #-}
foldChars ::
Monad m =>
(x -> Char -> x) ->
x ->
(x -> r) ->
Producer Text m () ->
m r
foldChars :: (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r
foldChars x -> Char -> x
step = (x -> Text -> x) -> x -> (x -> r) -> Producer Text m () -> m r
forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold ((x -> Char -> x) -> x -> Text -> x
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' x -> Char -> x
step)
{-# INLINEABLE foldChars #-}
head :: (Monad m) => Producer Text m () -> m (Maybe Char)
head :: Producer Text m () -> m (Maybe Char)
head = Producer Text m () -> m (Maybe Char)
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> m (Maybe Char)
go
where
go :: Producer Text m r -> m (Maybe Char)
go Producer Text m r
p = do
Either r (Char, Producer Text m r)
x <- Producer Text m r -> m (Either r (Char, Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> m (Either r (Char, Producer Text m r))
nextChar Producer Text m r
p
case Either r (Char, Producer Text m r)
x of
Left r
_ -> Maybe Char -> m (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Char
forall a. Maybe a
Nothing
Right (Char
c, Producer Text m r
_) -> Maybe Char -> m (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> Maybe Char
forall a. a -> Maybe a
Just Char
c)
{-# INLINEABLE head #-}
last :: (Monad m) => Producer Text m () -> m (Maybe Char)
last :: Producer Text m () -> m (Maybe Char)
last = Maybe Char -> Producer Text m () -> m (Maybe Char)
forall (m :: * -> *).
Monad m =>
Maybe Char -> Producer Text m () -> m (Maybe Char)
go Maybe Char
forall a. Maybe a
Nothing
where
go :: Maybe Char -> Producer Text m () -> m (Maybe Char)
go Maybe Char
r Producer Text m ()
p = do
Either () (Text, Producer Text m ())
x <- Producer Text m () -> m (Either () (Text, Producer Text m ()))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m ()
p
case Either () (Text, Producer Text m ())
x of
Left () -> Maybe Char -> m (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Char
r
Right (Text
txt, Producer Text m ()
p') ->
if Text -> Bool
T.null Text
txt
then Maybe Char -> Producer Text m () -> m (Maybe Char)
go Maybe Char
r Producer Text m ()
p'
else Maybe Char -> Producer Text m () -> m (Maybe Char)
go (Char -> Maybe Char
forall a. a -> Maybe a
Just (Char -> Maybe Char) -> Char -> Maybe Char
forall a b. (a -> b) -> a -> b
$ Text -> Char
T.last Text
txt) Producer Text m ()
p'
{-# INLINEABLE last #-}
null :: (Monad m) => Producer Text m () -> m Bool
null :: Producer Text m () -> m Bool
null = (Text -> Bool) -> Producer Text m () -> m Bool
forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.all Text -> Bool
T.null
{-# INLINEABLE null #-}
length :: (Monad m, Num n) => Producer Text m () -> m n
length :: Producer Text m () -> m n
length = (n -> Text -> n) -> n -> (n -> n) -> Producer Text m () -> m n
forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold (\n
n Text
txt -> n
n n -> n -> n
forall a. Num a => a -> a -> a
+ Int -> n
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Text -> Int
T.length Text
txt)) n
0 n -> n
forall a. a -> a
id
{-# INLINEABLE length #-}
any :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
any :: (Char -> Bool) -> Producer Text m () -> m Bool
any Char -> Bool
predicate = (Text -> Bool) -> Producer Text m () -> m Bool
forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.any ((Char -> Bool) -> Text -> Bool
T.any Char -> Bool
predicate)
{-# INLINEABLE any #-}
all :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
all :: (Char -> Bool) -> Producer Text m () -> m Bool
all Char -> Bool
predicate = (Text -> Bool) -> Producer Text m () -> m Bool
forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.all ((Char -> Bool) -> Text -> Bool
T.all Char -> Bool
predicate)
{-# INLINEABLE all #-}
maximum :: (Monad m) => Producer Text m () -> m (Maybe Char)
maximum :: Producer Text m () -> m (Maybe Char)
maximum = (Maybe Char -> Text -> Maybe Char)
-> Maybe Char
-> (Maybe Char -> Maybe Char)
-> Producer Text m ()
-> m (Maybe Char)
forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold Maybe Char -> Text -> Maybe Char
step Maybe Char
forall a. Maybe a
Nothing Maybe Char -> Maybe Char
forall a. a -> a
id
where
step :: Maybe Char -> Text -> Maybe Char
step Maybe Char
mc Text
txt =
if Text -> Bool
T.null Text
txt
then Maybe Char
mc
else Char -> Maybe Char
forall a. a -> Maybe a
Just (Char -> Maybe Char) -> Char -> Maybe Char
forall a b. (a -> b) -> a -> b
$ case Maybe Char
mc of
Maybe Char
Nothing -> Text -> Char
T.maximum Text
txt
Just Char
c -> Char -> Char -> Char
forall a. Ord a => a -> a -> a
max Char
c (Text -> Char
T.maximum Text
txt)
{-# INLINEABLE maximum #-}
minimum :: (Monad m) => Producer Text m () -> m (Maybe Char)
minimum :: Producer Text m () -> m (Maybe Char)
minimum = (Maybe Char -> Text -> Maybe Char)
-> Maybe Char
-> (Maybe Char -> Maybe Char)
-> Producer Text m ()
-> m (Maybe Char)
forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold Maybe Char -> Text -> Maybe Char
step Maybe Char
forall a. Maybe a
Nothing Maybe Char -> Maybe Char
forall a. a -> a
id
where
step :: Maybe Char -> Text -> Maybe Char
step Maybe Char
mc Text
txt =
if Text -> Bool
T.null Text
txt
then Maybe Char
mc
else case Maybe Char
mc of
Maybe Char
Nothing -> Char -> Maybe Char
forall a. a -> Maybe a
Just (Text -> Char
T.minimum Text
txt)
Just Char
c -> Char -> Maybe Char
forall a. a -> Maybe a
Just (Char -> Char -> Char
forall a. Ord a => a -> a -> a
min Char
c (Text -> Char
T.minimum Text
txt))
{-# INLINEABLE minimum #-}
find ::
(Monad m) =>
(Char -> Bool) ->
Producer Text m () ->
m (Maybe Char)
find :: (Char -> Bool) -> Producer Text m () -> m (Maybe Char)
find Char -> Bool
predicate Producer Text m ()
p = Producer Text m () -> m (Maybe Char)
forall (m :: * -> *).
Monad m =>
Producer Text m () -> m (Maybe Char)
head (Producer Text m ()
p Producer Text m ()
-> Proxy () Text () Text m () -> Producer Text m ()
forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> (Char -> Bool) -> Proxy () Text () Text m ()
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool) -> Pipe Text Text m r
filter Char -> Bool
predicate)
{-# INLINEABLE find #-}
index ::
(Monad m, Integral a) =>
a ->
Producer Text m () ->
m (Maybe Char)
index :: a -> Producer Text m () -> m (Maybe Char)
index a
n Producer Text m ()
p = Producer Text m () -> m (Maybe Char)
forall (m :: * -> *).
Monad m =>
Producer Text m () -> m (Maybe Char)
head (a -> Producer Text m () -> Producer Text m ()
forall (m :: * -> *) n r.
(Monad m, Integral n) =>
n -> Producer Text m r -> Producer Text m r
drop a
n Producer Text m ()
p)
{-# INLINEABLE index #-}
nextChar ::
(Monad m) =>
Producer Text m r ->
m (Either r (Char, Producer Text m r))
nextChar :: Producer Text m r -> m (Either r (Char, Producer Text m r))
nextChar = Producer Text m r -> m (Either r (Char, Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> m (Either r (Char, Producer Text m r))
go
where
go :: Producer Text m b -> m (Either b (Char, Producer Text m b))
go Producer Text m b
p = do
Either b (Text, Producer Text m b)
x <- Producer Text m b -> m (Either b (Text, Producer Text m b))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m b
p
case Either b (Text, Producer Text m b)
x of
Left b
r -> Either b (Char, Producer Text m b)
-> m (Either b (Char, Producer Text m b))
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either b (Char, Producer Text m b)
forall a b. a -> Either a b
Left b
r)
Right (Text
txt, Producer Text m b
p') -> case Text -> Maybe (Char, Text)
T.uncons Text
txt of
Maybe (Char, Text)
Nothing -> Producer Text m b -> m (Either b (Char, Producer Text m b))
go Producer Text m b
p'
Just (Char
c, Text
txt') -> Either b (Char, Producer Text m b)
-> m (Either b (Char, Producer Text m b))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Char, Producer Text m b) -> Either b (Char, Producer Text m b)
forall a b. b -> Either a b
Right (Char
c, Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt' Proxy X () () Text m () -> Producer Text m b -> Producer Text m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m b
p'))
{-# INLINEABLE nextChar #-}
drawChar :: (Monad m) => Parser Text m (Maybe Char)
drawChar :: Parser Text m (Maybe Char)
drawChar = do
Maybe Text
x <- StateT (Producer Text m x) m (Maybe Text)
forall (m :: * -> *) a. Monad m => Parser a m (Maybe a)
PP.draw
case Maybe Text
x of
Maybe Text
Nothing -> Maybe Char -> StateT (Producer Text m x) m (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Char
forall a. Maybe a
Nothing
Just Text
txt -> case Text -> Maybe (Char, Text)
T.uncons Text
txt of
Maybe (Char, Text)
Nothing -> StateT (Producer Text m x) m (Maybe Char)
forall (m :: * -> *). Monad m => Parser Text m (Maybe Char)
drawChar
Just (Char
c, Text
txt') -> do
Text -> Parser Text m ()
forall (m :: * -> *) a. Monad m => a -> Parser a m ()
PP.unDraw Text
txt'
Maybe Char -> StateT (Producer Text m x) m (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> Maybe Char
forall a. a -> Maybe a
Just Char
c)
{-# INLINEABLE drawChar #-}
unDrawChar :: (Monad m) => Char -> Parser Text m ()
unDrawChar :: Char -> Parser Text m ()
unDrawChar Char
c = (Proxy X () () Text m x -> Proxy X () () Text m x)
-> StateT (Proxy X () () Text m x) m ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Char -> Text
T.singleton Char
c) Proxy X () () Text m ()
-> Proxy X () () Text m x -> Proxy X () () Text m x
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>)
{-# INLINEABLE unDrawChar #-}
peekChar :: (Monad m) => Parser Text m (Maybe Char)
peekChar :: Parser Text m (Maybe Char)
peekChar = do
Maybe Char
x <- StateT (Producer Text m x) m (Maybe Char)
forall (m :: * -> *). Monad m => Parser Text m (Maybe Char)
drawChar
(Char -> StateT (Producer Text m x) m ())
-> Maybe Char -> StateT (Producer Text m x) m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\Char
h -> Char -> Parser Text m ()
forall (m :: * -> *). Monad m => Char -> Parser Text m ()
unDrawChar Char
h) Maybe Char
x
Maybe Char -> StateT (Producer Text m x) m (Maybe Char)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Char
x
{-# INLINEABLE peekChar #-}
isEndOfChars :: (Monad m) => Parser Text m Bool
isEndOfChars :: Parser Text m Bool
isEndOfChars = do
Maybe Char
x <- StateT (Producer Text m x) m (Maybe Char)
forall (m :: * -> *). Monad m => Parser Text m (Maybe Char)
peekChar
Bool -> StateT (Producer Text m x) m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return
( case Maybe Char
x of
Maybe Char
Nothing -> Bool
True
Just Char
_ -> Bool
False
)
{-# INLINEABLE isEndOfChars #-}
splitAt ::
(Monad m, Integral n) =>
n ->
Lens'
(Producer Text m r)
(Producer Text m (Producer Text m r))
splitAt :: n
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
splitAt n
n0 Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k Producer Text m r
p0 = (Producer Text m (Producer Text m r) -> Producer Text m r)
-> f (Producer Text m (Producer Text m r)) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Text m (Producer Text m r) -> Producer Text m r
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k (n -> Producer Text m r -> Producer Text m (Producer Text m r)
forall a (m :: * -> *) b x' x.
(Monad m, Integral a) =>
a -> Producer Text m b -> Proxy x' x () Text m (Producer Text m b)
go n
n0 Producer Text m r
p0))
where
go :: a -> Producer Text m b -> Proxy x' x () Text m (Producer Text m b)
go a
0 Producer Text m b
p = Producer Text m b -> Proxy x' x () Text m (Producer Text m b)
forall (m :: * -> *) a. Monad m => a -> m a
return Producer Text m b
p
go a
n Producer Text m b
p = do
Either b (Text, Producer Text m b)
x <- m (Either b (Text, Producer Text m b))
-> Proxy x' x () Text m (Either b (Text, Producer Text m b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Producer Text m b -> m (Either b (Text, Producer Text m b))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m b
p)
case Either b (Text, Producer Text m b)
x of
Left b
r -> Producer Text m b -> Proxy x' x () Text m (Producer Text m b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Producer Text m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
r)
Right (Text
txt, Producer Text m b
p') -> do
let len :: a
len = Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Text -> Int
T.length Text
txt)
if a
len a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
n
then do
Text -> Proxy x' x () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt
a -> Producer Text m b -> Proxy x' x () Text m (Producer Text m b)
go (a
n a -> a -> a
forall a. Num a => a -> a -> a
- a
len) Producer Text m b
p'
else do
let (Text
prefix, Text
suffix) = Int -> Text -> (Text, Text)
T.splitAt (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n) Text
txt
Text -> Proxy x' x () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
prefix
Producer Text m b -> Proxy x' x () Text m (Producer Text m b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
suffix Proxy X () () Text m () -> Producer Text m b -> Producer Text m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m b
p')
{-# INLINEABLE splitAt #-}
span ::
(Monad m) =>
(Char -> Bool) ->
Lens'
(Producer Text m r)
(Producer Text m (Producer Text m r))
span :: (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span Char -> Bool
predicate Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k Producer Text m r
p0 = (Producer Text m (Producer Text m r) -> Producer Text m r)
-> f (Producer Text m (Producer Text m r)) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Text m (Producer Text m r) -> Producer Text m r
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k (Producer Text m r -> Producer Text m (Producer Text m r)
go Producer Text m r
p0))
where
go :: Producer Text m r -> Producer Text m (Producer Text m r)
go Producer Text m r
p = do
Either r (Text, Producer Text m r)
x <- m (Either r (Text, Producer Text m r))
-> Proxy X () () Text m (Either r (Text, Producer Text m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Producer Text m r -> m (Either r (Text, Producer Text m r))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m r
p)
case Either r (Text, Producer Text m r)
x of
Left r
r -> Producer Text m r -> Producer Text m (Producer Text m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> Producer Text m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r)
Right (Text
txt, Producer Text m r
p') -> do
let (Text
prefix, Text
suffix) = (Char -> Bool) -> Text -> (Text, Text)
T.span Char -> Bool
predicate Text
txt
if Text -> Bool
T.null Text
suffix
then do
Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt
Producer Text m r -> Producer Text m (Producer Text m r)
go Producer Text m r
p'
else do
Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
prefix
Producer Text m r -> Producer Text m (Producer Text m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
suffix Proxy X () () Text m () -> Producer Text m r -> Producer Text m r
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m r
p')
{-# INLINEABLE span #-}
break ::
(Monad m) =>
(Char -> Bool) ->
Lens'
(Producer Text m r)
(Producer Text m (Producer Text m r))
break :: (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
break Char -> Bool
predicate = (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
predicate)
{-# INLINEABLE break #-}
groupBy ::
(Monad m) =>
(Char -> Char -> Bool) ->
Lens'
(Producer Text m r)
(Producer Text m (Producer Text m r))
groupBy :: (Char -> Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
groupBy Char -> Char -> Bool
equals Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k Producer Text m r
p0 = (Producer Text m (Producer Text m r) -> Producer Text m r)
-> f (Producer Text m (Producer Text m r)) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Text m (Producer Text m r) -> Producer Text m r
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k (Producer Text m r -> Producer Text m (Producer Text m r)
go Producer Text m r
p0))
where
go :: Producer Text m r -> Producer Text m (Producer Text m r)
go Producer Text m r
p = do
Either r (Text, Producer Text m r)
x <- m (Either r (Text, Producer Text m r))
-> Proxy X () () Text m (Either r (Text, Producer Text m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Producer Text m r -> m (Either r (Text, Producer Text m r))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m r
p)
case Either r (Text, Producer Text m r)
x of
Left r
r -> Producer Text m r -> Producer Text m (Producer Text m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> Producer Text m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r)
Right (Text
txt, Producer Text m r
p') -> case Text -> Maybe (Char, Text)
T.uncons Text
txt of
Maybe (Char, Text)
Nothing -> Producer Text m r -> Producer Text m (Producer Text m r)
go Producer Text m r
p'
Just (Char
c, Text
_) -> (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt Proxy X () () Text m () -> Producer Text m r -> Producer Text m r
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m r
p') Producer Text m r
-> ((Producer Text m (Producer Text m r)
-> Constant
(Producer Text m (Producer Text m r))
(Producer Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Producer Text m (Producer Text m r)) (Producer Text m r))
-> Producer Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span (Char -> Char -> Bool
equals Char
c)
{-# INLINEABLE groupBy #-}
group ::
Monad m =>
Lens'
(Producer Text m r)
(Producer Text m (Producer Text m r))
group :: Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
group = (Char -> Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
groupBy Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINEABLE group #-}
word ::
(Monad m) =>
Lens'
(Producer Text m r)
(Producer Text m (Producer Text m r))
word :: Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
word Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k Producer Text m r
p0 = (Producer Text m (Producer Text m r) -> Producer Text m r)
-> f (Producer Text m (Producer Text m r)) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Text m (Producer Text m r) -> Producer Text m r
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer Text m (Producer Text m r)
-> f (Producer Text m (Producer Text m r))
k (Producer Text m r -> Producer Text m (Producer Text m r)
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> Proxy X () () Text m (Producer Text m r)
to Producer Text m r
p0))
where
to :: Producer Text m r -> Proxy X () () Text m (Producer Text m r)
to Producer Text m r
p = do
Producer Text m r
p' <- Producer Text m r
p Producer Text m r
-> ((Proxy X () () Text m (Producer Text m r)
-> Constant
(Proxy X () () Text m (Producer Text m r))
(Proxy X () () Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Proxy X () () Text m (Producer Text m r)) (Producer Text m r))
-> Proxy X () () Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens'
(Producer Text m r) (Proxy X () () Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span Char -> Bool
isSpace
Producer Text m r
p' Producer Text m r
-> ((Proxy X () () Text m (Producer Text m r)
-> Constant
(Proxy X () () Text m (Producer Text m r))
(Proxy X () () Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Proxy X () () Text m (Producer Text m r)) (Producer Text m r))
-> Proxy X () () Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens'
(Producer Text m r) (Proxy X () () Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
break Char -> Bool
isSpace
{-# INLINEABLE word #-}
line ::
(Monad m) =>
Lens'
(Producer Text m r)
(Producer Text m (Producer Text m r))
line :: Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
line = (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n')
{-# INLINEABLE line #-}
drop ::
(Monad m, Integral n) =>
n ->
Producer Text m r ->
Producer Text m r
drop :: n -> Producer Text m r -> Producer Text m r
drop n
n Producer Text m r
p =
Proxy X () () Text m (Producer Text m r) -> Producer Text m r
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (m (Producer Text m r) -> Proxy X () () Text m (Producer Text m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Producer Text m r) -> Proxy X () () Text m (Producer Text m r))
-> m (Producer Text m r)
-> Proxy X () () Text m (Producer Text m r)
forall a b. (a -> b) -> a -> b
$ Effect m (Producer Text m r) -> m (Producer Text m r)
forall (m :: * -> *) r. Monad m => Effect m r -> m r
runEffect (Proxy X () () Text m (Producer Text m r)
-> (Text -> Proxy X () () X m ()) -> Effect m (Producer Text m r)
forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for (Producer Text m r
p Producer Text m r
-> ((Proxy X () () Text m (Producer Text m r)
-> Constant
(Proxy X () () Text m (Producer Text m r))
(Proxy X () () Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Proxy X () () Text m (Producer Text m r)) (Producer Text m r))
-> Proxy X () () Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. n
-> Lens'
(Producer Text m r) (Proxy X () () Text m (Producer Text m r))
forall (m :: * -> *) n r.
(Monad m, Integral n) =>
n
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
splitAt n
n) Text -> Proxy X () () X m ()
forall (m :: * -> *) a. Monad m => a -> m ()
discard))
{-# INLINEABLE drop #-}
dropWhile ::
(Monad m) =>
(Char -> Bool) ->
Producer Text m r ->
Producer Text m r
dropWhile :: (Char -> Bool) -> Producer Text m r -> Producer Text m r
dropWhile Char -> Bool
predicate Producer Text m r
p =
Proxy X () () Text m (Producer Text m r) -> Producer Text m r
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (m (Producer Text m r) -> Proxy X () () Text m (Producer Text m r)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Producer Text m r) -> Proxy X () () Text m (Producer Text m r))
-> m (Producer Text m r)
-> Proxy X () () Text m (Producer Text m r)
forall a b. (a -> b) -> a -> b
$ Effect m (Producer Text m r) -> m (Producer Text m r)
forall (m :: * -> *) r. Monad m => Effect m r -> m r
runEffect (Proxy X () () Text m (Producer Text m r)
-> (Text -> Proxy X () () X m ()) -> Effect m (Producer Text m r)
forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for (Producer Text m r
p Producer Text m r
-> ((Proxy X () () Text m (Producer Text m r)
-> Constant
(Proxy X () () Text m (Producer Text m r))
(Proxy X () () Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Proxy X () () Text m (Producer Text m r)) (Producer Text m r))
-> Proxy X () () Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens'
(Producer Text m r) (Proxy X () () Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span Char -> Bool
predicate) Text -> Proxy X () () X m ()
forall (m :: * -> *) a. Monad m => a -> m ()
discard))
{-# INLINEABLE dropWhile #-}
intersperse ::
(Monad m) => Char -> Producer Text m r -> Producer Text m r
intersperse :: Char -> Producer Text m r -> Producer Text m r
intersperse Char
c = Producer Text m r -> Producer Text m r
go0
where
go0 :: Producer Text m r -> Producer Text m r
go0 Producer Text m r
p = do
Either r (Text, Producer Text m r)
x <- m (Either r (Text, Producer Text m r))
-> Proxy X () () Text m (Either r (Text, Producer Text m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Producer Text m r -> m (Either r (Text, Producer Text m r))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m r
p)
case Either r (Text, Producer Text m r)
x of
Left r
r -> r -> Producer Text m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Right (Text
txt, Producer Text m r
p') -> do
Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Char -> Text -> Text
T.intersperse Char
c Text
txt)
Producer Text m r -> Producer Text m r
go1 Producer Text m r
p'
go1 :: Producer Text m r -> Producer Text m r
go1 Producer Text m r
p = do
Either r (Text, Producer Text m r)
x <- m (Either r (Text, Producer Text m r))
-> Proxy X () () Text m (Either r (Text, Producer Text m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Producer Text m r -> m (Either r (Text, Producer Text m r))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m r
p)
case Either r (Text, Producer Text m r)
x of
Left r
r -> r -> Producer Text m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Right (Text
txt, Producer Text m r
p') -> do
Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Char -> Text
T.singleton Char
c)
Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Char -> Text -> Text
T.intersperse Char
c Text
txt)
Producer Text m r -> Producer Text m r
go1 Producer Text m r
p'
{-# INLINEABLE intersperse #-}
pack :: Monad m => Lens' (Producer Char m r) (Producer Text m r)
pack :: Lens' (Producer Char m r) (Producer Text m r)
pack Producer Text m r -> f (Producer Text m r)
k Producer Char m r
p = (Producer Text m r -> Producer Char m r)
-> f (Producer Text m r) -> f (Producer Char m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Text m r -> Producer Char m r
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> Producer Char m r
_unpack (Producer Text m r -> f (Producer Text m r)
k (Producer Char m r -> Producer Text m r
forall (m :: * -> *) r.
Monad m =>
Producer Char m r -> Producer Text m r
_pack Producer Char m r
p))
{-# INLINEABLE pack #-}
unpack :: Monad m => Lens' (Producer Text m r) (Producer Char m r)
unpack :: Lens' (Producer Text m r) (Producer Char m r)
unpack Producer Char m r -> f (Producer Char m r)
k Producer Text m r
p = (Producer Char m r -> Producer Text m r)
-> f (Producer Char m r) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Char m r -> Producer Text m r
forall (m :: * -> *) r.
Monad m =>
Producer Char m r -> Producer Text m r
_pack (Producer Char m r -> f (Producer Char m r)
k (Producer Text m r -> Producer Char m r
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> Producer Char m r
_unpack Producer Text m r
p))
{-# INLINEABLE unpack #-}
_pack :: Monad m => Producer Char m r -> Producer Text m r
_pack :: Producer Char m r -> Producer Text m r
_pack Producer Char m r
p = (([Char] -> [Char]) -> Char -> [Char] -> [Char])
-> ([Char] -> [Char])
-> (([Char] -> [Char]) -> Text)
-> FreeT (Producer Char m) m r
-> Producer Text m r
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x)
-> x -> (x -> b) -> FreeT (Producer a m) m r -> Producer b m r
folds ([Char] -> [Char]) -> Char -> [Char] -> [Char]
forall a c. ([a] -> c) -> a -> [a] -> c
step [Char] -> [Char]
forall a. a -> a
id ([Char] -> [Char]) -> Text
forall a. ([a] -> [Char]) -> Text
done (Producer Char m r
p Producer Char m r
-> ((FreeT (Producer Char m) m r
-> Constant
(FreeT (Producer Char m) m r) (FreeT (Producer Char m) m r))
-> Producer Char m r
-> Constant (FreeT (Producer Char m) m r) (Producer Char m r))
-> FreeT (Producer Char m) m r
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. Int
-> Lens
(Producer Char m r)
(Producer Char m r)
(FreeT (Producer Char m) m r)
(FreeT (Producer Char m) m r)
forall (m :: * -> *) a' x a.
Monad m =>
Int
-> Lens
(Producer a' m x)
(Producer a m x)
(FreeT (Producer a' m) m x)
(FreeT (Producer a m) m x)
PG.chunksOf Int
defaultChunkSize)
where
step :: ([a] -> c) -> a -> [a] -> c
step [a] -> c
diffAs a
w8 = [a] -> c
diffAs ([a] -> c) -> ([a] -> [a]) -> [a] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a
w8 a -> [a] -> [a]
forall a. a -> [a] -> [a]
:)
done :: ([a] -> [Char]) -> Text
done [a] -> [Char]
diffAs = [Char] -> Text
T.pack ([a] -> [Char]
diffAs [])
{-# INLINEABLE _pack #-}
_unpack :: Monad m => Producer Text m r -> Producer Char m r
_unpack :: Producer Text m r -> Producer Char m r
_unpack Producer Text m r
p = Producer Text m r
-> (Text -> Proxy X () () Char m ()) -> Producer Char m r
forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for Producer Text m r
p ([Char] -> Proxy X () () Char m ()
forall (m :: * -> *) (f :: * -> *) a x' x.
(Functor m, Foldable f) =>
f a -> Proxy x' x () a m ()
each ([Char] -> Proxy X () () Char m ())
-> (Text -> [Char]) -> Text -> Proxy X () () Char m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Char]
T.unpack)
{-# INLINEABLE _unpack #-}
defaultChunkSize :: Int
defaultChunkSize :: Int
defaultChunkSize = Int
16384 Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
1)
chunksOf ::
(Monad m, Integral n) =>
n ->
Lens'
(Producer Text m r)
(FreeT (Producer Text m) m r)
chunksOf :: n -> Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
chunksOf n
n FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k Producer Text m r
p0 = (FreeT (Producer Text m) m r -> Producer Text m r)
-> f (FreeT (Producer Text m) m r) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) a x.
Monad m =>
FreeT (Producer a m) m x -> Producer a m x
concats (FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k (m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go Producer Text m r
p0)))
where
go :: Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go Producer Text m r
p = do
Either r (Text, Producer Text m r)
x <- Producer Text m r -> m (Either r (Text, Producer Text m r))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m r
p
FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)))
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall a b. (a -> b) -> a -> b
$ case Either r (Text, Producer Text m r)
x of
Left r
r -> r -> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. a -> FreeF f a b
Pure r
r
Right (Text
txt, Producer Text m r
p') -> Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. f b -> FreeF f a b
Free (Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall a b. (a -> b) -> a -> b
$ do
Producer Text m r
p'' <- (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt Proxy X () () Text m () -> Producer Text m r -> Producer Text m r
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m r
p') Producer Text m r
-> ((Producer Text m (Producer Text m r)
-> Constant
(Producer Text m (Producer Text m r))
(Producer Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Producer Text m (Producer Text m r)) (Producer Text m r))
-> Producer Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. n
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) n r.
(Monad m, Integral n) =>
n
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
splitAt n
n
FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
forall a b. (a -> b) -> a -> b
$ m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go Producer Text m r
p'')
{-# INLINEABLE chunksOf #-}
splitsWith ::
(Monad m) =>
(Char -> Bool) ->
Producer Text m r ->
FreeT (Producer Text m) m r
splitsWith :: (Char -> Bool) -> Producer Text m r -> FreeT (Producer Text m) m r
splitsWith Char -> Bool
predicate Producer Text m r
p0 = m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go0 Producer Text m r
p0)
where
go0 :: Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go0 Producer Text m r
p = do
Either r (Text, Producer Text m r)
x <- Producer Text m r -> m (Either r (Text, Producer Text m r))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m r
p
case Either r (Text, Producer Text m r)
x of
Left r
r -> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. a -> FreeF f a b
Pure r
r)
Right (Text
txt, Producer Text m r
p') ->
if Text -> Bool
T.null Text
txt
then Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go0 Producer Text m r
p'
else FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)))
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall a b. (a -> b) -> a -> b
$
Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. f b -> FreeF f a b
Free (Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall a b. (a -> b) -> a -> b
$ do
Producer Text m r
p'' <- (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt Proxy X () () Text m () -> Producer Text m r -> Producer Text m r
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m r
p') Producer Text m r
-> ((Producer Text m (Producer Text m r)
-> Constant
(Producer Text m (Producer Text m r))
(Producer Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Producer Text m (Producer Text m r)) (Producer Text m r))
-> Producer Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
predicate)
FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
forall a b. (a -> b) -> a -> b
$ m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go1 Producer Text m r
p'')
go1 :: Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go1 Producer Text m r
p = do
Either r (Char, Producer Text m r)
x <- Producer Text m r -> m (Either r (Char, Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> m (Either r (Char, Producer Text m r))
nextChar Producer Text m r
p
FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)))
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall a b. (a -> b) -> a -> b
$ case Either r (Char, Producer Text m r)
x of
Left r
r -> r -> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. a -> FreeF f a b
Pure r
r
Right (Char
_, Producer Text m r
p') -> Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. f b -> FreeF f a b
Free (Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall a b. (a -> b) -> a -> b
$ do
Producer Text m r
p'' <- Producer Text m r
p' Producer Text m r
-> ((Producer Text m (Producer Text m r)
-> Constant
(Producer Text m (Producer Text m r))
(Producer Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Producer Text m (Producer Text m r)) (Producer Text m r))
-> Producer Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
predicate)
FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
forall a b. (a -> b) -> a -> b
$ m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
go1 Producer Text m r
p'')
{-# INLINEABLE splitsWith #-}
splits ::
(Monad m) =>
Char ->
Lens'
(Producer Text m r)
(FreeT (Producer Text m) m r)
splits :: Char -> Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
splits Char
c FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k Producer Text m r
p =
(FreeT (Producer Text m) m r -> Producer Text m r)
-> f (FreeT (Producer Text m) m r) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Producer Text m ()
-> FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) a x.
Monad m =>
Producer a m () -> FreeT (Producer a m) m x -> Producer a m x
intercalates (Text -> Producer Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Char -> Text
T.singleton Char
c))) (FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k ((Char -> Bool) -> Producer Text m r -> FreeT (Producer Text m) m r
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool) -> Producer Text m r -> FreeT (Producer Text m) m r
splitsWith (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==) Producer Text m r
p))
{-# INLINEABLE splits #-}
groupsBy ::
Monad m =>
(Char -> Char -> Bool) ->
Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groupsBy :: (Char -> Char -> Bool)
-> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groupsBy Char -> Char -> Bool
equals FreeT (Producer Text m) m x -> f (FreeT (Producer Text m) m x)
k Producer Text m x
p0 = (FreeT (Producer Text m) m x -> Producer Text m x)
-> f (FreeT (Producer Text m) m x) -> f (Producer Text m x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FreeT (Producer Text m) m x -> Producer Text m x
forall (m :: * -> *) a x.
Monad m =>
FreeT (Producer a m) m x -> Producer a m x
concats (FreeT (Producer Text m) m x -> f (FreeT (Producer Text m) m x)
k (m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
-> FreeT (Producer Text m) m x
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m x
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
go Producer Text m x
p0)))
where
go :: Producer Text m x
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
go Producer Text m x
p = do
Either x (Text, Producer Text m x)
x <- Producer Text m x -> m (Either x (Text, Producer Text m x))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m x
p
case Either x (Text, Producer Text m x)
x of
Left x
r -> FreeF (Producer Text m) x (FreeT (Producer Text m) m x)
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
forall (m :: * -> *) a. Monad m => a -> m a
return (x -> FreeF (Producer Text m) x (FreeT (Producer Text m) m x)
forall (f :: * -> *) a b. a -> FreeF f a b
Pure x
r)
Right (Text
bs, Producer Text m x
p') -> case Text -> Maybe (Char, Text)
T.uncons Text
bs of
Maybe (Char, Text)
Nothing -> Producer Text m x
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
go Producer Text m x
p'
Just (Char
c, Text
_) -> do
FreeF (Producer Text m) x (FreeT (Producer Text m) m x)
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeF (Producer Text m) x (FreeT (Producer Text m) m x)
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x)))
-> FreeF (Producer Text m) x (FreeT (Producer Text m) m x)
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
forall a b. (a -> b) -> a -> b
$
Proxy X () () Text m (FreeT (Producer Text m) m x)
-> FreeF (Producer Text m) x (FreeT (Producer Text m) m x)
forall (f :: * -> *) a b. f b -> FreeF f a b
Free (Proxy X () () Text m (FreeT (Producer Text m) m x)
-> FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
-> Proxy X () () Text m (FreeT (Producer Text m) m x)
-> FreeF (Producer Text m) x (FreeT (Producer Text m) m x)
forall a b. (a -> b) -> a -> b
$ do
Producer Text m x
p'' <- (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
bs Proxy X () () Text m () -> Producer Text m x -> Producer Text m x
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m x
p') Producer Text m x
-> ((Producer Text m (Producer Text m x)
-> Constant
(Producer Text m (Producer Text m x))
(Producer Text m (Producer Text m x)))
-> Producer Text m x
-> Constant
(Producer Text m (Producer Text m x)) (Producer Text m x))
-> Producer Text m (Producer Text m x)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens' (Producer Text m x) (Producer Text m (Producer Text m x))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
span (Char -> Char -> Bool
equals Char
c)
FreeT (Producer Text m) m x
-> Proxy X () () Text m (FreeT (Producer Text m) m x)
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeT (Producer Text m) m x
-> Proxy X () () Text m (FreeT (Producer Text m) m x))
-> FreeT (Producer Text m) m x
-> Proxy X () () Text m (FreeT (Producer Text m) m x)
forall a b. (a -> b) -> a -> b
$ m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
-> FreeT (Producer Text m) m x
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m x
-> m (FreeF (Producer Text m) x (FreeT (Producer Text m) m x))
go Producer Text m x
p'')
{-# INLINEABLE groupsBy #-}
groups ::
Monad m =>
Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groups :: Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groups = (Char -> Char -> Bool)
-> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
forall (m :: * -> *) x.
Monad m =>
(Char -> Char -> Bool)
-> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groupsBy Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINEABLE groups #-}
lines ::
(Monad m) => Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
lines :: Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
lines FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k Producer Text m r
p = (FreeT (Producer Text m) m r -> Producer Text m r)
-> f (FreeT (Producer Text m) m r) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) r.
Monad m =>
FreeT (Producer Text m) m r -> Producer Text m r
_unlines (FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k (Producer Text m r -> FreeT (Producer Text m) m r
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> FreeT (Producer Text m) m r
_lines Producer Text m r
p))
{-# INLINEABLE lines #-}
unlines ::
Monad m =>
Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
unlines :: Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
unlines Producer Text m r -> f (Producer Text m r)
k FreeT (Producer Text m) m r
p = (Producer Text m r -> FreeT (Producer Text m) m r)
-> f (Producer Text m r) -> f (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Text m r -> FreeT (Producer Text m) m r
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> FreeT (Producer Text m) m r
_lines (Producer Text m r -> f (Producer Text m r)
k (FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) r.
Monad m =>
FreeT (Producer Text m) m r -> Producer Text m r
_unlines FreeT (Producer Text m) m r
p))
{-# INLINEABLE unlines #-}
_lines ::
Monad m =>
Producer Text m r ->
FreeT (Producer Text m) m r
_lines :: Producer Text m r -> FreeT (Producer Text m) m r
_lines Producer Text m r
p0 = m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (Producer Text m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (m :: * -> *) a.
Monad m =>
Producer Text m a
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
go0 Producer Text m r
p0)
where
go0 :: Producer Text m a
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
go0 Producer Text m a
p = do
Either a (Text, Producer Text m a)
x <- Producer Text m a -> m (Either a (Text, Producer Text m a))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer Text m a
p
case Either a (Text, Producer Text m a)
x of
Left a
r -> FreeF (Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
forall (m :: * -> *) a. Monad m => a -> m a
return (a
-> FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
forall (f :: * -> *) a b. a -> FreeF f a b
Pure a
r)
Right (Text
txt, Producer Text m a
p') ->
if Text -> Bool
T.null Text
txt
then Producer Text m a
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
go0 Producer Text m a
p'
else FreeF (Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeF (Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)))
-> FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
forall a b. (a -> b) -> a -> b
$ Proxy X () () Text m (FreeT (Proxy X () () Text m) m a)
-> FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
forall (f :: * -> *) a b. f b -> FreeF f a b
Free (Proxy X () () Text m (FreeT (Proxy X () () Text m) m a)
-> FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
-> Proxy X () () Text m (FreeT (Proxy X () () Text m) m a)
-> FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
forall a b. (a -> b) -> a -> b
$ Producer Text m a
-> Proxy X () () Text m (FreeT (Proxy X () () Text m) m a)
go1 (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
txt Proxy X () () Text m () -> Producer Text m a -> Producer Text m a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m a
p')
go1 :: Producer Text m a
-> Proxy X () () Text m (FreeT (Proxy X () () Text m) m a)
go1 Producer Text m a
p = do
Producer Text m a
p' <- Producer Text m a
p Producer Text m a
-> ((Producer Text m (Producer Text m a)
-> Constant
(Producer Text m (Producer Text m a))
(Producer Text m (Producer Text m a)))
-> Producer Text m a
-> Constant
(Producer Text m (Producer Text m a)) (Producer Text m a))
-> Producer Text m (Producer Text m a)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens' (Producer Text m a) (Producer Text m (Producer Text m a))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
break (Char
'\n' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==)
FreeT (Proxy X () () Text m) m a
-> Proxy X () () Text m (FreeT (Proxy X () () Text m) m a)
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeT (Proxy X () () Text m) m a
-> Proxy X () () Text m (FreeT (Proxy X () () Text m) m a))
-> FreeT (Proxy X () () Text m) m a
-> Proxy X () () Text m (FreeT (Proxy X () () Text m) m a)
forall a b. (a -> b) -> a -> b
$
m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
-> FreeT (Proxy X () () Text m) m a
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
-> FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
-> FreeT (Proxy X () () Text m) m a
forall a b. (a -> b) -> a -> b
$ do
Either a (Char, Producer Text m a)
x <- Producer Text m a -> m (Either a (Char, Producer Text m a))
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> m (Either r (Char, Producer Text m r))
nextChar Producer Text m a
p'
case Either a (Char, Producer Text m a)
x of
Left a
r -> FreeF (Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeF (Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)))
-> FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
forall a b. (a -> b) -> a -> b
$ a
-> FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a)
forall (f :: * -> *) a b. a -> FreeF f a b
Pure a
r
Right (Char
_, Producer Text m a
p'') -> Producer Text m a
-> m (FreeF
(Proxy X () () Text m) a (FreeT (Proxy X () () Text m) m a))
go0 Producer Text m a
p''
{-# INLINEABLE _lines #-}
_unlines ::
Monad m =>
FreeT (Producer Text m) m r ->
Producer Text m r
_unlines :: FreeT (Producer Text m) m r -> Producer Text m r
_unlines = FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) a x.
Monad m =>
FreeT (Producer a m) m x -> Producer a m x
concats (FreeT (Producer Text m) m r -> Producer Text m r)
-> (FreeT (Producer Text m) m r -> FreeT (Producer Text m) m r)
-> FreeT (Producer Text m) m r
-> Producer Text m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall r. Producer Text m r -> Producer Text m r)
-> FreeT (Producer Text m) m r -> FreeT (Producer Text m) m r
forall (m :: * -> *) (g :: * -> *) (f :: * -> *) x.
(Monad m, Functor g) =>
(forall r. f r -> g r) -> FreeT f m x -> FreeT g m x
maps (Producer Text m r -> Producer Text m () -> Producer Text m r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> Producer Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Char -> Text
T.singleton Char
'\n'))
{-# INLINEABLE _unlines #-}
words ::
(Monad m) => Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
words :: Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
words FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k Producer Text m r
p = (FreeT (Producer Text m) m r -> Producer Text m r)
-> f (FreeT (Producer Text m) m r) -> f (Producer Text m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) r.
Monad m =>
FreeT (Producer Text m) m r -> Producer Text m r
_unwords (FreeT (Producer Text m) m r -> f (FreeT (Producer Text m) m r)
k (Producer Text m r -> FreeT (Producer Text m) m r
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> FreeT (Producer Text m) m r
_words Producer Text m r
p))
{-# INLINEABLE words #-}
unwords ::
Monad m =>
Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
unwords :: Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
unwords Producer Text m r -> f (Producer Text m r)
k FreeT (Producer Text m) m r
p = (Producer Text m r -> FreeT (Producer Text m) m r)
-> f (Producer Text m r) -> f (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Producer Text m r -> FreeT (Producer Text m) m r
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> FreeT (Producer Text m) m r
_words (Producer Text m r -> f (Producer Text m r)
k (FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) r.
Monad m =>
FreeT (Producer Text m) m r -> Producer Text m r
_unwords FreeT (Producer Text m) m r
p))
{-# INLINEABLE unwords #-}
_words :: (Monad m) => Producer Text m r -> FreeT (Producer Text m) m r
_words :: Producer Text m r -> FreeT (Producer Text m) m r
_words Producer Text m r
p = m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT (m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> FreeT (Producer Text m) m r
forall a b. (a -> b) -> a -> b
$ do
Either r (Text, Producer Text m r)
x <- Producer Text m r -> m (Either r (Text, Producer Text m r))
forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next ((Char -> Bool) -> Producer Text m r -> Producer Text m r
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool) -> Producer Text m r -> Producer Text m r
dropWhile Char -> Bool
isSpace Producer Text m r
p)
FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (m :: * -> *) a. Monad m => a -> m a
return (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r)))
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall a b. (a -> b) -> a -> b
$ case Either r (Text, Producer Text m r)
x of
Left r
r -> r -> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. a -> FreeF f a b
Pure r
r
Right (Text
bs, Producer Text m r
p') -> Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall (f :: * -> *) a b. f b -> FreeF f a b
Free (Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
-> FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
forall a b. (a -> b) -> a -> b
$ do
Producer Text m r
p'' <- (Text -> Proxy X () () Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield Text
bs Proxy X () () Text m () -> Producer Text m r -> Producer Text m r
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer Text m r
p') Producer Text m r
-> ((Producer Text m (Producer Text m r)
-> Constant
(Producer Text m (Producer Text m r))
(Producer Text m (Producer Text m r)))
-> Producer Text m r
-> Constant
(Producer Text m (Producer Text m r)) (Producer Text m r))
-> Producer Text m (Producer Text m r)
forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
forall (m :: * -> *) r.
Monad m =>
(Char -> Bool)
-> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
break Char -> Bool
isSpace
FreeT (Producer Text m) m r
-> Proxy X () () Text m (FreeT (Producer Text m) m r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Producer Text m r -> FreeT (Producer Text m) m r
forall (m :: * -> *) r.
Monad m =>
Producer Text m r -> FreeT (Producer Text m) m r
_words Producer Text m r
p'')
{-# INLINEABLE _words #-}
_unwords :: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
_unwords :: FreeT (Producer Text m) m r -> Producer Text m r
_unwords = Producer Text m ()
-> FreeT (Producer Text m) m r -> Producer Text m r
forall (m :: * -> *) a x.
Monad m =>
Producer a m () -> FreeT (Producer a m) m x -> Producer a m x
intercalates (Text -> Producer Text m ()
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Text -> Producer Text m ()) -> Text -> Producer Text m ()
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
' ')
{-# INLINEABLE _unwords #-}
intercalate ::
(Monad m) =>
Producer Text m () ->
FreeT (Producer Text m) m r ->
Producer Text m r
intercalate :: Producer Text m ()
-> FreeT (Producer Text m) m r -> Producer Text m r
intercalate Producer Text m ()
p0 = FreeT (Producer Text m) m r -> Producer Text m r
go0
where
go0 :: FreeT (Producer Text m) m r -> Producer Text m r
go0 FreeT (Producer Text m) m r
f = do
FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
x <- m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> Proxy
X
()
()
Text
m
(FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (FreeT (Producer Text m) m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (f :: * -> *) (m :: * -> *) a.
FreeT f m a -> m (FreeF f a (FreeT f m a))
runFreeT FreeT (Producer Text m) m r
f)
case FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
x of
Pure r
r -> r -> Producer Text m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Free Proxy X () () Text m (FreeT (Producer Text m) m r)
p -> do
FreeT (Producer Text m) m r
f' <- Proxy X () () Text m (FreeT (Producer Text m) m r)
p
FreeT (Producer Text m) m r -> Producer Text m r
go1 FreeT (Producer Text m) m r
f'
go1 :: FreeT (Producer Text m) m r -> Producer Text m r
go1 FreeT (Producer Text m) m r
f = do
FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
x <- m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
-> Proxy
X
()
()
Text
m
(FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (FreeT (Producer Text m) m r
-> m (FreeF (Producer Text m) r (FreeT (Producer Text m) m r))
forall (f :: * -> *) (m :: * -> *) a.
FreeT f m a -> m (FreeF f a (FreeT f m a))
runFreeT FreeT (Producer Text m) m r
f)
case FreeF (Producer Text m) r (FreeT (Producer Text m) m r)
x of
Pure r
r -> r -> Producer Text m r
forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Free Proxy X () () Text m (FreeT (Producer Text m) m r)
p -> do
Producer Text m ()
p0
FreeT (Producer Text m) m r
f' <- Proxy X () () Text m (FreeT (Producer Text m) m r)
p
FreeT (Producer Text m) m r -> Producer Text m r
go1 FreeT (Producer Text m) m r
f'
{-# INLINEABLE intercalate #-}
type Lens' a b = forall f. Functor f => (b -> f b) -> (a -> f a)