]> git.immae.eu Git - github/fretlink/text-pipes.git/blame - Pipes/Text.hs
more documentation restructuring
[github/fretlink/text-pipes.git] / Pipes / Text.hs
CommitLineData
9667f797
GG
1{-# LANGUAGE RankNTypes, TypeFamilies, BangPatterns, Trustworthy #-}
2
74377aa0 3{-| This package provides @pipes@ utilities for \'text streams\', which are
0ac0c414 4 streams of 'Text' chunks. The individual chunks are uniformly @strict@, and you
5 will generally want @Data.Text@ in scope. But the type @Producer Text m r@ is
74377aa0 6 in some ways the pipes equivalent of the lazy @Text@ type.
0ac0c414 7
8 This module provides many functions equivalent in one way or another to
9 the 'pure' functions in
10 <https://hackage.haskell.org/package/text-1.1.0.0/docs/Data-Text-Lazy.html Data.Text.Lazy>.
74377aa0 11 They transform, divide, group and fold text streams. Though @Producer Text m r@
12 is \'effectful\' Text, functions
0ac0c414 13 in this module are \'pure\' in the sense that they are uniformly monad-independent.
74377aa0 14 Simple IO operations are defined in @Pipes.Text.IO@ -- as lazy IO @Text@
15 operations are in @Data.Text.Lazy.IO@. Interoperation with @ByteString@
16 is provided in @Pipes.Text.Encoding@, which parallels @Data.Text.Lazy.Encoding@.
17
18 The Text type exported by @Data.Text.Lazy@ is basically '[Text]'. The implementation
19 is arranged so that the individual strict 'Text' chunks are kept to a reasonable size;
20 the user is not aware of the divisions between the connected 'Text' chunks.
21 So also here: the functions in this module are designed to operate on streams that
0ac0c414 22 are insensitive to text boundaries. This means that they may freely split
74377aa0 23 text into smaller texts and /discard empty texts/. However, the objective is
24 that they should /never concatenate texts/ in order to provide strict upper
25 bounds on memory usage.
26
0ac0c414 27 For example, to stream only the first three lines of 'stdin' to 'stdout' you
31f41a5d 28 might write:
91727d11 29
30> import Pipes
31f41a5d 31> import qualified Pipes.Text as Text
74377aa0 32> import qualified Pipes.Text.IO as Text
33> import Pipes.Group
34> import Lens.Family
35>
31f41a5d 36> main = runEffect $ takeLines 3 Text.stdin >-> Text.stdout
74377aa0 37> where
38> takeLines n = Text.unlines . takes' n . view Text.lines
39> -- or equivalently:
40> -- takeLines n = over Text.lines (takes' n)
91727d11 41
31f41a5d 42 The above program will never bring more than one chunk of text (~ 32 KB) into
74377aa0 43 memory, no matter how long the lines are.
44
45 As this example shows, one superficial difference from @Data.Text.Lazy@
46 is that many of the operations, like 'lines',
47 are \'lensified\'; this has a number of advantages where it is possible, in particular
48 it facilitates their use with 'Parser's of Text in the general pipes sense.
49 Each such expression reduces to the naturally corresponding function when
50 used with @view@ or @(^.)@.
51
52 A more important difference the example reveals is in the types closely associated with
53 the central type, @Producer Text m r@. In @Data.Text@ and @Data.Text.Lazy@
54 we find functions like
55
56> splitAt :: Int -> Text -> (Text, Text)
57> lines :: Int -> Text -> [Text]
58
59 which relate a Text with a pair or list of Texts. The corresponding functions here (taking
60 account of \'lensification\') are
61
62> view . splitAt :: (Monad m, Integral n)
63> => n -> Producer Text m r -> Producer Text.Text m (Producer Text.Text m r)
64> view lines :: Monad m => Producer Text m r -> FreeT (Producer Text m) m r
65
66 In the type @Producer Text.Text m (Producer Text.Text m r)@ the second
67 element of the \'pair\' of of \'effectful Texts\' cannot simply be retrieved
68 with 'snd'. This is an \'effectful\' pair, and one must work through the effects
69 of the first element to arrive at the second. Similarly in @FreeT (Producer Text m) m r@,
70 which corresponds with @[Text]@, on cannot simply drop 10 Producers and take the others;
71 we can only get to the ones we want to take by working through their predecessors.
72
73 Some of the types may be more readable if you imagine that we have introduced
74 our own type synonyms
75
76> type Text m r = Producer T.Text m r
77> type Texts m r = FreeT (Producer T.Text m) m r
78
79 Then we would think of the types above as
80
81> view . splitAt :: (Monad m, Integral n) => n -> Text m r -> Text m (Text m r)
82> view lines :: (Monad m) => Text m r -> Texts m r
83
84 which brings one closer to the types of the similar functions in @Data.Text.Lazy@
85
91727d11 86-}
87
7faef8bc 88module Pipes.Text (
91727d11 89 -- * Producers
1a83ae4e 90 fromLazy
91727d11 91
92 -- * Pipes
1677dc12 93 , map
94 , concatMap
95 , take
96 , drop
97 , takeWhile
98 , dropWhile
99 , filter
100 , scan
1677dc12 101 , pack
102 , unpack
103 , toCaseFold
104 , toLower
105 , toUpper
106 , stripStart
91727d11 107
108 -- * Folds
1677dc12 109 , toLazy
110 , toLazyM
111 , foldChars
112 , head
113 , last
114 , null
115 , length
116 , any
117 , all
118 , maximum
119 , minimum
120 , find
121 , index
122 , count
123
124 -- * Primitive Character Parsers
1677dc12 125 , nextChar
126 , drawChar
127 , unDrawChar
128 , peekChar
9e9bb0ce 129 , isEndOfChars
1677dc12 130
131 -- * Parsing Lenses
9e9bb0ce 132 , splitAt
1677dc12 133 , span
134 , break
135 , groupBy
136 , group
9e9bb0ce 137 , word
138 , line
1677dc12 139
140 -- * FreeT Splitters
141 , chunksOf
142 , splitsWith
0f8c6f1b 143 , splits
1a83ae4e 144 , groupsBy
145 , groups
1677dc12 146 , lines
147 , words
148
91727d11 149 -- * Transformations
1677dc12 150 , intersperse
9e9bb0ce 151 , packChars
31f41a5d 152
91727d11 153 -- * Joiners
1677dc12 154 , intercalate
155 , unlines
156 , unwords
9e9bb0ce 157
1a83ae4e 158 -- * Re-exports
91727d11 159 -- $reexports
1677dc12 160 , module Data.ByteString
161 , module Data.Text
162 , module Data.Profunctor
1677dc12 163 , module Pipes.Parse
7ed76745 164 , module Pipes.Group
91727d11 165 ) where
166
0f8c6f1b 167import Control.Applicative ((<*))
70125641 168import Control.Monad (liftM, join)
9e9bb0ce 169import Control.Monad.Trans.State.Strict (StateT(..), modify)
91727d11 170import qualified Data.Text as T
91727d11 171import Data.Text (Text)
172import qualified Data.Text.Lazy as TL
91727d11 173import Data.Text.Lazy.Internal (foldrChunks, defaultChunkSize)
31f41a5d 174import Data.ByteString (ByteString)
1677dc12 175import Data.Functor.Constant (Constant(Constant, getConstant))
91727d11 176import Data.Functor.Identity (Identity)
1677dc12 177import Data.Profunctor (Profunctor)
178import qualified Data.Profunctor
91727d11 179import Pipes
7fc48f7c 180import Pipes.Group (concats, intercalates, FreeT(..), FreeF(..))
7ed76745 181import qualified Pipes.Group as PG
91727d11 182import qualified Pipes.Parse as PP
7ed76745 183import Pipes.Parse (Parser)
91727d11 184import qualified Pipes.Prelude as P
91727d11 185import Data.Char (isSpace)
1a83ae4e 186import Data.Word (Word8)
1677dc12 187
91727d11 188import Prelude hiding (
189 all,
190 any,
191 break,
192 concat,
193 concatMap,
194 drop,
195 dropWhile,
196 elem,
197 filter,
198 head,
199 last,
200 lines,
201 length,
202 map,
203 maximum,
204 minimum,
205 notElem,
206 null,
207 readFile,
208 span,
209 splitAt,
210 take,
211 takeWhile,
212 unlines,
213 unwords,
214 words,
215 writeFile )
216
217-- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's
218fromLazy :: (Monad m) => TL.Text -> Producer' Text m ()
219fromLazy = foldrChunks (\e a -> yield e >> a) (return ())
ca6f90a0 220{-# INLINE fromLazy #-}
91727d11 221
1677dc12 222
223type Lens' a b = forall f . Functor f => (b -> f b) -> (a -> f a)
224
225type Iso' a b = forall f p . (Functor f, Profunctor p) => p b (f b) -> p a (f a)
226
227(^.) :: a -> ((b -> Constant b b) -> (a -> Constant b a)) -> b
228a ^. lens = getConstant (lens Constant a)
229
230
91727d11 231-- | Apply a transformation to each 'Char' in the stream
232map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
233map f = P.map (T.map f)
234{-# INLINABLE map #-}
235
ff38b9f0 236{-# RULES "p >-> map f" forall p f .
237 p >-> map f = for p (\txt -> yield (T.map f txt))
238 #-}
239
31f41a5d 240-- | Map a function over the characters of a text stream and concatenate the results
91727d11 241concatMap
242 :: (Monad m) => (Char -> Text) -> Pipe Text Text m r
243concatMap f = P.map (T.concatMap f)
244{-# INLINABLE concatMap #-}
245
ff38b9f0 246{-# RULES "p >-> concatMap f" forall p f .
247 p >-> concatMap f = for p (\txt -> yield (T.concatMap f txt))
248 #-}
7faef8bc 249
ff38b9f0 250
c0343bc9 251-- | Transform a Pipe of 'String's into one of 'Text' chunks
7faef8bc 252pack :: Monad m => Pipe String Text m r
253pack = P.map T.pack
254{-# INLINEABLE pack #-}
255
ff38b9f0 256{-# RULES "p >-> pack" forall p .
257 p >-> pack = for p (\txt -> yield (T.pack txt))
258 #-}
259
260-- | Transform a Pipes of 'Text' chunks into one of 'String's
7faef8bc 261unpack :: Monad m => Pipe Text String m r
d4732515 262unpack = for cat (\t -> yield (T.unpack t))
7faef8bc 263{-# INLINEABLE unpack #-}
264
ff38b9f0 265{-# RULES "p >-> unpack" forall p .
266 p >-> unpack = for p (\txt -> yield (T.unpack txt))
267 #-}
d4732515 268
b0d86a59 269-- | @toCaseFold@, @toLower@, @toUpper@ and @stripStart@ are standard 'Text' utilities,
270-- here acting as 'Text' pipes, rather as they would on a lazy text
7faef8bc 271toCaseFold :: Monad m => Pipe Text Text m ()
272toCaseFold = P.map T.toCaseFold
273{-# INLINEABLE toCaseFold #-}
274
ff38b9f0 275{-# RULES "p >-> toCaseFold" forall p .
276 p >-> toCaseFold = for p (\txt -> yield (T.toCaseFold txt))
277 #-}
278
279
c0343bc9 280-- | lowercase incoming 'Text'
7faef8bc 281toLower :: Monad m => Pipe Text Text m ()
282toLower = P.map T.toLower
283{-# INLINEABLE toLower #-}
284
ff38b9f0 285{-# RULES "p >-> toLower" forall p .
286 p >-> toLower = for p (\txt -> yield (T.toLower txt))
287 #-}
288
c0343bc9 289-- | uppercase incoming 'Text'
7faef8bc 290toUpper :: Monad m => Pipe Text Text m ()
291toUpper = P.map T.toUpper
292{-# INLINEABLE toUpper #-}
293
ff38b9f0 294{-# RULES "p >-> toUpper" forall p .
295 p >-> toUpper = for p (\txt -> yield (T.toUpper txt))
296 #-}
297
c0343bc9 298-- | Remove leading white space from an incoming succession of 'Text's
7faef8bc 299stripStart :: Monad m => Pipe Text Text m r
300stripStart = do
301 chunk <- await
302 let text = T.stripStart chunk
303 if T.null text
304 then stripStart
b0d86a59 305 else do yield text
306 cat
7faef8bc 307{-# INLINEABLE stripStart #-}
308
31f41a5d 309-- | @(take n)@ only allows @n@ individual characters to pass;
310-- contrast @Pipes.Prelude.take@ which would let @n@ chunks pass.
91727d11 311take :: (Monad m, Integral a) => a -> Pipe Text Text m ()
312take n0 = go n0 where
313 go n
314 | n <= 0 = return ()
315 | otherwise = do
31f41a5d 316 txt <- await
317 let len = fromIntegral (T.length txt)
91727d11 318 if (len > n)
31f41a5d 319 then yield (T.take (fromIntegral n) txt)
91727d11 320 else do
31f41a5d 321 yield txt
91727d11 322 go (n - len)
323{-# INLINABLE take #-}
324
31f41a5d 325-- | @(drop n)@ drops the first @n@ characters
91727d11 326drop :: (Monad m, Integral a) => a -> Pipe Text Text m r
327drop n0 = go n0 where
328 go n
329 | n <= 0 = cat
330 | otherwise = do
31f41a5d 331 txt <- await
332 let len = fromIntegral (T.length txt)
91727d11 333 if (len >= n)
334 then do
31f41a5d 335 yield (T.drop (fromIntegral n) txt)
91727d11 336 cat
337 else go (n - len)
338{-# INLINABLE drop #-}
339
31f41a5d 340-- | Take characters until they fail the predicate
91727d11 341takeWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m ()
342takeWhile predicate = go
343 where
344 go = do
31f41a5d 345 txt <- await
346 let (prefix, suffix) = T.span predicate txt
91727d11 347 if (T.null suffix)
348 then do
31f41a5d 349 yield txt
91727d11 350 go
351 else yield prefix
352{-# INLINABLE takeWhile #-}
353
31f41a5d 354-- | Drop characters until they fail the predicate
91727d11 355dropWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
356dropWhile predicate = go where
357 go = do
31f41a5d 358 txt <- await
359 case T.findIndex (not . predicate) txt of
91727d11 360 Nothing -> go
361 Just i -> do
31f41a5d 362 yield (T.drop i txt)
91727d11 363 cat
364{-# INLINABLE dropWhile #-}
365
366-- | Only allows 'Char's to pass if they satisfy the predicate
367filter :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
368filter predicate = P.map (T.filter predicate)
369{-# INLINABLE filter #-}
370
ff38b9f0 371{-# RULES "p >-> filter q" forall p q .
372 p >-> filter q = for p (\txt -> yield (T.filter q txt))
373 #-}
374
31f41a5d 375-- | Strict left scan over the characters
91727d11 376scan
377 :: (Monad m)
378 => (Char -> Char -> Char) -> Char -> Pipe Text Text m r
11645cdc
GG
379scan step begin = do
380 yield (T.singleton begin)
381 go begin
91727d11 382 where
31f41a5d 383 go c = do
384 txt <- await
385 let txt' = T.scanl step c txt
386 c' = T.last txt'
11645cdc 387 yield (T.tail txt')
31f41a5d 388 go c'
91727d11 389{-# INLINABLE scan #-}
390
391{-| Fold a pure 'Producer' of strict 'Text's into a lazy
392 'TL.Text'
393-}
394toLazy :: Producer Text Identity () -> TL.Text
395toLazy = TL.fromChunks . P.toList
396{-# INLINABLE toLazy #-}
397
398{-| Fold an effectful 'Producer' of strict 'Text's into a lazy
399 'TL.Text'
400
401 Note: 'toLazyM' is not an idiomatic use of @pipes@, but I provide it for
402 simple testing purposes. Idiomatic @pipes@ style consumes the chunks
403 immediately as they are generated instead of loading them all into memory.
404-}
405toLazyM :: (Monad m) => Producer Text m () -> m TL.Text
406toLazyM = liftM TL.fromChunks . P.toListM
407{-# INLINABLE toLazyM #-}
408
31f41a5d 409-- | Reduce the text stream using a strict left fold over characters
64e03122 410foldChars
91727d11 411 :: Monad m
412 => (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r
64e03122 413foldChars step begin done = P.fold (T.foldl' step) begin done
1677dc12 414{-# INLINABLE foldChars #-}
91727d11 415
416-- | Retrieve the first 'Char'
417head :: (Monad m) => Producer Text m () -> m (Maybe Char)
418head = go
419 where
420 go p = do
421 x <- nextChar p
422 case x of
423 Left _ -> return Nothing
31f41a5d 424 Right (c, _) -> return (Just c)
91727d11 425{-# INLINABLE head #-}
426
427-- | Retrieve the last 'Char'
428last :: (Monad m) => Producer Text m () -> m (Maybe Char)
429last = go Nothing
430 where
431 go r p = do
432 x <- next p
433 case x of
434 Left () -> return r
31f41a5d 435 Right (txt, p') ->
436 if (T.null txt)
91727d11 437 then go r p'
31f41a5d 438 else go (Just $ T.last txt) p'
91727d11 439{-# INLINABLE last #-}
440
441-- | Determine if the stream is empty
442null :: (Monad m) => Producer Text m () -> m Bool
443null = P.all T.null
444{-# INLINABLE null #-}
445
62e8521c 446-- | Count the number of characters in the stream
91727d11 447length :: (Monad m, Num n) => Producer Text m () -> m n
31f41a5d 448length = P.fold (\n txt -> n + fromIntegral (T.length txt)) 0 id
91727d11 449{-# INLINABLE length #-}
450
451-- | Fold that returns whether 'M.Any' received 'Char's satisfy the predicate
452any :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
453any predicate = P.any (T.any predicate)
454{-# INLINABLE any #-}
455
456-- | Fold that returns whether 'M.All' received 'Char's satisfy the predicate
457all :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
458all predicate = P.all (T.all predicate)
459{-# INLINABLE all #-}
460
62e8521c 461-- | Return the maximum 'Char' within a text stream
91727d11 462maximum :: (Monad m) => Producer Text m () -> m (Maybe Char)
463maximum = P.fold step Nothing id
464 where
31f41a5d 465 step mc txt =
466 if (T.null txt)
467 then mc
468 else Just $ case mc of
469 Nothing -> T.maximum txt
470 Just c -> max c (T.maximum txt)
91727d11 471{-# INLINABLE maximum #-}
472
62e8521c 473-- | Return the minimum 'Char' within a text stream (surely very useful!)
91727d11 474minimum :: (Monad m) => Producer Text m () -> m (Maybe Char)
475minimum = P.fold step Nothing id
476 where
31f41a5d 477 step mc txt =
478 if (T.null txt)
479 then mc
480 else case mc of
481 Nothing -> Just (T.minimum txt)
482 Just c -> Just (min c (T.minimum txt))
91727d11 483{-# INLINABLE minimum #-}
484
91727d11 485-- | Find the first element in the stream that matches the predicate
486find
487 :: (Monad m)
488 => (Char -> Bool) -> Producer Text m () -> m (Maybe Char)
489find predicate p = head (p >-> filter predicate)
490{-# INLINABLE find #-}
491
62e8521c 492-- | Index into a text stream
91727d11 493index
494 :: (Monad m, Integral a)
495 => a-> Producer Text m () -> m (Maybe Char)
496index n p = head (p >-> drop n)
497{-# INLINABLE index #-}
498
63ea9ffd 499
31f41a5d 500-- | Store a tally of how many segments match the given 'Text'
501count :: (Monad m, Num n) => Text -> Producer Text m () -> m n
502count c p = P.fold (+) 0 id (p >-> P.map (fromIntegral . T.count c))
503{-# INLINABLE count #-}
504
9e9bb0ce 505
1a83ae4e 506-- | Consume the first character from a stream of 'Text'
507--
508-- 'next' either fails with a 'Left' if the 'Producer' has no more characters or
509-- succeeds with a 'Right' providing the next character and the remainder of the
510-- 'Producer'.
9e9bb0ce 511
9e9bb0ce 512nextChar
513 :: (Monad m)
514 => Producer Text m r
515 -> m (Either r (Char, Producer Text m r))
516nextChar = go
517 where
518 go p = do
519 x <- next p
520 case x of
521 Left r -> return (Left r)
522 Right (txt, p') -> case (T.uncons txt) of
523 Nothing -> go p'
524 Just (c, txt') -> return (Right (c, yield txt' >> p'))
525{-# INLINABLE nextChar #-}
526
1a83ae4e 527-- | Draw one 'Char' from a stream of 'Text', returning 'Left' if the 'Producer' is empty
528
9e9bb0ce 529drawChar :: (Monad m) => Parser Text m (Maybe Char)
530drawChar = do
531 x <- PP.draw
532 case x of
533 Nothing -> return Nothing
534 Just txt -> case (T.uncons txt) of
535 Nothing -> drawChar
536 Just (c, txt') -> do
537 PP.unDraw txt'
538 return (Just c)
539{-# INLINABLE drawChar #-}
540
541-- | Push back a 'Char' onto the underlying 'Producer'
542unDrawChar :: (Monad m) => Char -> Parser Text m ()
543unDrawChar c = modify (yield (T.singleton c) >>)
544{-# INLINABLE unDrawChar #-}
545
546{-| 'peekChar' checks the first 'Char' in the stream, but uses 'unDrawChar' to
547 push the 'Char' back
548
549> peekChar = do
550> x <- drawChar
551> case x of
552> Left _ -> return ()
553> Right c -> unDrawChar c
554> return x
1a83ae4e 555
9e9bb0ce 556-}
1a83ae4e 557
9e9bb0ce 558peekChar :: (Monad m) => Parser Text m (Maybe Char)
559peekChar = do
560 x <- drawChar
561 case x of
562 Nothing -> return ()
563 Just c -> unDrawChar c
564 return x
565{-# INLINABLE peekChar #-}
566
567{-| Check if the underlying 'Producer' has no more characters
568
569 Note that this will skip over empty 'Text' chunks, unlike
570 'PP.isEndOfInput' from @pipes-parse@, which would consider
571 an empty 'Text' a valid bit of input.
572
573> isEndOfChars = liftM isLeft peekChar
574-}
575isEndOfChars :: (Monad m) => Parser Text m Bool
576isEndOfChars = do
577 x <- peekChar
578 return (case x of
579 Nothing -> True
580 Just _-> False )
581{-# INLINABLE isEndOfChars #-}
582
583
31f41a5d 584-- | Splits a 'Producer' after the given number of characters
91727d11 585splitAt
586 :: (Monad m, Integral n)
587 => n
9e9bb0ce 588 -> Lens' (Producer Text m r)
589 (Producer Text m (Producer Text m r))
590splitAt n0 k p0 = fmap join (k (go n0 p0))
91727d11 591 where
592 go 0 p = return p
593 go n p = do
594 x <- lift (next p)
595 case x of
596 Left r -> return (return r)
31f41a5d 597 Right (txt, p') -> do
598 let len = fromIntegral (T.length txt)
91727d11 599 if (len <= n)
600 then do
31f41a5d 601 yield txt
91727d11 602 go (n - len) p'
603 else do
31f41a5d 604 let (prefix, suffix) = T.splitAt (fromIntegral n) txt
91727d11 605 yield prefix
606 return (yield suffix >> p')
607{-# INLINABLE splitAt #-}
608
91727d11 609
1a83ae4e 610-- | Split a text stream in two, producing the longest
611-- consecutive group of characters that satisfies the predicate
612-- and returning the rest
613
91727d11 614span
615 :: (Monad m)
616 => (Char -> Bool)
9e9bb0ce 617 -> Lens' (Producer Text m r)
618 (Producer Text m (Producer Text m r))
619span predicate k p0 = fmap join (k (go p0))
91727d11 620 where
621 go p = do
622 x <- lift (next p)
623 case x of
624 Left r -> return (return r)
31f41a5d 625 Right (txt, p') -> do
626 let (prefix, suffix) = T.span predicate txt
91727d11 627 if (T.null suffix)
628 then do
31f41a5d 629 yield txt
91727d11 630 go p'
631 else do
632 yield prefix
633 return (yield suffix >> p')
634{-# INLINABLE span #-}
635
1a83ae4e 636{-| Split a text stream in two, producing the longest
62e8521c 637 consecutive group of characters that don't satisfy the predicate
91727d11 638-}
639break
640 :: (Monad m)
641 => (Char -> Bool)
9e9bb0ce 642 -> Lens' (Producer Text m r)
643 (Producer Text m (Producer Text m r))
91727d11 644break predicate = span (not . predicate)
645{-# INLINABLE break #-}
646
9e9bb0ce 647{-| Improper lens that splits after the first group of equivalent Chars, as
648 defined by the given equivalence relation
649-}
650groupBy
651 :: (Monad m)
652 => (Char -> Char -> Bool)
653 -> Lens' (Producer Text m r)
654 (Producer Text m (Producer Text m r))
655groupBy equals k p0 = fmap join (k ((go p0))) where
656 go p = do
657 x <- lift (next p)
658 case x of
659 Left r -> return (return r)
660 Right (txt, p') -> case T.uncons txt of
661 Nothing -> go p'
662 Just (c, _) -> (yield txt >> p') ^. span (equals c)
663{-# INLINABLE groupBy #-}
664
665-- | Improper lens that splits after the first succession of identical 'Char' s
666group :: Monad m
667 => Lens' (Producer Text m r)
668 (Producer Text m (Producer Text m r))
669group = groupBy (==)
670{-# INLINABLE group #-}
671
672{-| Improper lens that splits a 'Producer' after the first word
673
674 Unlike 'words', this does not drop leading whitespace
675-}
676word :: (Monad m)
677 => Lens' (Producer Text m r)
678 (Producer Text m (Producer Text m r))
679word k p0 = fmap join (k (to p0))
680 where
681 to p = do
682 p' <- p^.span isSpace
683 p'^.break isSpace
684{-# INLINABLE word #-}
685
686
687line :: (Monad m)
688 => Lens' (Producer Text m r)
689 (Producer Text m (Producer Text m r))
690line = break (== '\n')
691
692{-# INLINABLE line #-}
693
694
695-- | Intersperse a 'Char' in between the characters of stream of 'Text'
696intersperse
697 :: (Monad m) => Char -> Producer Text m r -> Producer Text m r
698intersperse c = go0
699 where
700 go0 p = do
701 x <- lift (next p)
702 case x of
703 Left r -> return r
704 Right (txt, p') -> do
705 yield (T.intersperse c txt)
706 go1 p'
707 go1 p = do
708 x <- lift (next p)
709 case x of
710 Left r -> return r
711 Right (txt, p') -> do
712 yield (T.singleton c)
713 yield (T.intersperse c txt)
714 go1 p'
715{-# INLINABLE intersperse #-}
716
717
718
719-- | Improper isomorphism between a 'Producer' of 'ByteString's and 'Word8's
720packChars :: Monad m => Iso' (Producer Char m x) (Producer Text m x)
721packChars = Data.Profunctor.dimap to (fmap from)
722 where
723 -- to :: Monad m => Producer Char m x -> Producer Text m x
7ed76745 724 to p = PG.folds step id done (p^.PG.chunksOf defaultChunkSize)
9e9bb0ce 725
726 step diffAs c = diffAs . (c:)
727
728 done diffAs = T.pack (diffAs [])
729
730 -- from :: Monad m => Producer Text m x -> Producer Char m x
731 from p = for p (each . T.unpack)
732{-# INLINABLE packChars #-}
733
0f8c6f1b 734
735-- | Split a text stream into 'FreeT'-delimited text streams of fixed size
736chunksOf
737 :: (Monad m, Integral n)
738 => n -> Lens' (Producer Text m r)
739 (FreeT (Producer Text m) m r)
740chunksOf n k p0 = fmap concats (k (FreeT (go p0)))
741 where
742 go p = do
743 x <- next p
744 return $ case x of
7ed76745 745 Left r -> Pure r
746 Right (txt, p') -> Free $ do
0f8c6f1b 747 p'' <- (yield txt >> p') ^. splitAt n
7ed76745 748 return $ FreeT (go p'')
0f8c6f1b 749{-# INLINABLE chunksOf #-}
750
751
62e8521c 752{-| Split a text stream into sub-streams delimited by characters that satisfy the
91727d11 753 predicate
754-}
1677dc12 755splitsWith
91727d11 756 :: (Monad m)
757 => (Char -> Bool)
758 -> Producer Text m r
7ed76745 759 -> FreeT (Producer Text m) m r
760splitsWith predicate p0 = FreeT (go0 p0)
91727d11 761 where
762 go0 p = do
763 x <- next p
764 case x of
7ed76745 765 Left r -> return (Pure r)
31f41a5d 766 Right (txt, p') ->
767 if (T.null txt)
91727d11 768 then go0 p'
7ed76745 769 else return $ Free $ do
9e9bb0ce 770 p'' <- (yield txt >> p') ^. span (not . predicate)
7ed76745 771 return $ FreeT (go1 p'')
91727d11 772 go1 p = do
773 x <- nextChar p
774 return $ case x of
7ed76745 775 Left r -> Pure r
776 Right (_, p') -> Free $ do
9e9bb0ce 777 p'' <- p' ^. span (not . predicate)
7ed76745 778 return $ FreeT (go1 p'')
1677dc12 779{-# INLINABLE splitsWith #-}
91727d11 780
31f41a5d 781-- | Split a text stream using the given 'Char' as the delimiter
0f8c6f1b 782splits :: (Monad m)
91727d11 783 => Char
0f8c6f1b 784 -> Lens' (Producer Text m r)
785 (FreeT (Producer Text m) m r)
786splits c k p =
7ed76745 787 fmap (PG.intercalates (yield (T.singleton c))) (k (splitsWith (c ==) p))
0f8c6f1b 788{-# INLINABLE splits #-}
789
790{-| Isomorphism between a stream of 'Text' and groups of equivalent 'Char's , using the
791 given equivalence relation
792-}
793groupsBy
794 :: Monad m
795 => (Char -> Char -> Bool)
796 -> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
7ed76745 797groupsBy equals k p0 = fmap concats (k (FreeT (go p0))) where
0f8c6f1b 798 go p = do x <- next p
7ed76745 799 case x of Left r -> return (Pure r)
0f8c6f1b 800 Right (bs, p') -> case T.uncons bs of
801 Nothing -> go p'
7ed76745 802 Just (c, _) -> do return $ Free $ do
0f8c6f1b 803 p'' <- (yield bs >> p')^.span (equals c)
7ed76745 804 return $ FreeT (go p'')
0f8c6f1b 805{-# INLINABLE groupsBy #-}
806
807
808-- | Like 'groupsBy', where the equality predicate is ('==')
809groups
810 :: Monad m
811 => Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
812groups = groupsBy (==)
813{-# INLINABLE groups #-}
814
91727d11 815
91727d11 816
62e8521c 817{-| Split a text stream into 'FreeT'-delimited lines
91727d11 818-}
819lines
0f8c6f1b 820 :: (Monad m) => Iso' (Producer Text m r) (FreeT (Producer Text m) m r)
821lines = Data.Profunctor.dimap _lines (fmap _unlines)
91727d11 822 where
7ed76745 823 _lines p0 = FreeT (go0 p0)
0f8c6f1b 824 where
825 go0 p = do
826 x <- next p
827 case x of
7ed76745 828 Left r -> return (Pure r)
0f8c6f1b 829 Right (txt, p') ->
830 if (T.null txt)
831 then go0 p'
7ed76745 832 else return $ Free $ go1 (yield txt >> p')
0f8c6f1b 833 go1 p = do
834 p' <- p ^. break ('\n' ==)
7ed76745 835 return $ FreeT $ do
0f8c6f1b 836 x <- nextChar p'
837 case x of
7ed76745 838 Left r -> return $ Pure r
0f8c6f1b 839 Right (_, p'') -> go0 p''
840 -- _unlines
841 -- :: Monad m
842 -- => FreeT (Producer Text m) m x -> Producer Text m x
7fc48f7c 843 _unlines = concats . PG.maps (<* yield (T.singleton '\n'))
844
0f8c6f1b 845
91727d11 846{-# INLINABLE lines #-}
91727d11 847
31f41a5d 848
31f41a5d 849-- | Split a text stream into 'FreeT'-delimited words
91727d11 850words
0f8c6f1b 851 :: (Monad m) => Iso' (Producer Text m r) (FreeT (Producer Text m) m r)
852words = Data.Profunctor.dimap go (fmap _unwords)
91727d11 853 where
7ed76745 854 go p = FreeT $ do
cf10d6f1 855 x <- next (p >-> dropWhile isSpace)
856 return $ case x of
7ed76745 857 Left r -> Pure r
858 Right (bs, p') -> Free $ do
9e9bb0ce 859 p'' <- (yield bs >> p') ^. break isSpace
cf10d6f1 860 return (go p'')
7ed76745 861 _unwords = PG.intercalates (yield $ T.singleton ' ')
0f8c6f1b 862
91727d11 863{-# INLINABLE words #-}
864
cf10d6f1 865
31f41a5d 866{-| 'intercalate' concatenates the 'FreeT'-delimited text streams after
867 interspersing a text stream in between them
91727d11 868-}
869intercalate
870 :: (Monad m)
871 => Producer Text m ()
872 -> FreeT (Producer Text m) m r
873 -> Producer Text m r
874intercalate p0 = go0
875 where
876 go0 f = do
7ed76745 877 x <- lift (runFreeT f)
91727d11 878 case x of
7ed76745 879 Pure r -> return r
880 Free p -> do
91727d11 881 f' <- p
882 go1 f'
883 go1 f = do
7ed76745 884 x <- lift (runFreeT f)
91727d11 885 case x of
7ed76745 886 Pure r -> return r
887 Free p -> do
91727d11 888 p0
889 f' <- p
890 go1 f'
891{-# INLINABLE intercalate #-}
892
62e8521c 893{-| Join 'FreeT'-delimited lines into a text stream
91727d11 894-}
895unlines
896 :: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
897unlines = go
898 where
899 go f = do
7ed76745 900 x <- lift (runFreeT f)
91727d11 901 case x of
7ed76745 902 Pure r -> return r
903 Free p -> do
91727d11 904 f' <- p
905 yield $ T.singleton '\n'
906 go f'
907{-# INLINABLE unlines #-}
908
31f41a5d 909{-| Join 'FreeT'-delimited words into a text stream
91727d11 910-}
911unwords
912 :: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
7fc48f7c 913unwords = intercalate (yield $ T.singleton ' ')
91727d11 914{-# INLINABLE unwords #-}
915
91727d11 916
91727d11 917{- $reexports
91727d11 918
919 @Data.Text@ re-exports the 'Text' type.
920
0f8c6f1b 921 @Pipes.Parse@ re-exports 'input', 'concat', 'FreeT' (the type) and the 'Parse' synonym.
64e03122 922-}
923
bbdfd305 924