-}
+type Lens s t a b = forall f . Functor f => (a -> f b) -> (s -> f t)
+
+
+(^.) :: a -> ((b -> Constant b b) -> (a -> Constant b a)) -> b
+a ^. lens = getConstant (lens Constant a)
+
-- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's
fromLazy :: (Monad m) => TL.Text -> Producer' Text m ()
fromLazy = TL.foldrChunks (\e a -> yield e >> a) (return ())
{-# INLINE fromLazy #-}
-(^.) :: a -> ((b -> Constant b b) -> (a -> Constant b a)) -> b
-a ^. lens = getConstant (lens Constant a)
-
-- | Apply a transformation to each 'Char' in the stream
map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
splitAt
:: (Monad m, Integral n)
=> n
- -> Lens'_ (Producer Text m r)
- (Producer Text m (Producer Text m r))
+ -> Lens (Producer Text m x)
+ (Producer Text m y)
+ (Producer Text m (Producer Text m x))
+ (Producer Text m (Producer Text m y))
splitAt n0 k p0 = fmap join (k (go n0 p0))
where
go 0 p = return p
span
:: (Monad m)
=> (Char -> Bool)
- -> Lens'_ (Producer Text m r)
- (Producer Text m (Producer Text m r))
+ -> Lens (Producer Text m x)
+ (Producer Text m y)
+ (Producer Text m (Producer Text m x))
+ (Producer Text m (Producer Text m y))
span predicate k p0 = fmap join (k (go p0))
where
go p = do
break
:: (Monad m)
=> (Char -> Bool)
- -> Lens'_ (Producer Text m r)
- (Producer Text m (Producer Text m r))
+ -> Lens (Producer Text m x)
+ (Producer Text m y)
+ (Producer Text m (Producer Text m x))
+ (Producer Text m (Producer Text m y))
break predicate = span (not . predicate)
{-# INLINABLE break #-}
groupBy
:: (Monad m)
=> (Char -> Char -> Bool)
- -> Lens'_ (Producer Text m r)
- (Producer Text m (Producer Text m r))
+ -> Lens (Producer Text m x)
+ (Producer Text m y)
+ (Producer Text m (Producer Text m x))
+ (Producer Text m (Producer Text m y))
groupBy equals k p0 = fmap join (k ((go p0))) where
go p = do
x <- lift (next p)
Unlike 'words', this does not drop leading whitespace
-}
word :: (Monad m)
- => Lens'_ (Producer Text m r)
- (Producer Text m (Producer Text m r))
+ => Lens (Producer Text m x)
+ (Producer Text m y)
+ (Producer Text m (Producer Text m x))
+ (Producer Text m (Producer Text m y))
word k p0 = fmap join (k (to p0))
where
to p = do
line :: (Monad m)
- => Lens'_ (Producer Text m r)
- (Producer Text m (Producer Text m r))
+ => Lens (Producer Text m x)
+ (Producer Text m y)
+ (Producer Text m (Producer Text m x))
+ (Producer Text m (Producer Text m y))
line = break (== '\n')
{-# INLINABLE line #-}
-- | Split a text stream into 'FreeT'-delimited text streams of fixed size
chunksOf
:: (Monad m, Integral n)
- => n -> Lens'_ (Producer Text m r)
- (FreeT (Producer Text m) m r)
+ => n -> Lens (Producer Text m x)
+ (Producer Text m y)
+ (FreeT (Producer Text m) m x)
+ (FreeT (Producer Text m) m y)
chunksOf n k p0 = fmap concats (k (FreeT (go p0)))
where
go p = do
-- | Split a text stream using the given 'Char' as the delimiter
splits :: (Monad m)
- => Char
- -> Lens'_ (Producer Text m r)
- (FreeT (Producer Text m) m r)
+ => Char -> Lens (Producer Text m x)
+ (Producer Text m y)
+ (FreeT (Producer Text m) m x)
+ (FreeT (Producer Text m) m y)
splits c k p =
fmap (PG.intercalates (yield (T.singleton c))) (k (splitsWith (c ==) p))
{-# INLINABLE splits #-}
groupsBy
:: Monad m
=> (Char -> Char -> Bool)
- -> Lens'_ (Producer Text m x) (FreeT (Producer Text m) m x)
+ -> Lens (Producer Text m x)
+ (Producer Text m y)
+ (FreeT (Producer Text m) m x)
+ (FreeT (Producer Text m) m y)
groupsBy equals k p0 = fmap concats (k (FreeT (go p0))) where
go p = do x <- next p
case x of Left r -> return (Pure r)
-- | Like 'groupsBy', where the equality predicate is ('==')
groups
:: Monad m
- => Lens'_ (Producer Text m x) (FreeT (Producer Text m) m x)
+ => Lens (Producer Text m x)
+ (Producer Text m y)
+ (FreeT (Producer Text m) m x)
+ (FreeT (Producer Text m) m y)
groups = groupsBy (==)
{-# INLINABLE groups #-}
{-| Split a text stream into 'FreeT'-delimited lines
-}
lines
- :: (Monad m) => Iso'_ (Producer Text m r) (FreeT (Producer Text m) m r)
-lines = Data.Profunctor.dimap _lines (fmap _unlines)
- where
- _lines p0 = FreeT (go0 p0)
+ :: (Monad m)
+ => Lens (Producer Text m x)
+ (Producer Text m y)
+ (FreeT (Producer Text m) m x)
+ (FreeT (Producer Text m) m y)
+lines k p = fmap _unlines (k (_lines p))
+{-# INLINABLE lines #-}
+
+_lines
+ :: Monad m
+ => Producer Text m x -> FreeT (Producer Text m) m x
+_lines p0 = FreeT (go0 p0)
where
go0 p = do
x <- next p
case x of
Left r -> return $ Pure r
Right (_, p'') -> go0 p''
- -- _unlines
- -- :: Monad m
- -- => FreeT (Producer Text m) m x -> Producer Text m x
- _unlines = concats . PG.maps (<* yield (T.singleton '\n'))
-
+{-# INLINABLE _lines #-}
+
+_unlines
+ :: Monad m
+ => FreeT (Producer Text m) m x -> Producer Text m x
+_unlines = concats . PG.maps (<* yield (T.singleton '\n'))
+{-# INLINABLE _unlines #-}
+
-{-# INLINABLE lines #-}
-- | Split a text stream into 'FreeT'-delimited words
{-| Join 'FreeT'-delimited lines into a text stream
-}
unlines
- :: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
-unlines = go
- where
- go f = do
- x <- lift (runFreeT f)
- case x of
- Pure r -> return r
- Free p -> do
- f' <- p
- yield $ T.singleton '\n'
- go f'
+ :: (Monad m)
+ => Lens (FreeT (Producer Text m) m x)
+ (FreeT (Producer Text m) m y)
+ (Producer Text m x)
+ (Producer Text m y)
+
+unlines k p = fmap _lines (k (_unlines p))
{-# INLINABLE unlines #-}
{-| Join 'FreeT'-delimited words into a text stream