aboutsummaryrefslogtreecommitdiffhomepage
path: root/Pipes/Text.hs
blob: 20c226edfdb06372a525dc3f293a19214d9b82fb (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
{-# LANGUAGE RankNTypes, TypeFamilies, BangPatterns, Safe#-}

{-| The module @Pipes.Text@ closely follows @Pipes.ByteString@ from 
    the @pipes-bytestring@ package. A draft tutorial can be found in
    @Pipes.Text.Tutorial@. 
-}

module Pipes.Text  (
    -- * Producers
    fromLazy

    -- * Pipes
    , map
    , concatMap
    , take
    , takeWhile
    , filter
    , toCaseFold
    , toLower
    , toUpper
    , stripStart
    , scan

    -- * Folds
    , toLazy
    , toLazyM
    , foldChars
    , head
    , last
    , null
    , length
    , any
    , all
    , maximum
    , minimum
    , find
    , index

    -- * Primitive Character Parsers
    , nextChar
    , drawChar
    , unDrawChar
    , peekChar
    , isEndOfChars

    -- * Parsing Lenses
    , splitAt
    , span
    , break
    , groupBy
    , group
    , word
    , line

    -- * Transforming Text and Character Streams
    , drop
    , dropWhile
    , pack
    , unpack
    , intersperse

    -- * FreeT Transformations
    , chunksOf
    , splitsWith
    , splits
    , groupsBy
    , groups
    , lines
    , unlines
    , words
    , unwords
    , intercalate

    -- * Re-exports
    -- $reexports
    , module Data.ByteString
    , module Data.Text
    , module Pipes.Parse
    , module Pipes.Group
    ) where

import Control.Applicative ((*>))
import Control.Monad (liftM, join)
import Data.Functor.Constant (Constant(..))
import Data.Functor.Identity (Identity)
import Control.Monad.Trans.State.Strict (modify)

import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import Data.ByteString (ByteString)
import Data.Char (isSpace)
import Foreign.Storable (sizeOf)
import Data.Bits (shiftL)

import Pipes
import Pipes.Group (folds, maps, concats, intercalates, FreeT(..), FreeF(..))
import qualified Pipes.Group as PG
import qualified Pipes.Parse as PP
import Pipes.Parse (Parser)
import qualified Pipes.Prelude as P



import Prelude hiding (
    all,
    any,
    break,
    concat,
    concatMap,
    drop,
    dropWhile,
    elem,
    filter,
    head,
    last,
    lines,
    length,
    map,
    maximum,
    minimum,
    notElem,
    null,
    readFile,
    span,
    splitAt,
    take,
    takeWhile,
    unlines,
    unwords,
    words,
    writeFile )

-- $setup
-- >>> :set -XOverloadedStrings
-- >>> import Data.Text (Text)
-- >>> import qualified Data.Text as T
-- >>> import qualified Data.Text.Lazy.IO as TL
-- >>> import Data.Char

-- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's. Producers in 
-- IO can be found in 'Pipes.Text.IO' or in pipes-bytestring, employed with the
-- decoding lenses in 'Pipes.Text.Encoding'
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

-- >>> let margaret =  ["Margaret, are you grieving\nOver Golde","ngrove unleaving?":: Text]
-- >>> TL.putStrLn . toLazy $ each margaret >-> map Data.Char.toUpper
-- MARGARET, ARE YOU GRIEVING
-- OVER GOLDENGROVE UNLEAVING?
map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
map f = P.map (T.map f)
{-# INLINABLE map #-}

-- | Map a function over the characters of a text stream and concatenate the results

concatMap
    :: (Monad m) => (Char -> Text) -> Pipe Text Text m r
concatMap f = P.map (T.concatMap f)
{-# INLINABLE concatMap #-}

-- | @(take n)@ only allows @n@ individual characters to pass;
--  contrast @Pipes.Prelude.take@ which would let @n@ chunks pass.
take :: (Monad m, Integral a) => a -> Pipe Text Text m ()
take n0 = go n0 where
    go n
        | n <= 0    = return ()
        | otherwise = do 
            txt <- await
            let len = fromIntegral (T.length txt)
            if (len > n)
                then yield (T.take (fromIntegral n) txt)
                else do
                    yield txt
                    go (n - len)
{-# INLINABLE take #-}

-- | Take characters until they fail the predicate
takeWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m ()
takeWhile predicate = go
  where
    go = do
        txt <- await
        let (prefix, suffix) = T.span predicate txt
        if (T.null suffix)
            then do
                yield txt
                go
            else yield prefix
{-# INLINABLE takeWhile #-}

-- | Only allows 'Char's to pass if they satisfy the predicate
filter :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
filter predicate = P.map (T.filter predicate)
{-# INLINABLE filter #-}

-- | Strict left scan over the characters
-- >>> let margaret = ["Margaret, are you grieving\nOver Golde","ngrove unleaving?":: Text]
-- >>> let title_caser a x = case a of ' ' -> Data.Char.toUpper x; _ -> x
-- >>> toLazy $ each margaret >-> scan title_caser ' ' 
-- " Margaret, Are You Grieving\nOver Goldengrove Unleaving?"

scan
    :: (Monad m)
    => (Char -> Char -> Char) -> Char -> Pipe Text Text m r
scan step begin = do
    yield (T.singleton begin)
    go begin
  where
    go c = do
        txt <- await
        let txt' = T.scanl step c txt
            c' = T.last txt'
        yield (T.tail txt')
        go c'
{-# INLINABLE scan #-}

-- | @toCaseFold@, @toLower@, @toUpper@ and @stripStart@ are standard 'Text' utilities,
-- here acting as 'Text' pipes, rather as they would  on a lazy text
toCaseFold :: Monad m => Pipe Text Text m r
toCaseFold = P.map T.toCaseFold
{-# INLINEABLE toCaseFold #-}

-- | lowercase incoming 'Text'
toLower :: Monad m => Pipe Text Text m r
toLower = P.map T.toLower
{-# INLINEABLE toLower #-}

-- | uppercase incoming 'Text'
toUpper :: Monad m => Pipe Text Text m r
toUpper = P.map T.toUpper
{-# INLINEABLE toUpper #-}

-- | Remove leading white space from an incoming succession of 'Text's
stripStart :: Monad m => Pipe Text Text m r
stripStart = do
    chunk <- await
    let text = T.stripStart chunk
    if T.null text
      then stripStart
      else do yield text
              cat
{-# INLINEABLE stripStart #-}

{-| Fold a pure 'Producer' of strict 'Text's into a lazy
    'TL.Text'
-}
toLazy :: Producer Text Identity () -> TL.Text
toLazy = TL.fromChunks . P.toList
{-# INLINABLE toLazy #-}

{-| Fold an effectful 'Producer' of strict 'Text's into a lazy
    'TL.Text'

    Note: 'toLazyM' is not an idiomatic use of @pipes@, but I provide it for
    simple testing purposes.  Idiomatic @pipes@ style consumes the chunks
    immediately as they are generated instead of loading them all into memory.
-}
toLazyM :: (Monad m) => Producer Text m () -> m TL.Text
toLazyM = liftM TL.fromChunks . P.toListM
{-# INLINABLE toLazyM #-}

-- | Reduce the text stream using a strict left fold over characters
foldChars
    :: Monad m
    => (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r
foldChars step begin done = P.fold (T.foldl' step) begin done
{-# INLINABLE foldChars #-}


-- | Retrieve the first 'Char'
head :: (Monad m) => Producer Text m () -> m (Maybe Char)
head = go
  where
    go p = do
        x <- nextChar p
        case x of
            Left   _      -> return  Nothing
            Right (c, _) -> return (Just c)
{-# INLINABLE head #-}

-- | Retrieve the last 'Char'
last :: (Monad m) => Producer Text m () -> m (Maybe Char)
last = go Nothing
  where
    go r p = do
        x <- next p
        case x of
            Left   ()      -> return r
            Right (txt, p') ->
                if (T.null txt)
                then go r p'
                else go (Just $ T.last txt) p'
{-# INLINABLE last #-}

-- | Determine if the stream is empty
null :: (Monad m) => Producer Text m () -> m Bool
null = P.all T.null
{-# INLINABLE null #-}

-- | Count the number of characters in the stream
length :: (Monad m, Num n) => Producer Text m () -> m n
length = P.fold (\n txt -> n + fromIntegral (T.length txt)) 0 id
{-# INLINABLE length #-}

-- | Fold that returns whether 'M.Any' received 'Char's satisfy the predicate
any :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
any predicate = P.any (T.any predicate)
{-# INLINABLE any #-}

-- | Fold that returns whether 'M.All' received 'Char's satisfy the predicate
all :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
all predicate = P.all (T.all predicate)
{-# INLINABLE all #-}

-- | Return the maximum 'Char' within a text stream
maximum :: (Monad m) => Producer Text m () -> m (Maybe Char)
maximum = P.fold step Nothing id
  where
    step mc txt =
        if (T.null txt)
        then mc
        else Just $ case mc of
            Nothing -> T.maximum txt
            Just c -> max c (T.maximum txt)
{-# INLINABLE maximum #-}

-- | Return the minimum 'Char' within a text stream (surely very useful!)
minimum :: (Monad m) => Producer Text m () -> m (Maybe Char)
minimum = P.fold step Nothing id
  where
    step mc txt =
        if (T.null txt)
        then mc
        else case mc of
            Nothing -> Just (T.minimum txt)
            Just c -> Just (min c (T.minimum txt))
{-# INLINABLE minimum #-}

-- | Find the first element in the stream that matches the predicate
find
    :: (Monad m)
    => (Char -> Bool) -> Producer Text m () -> m (Maybe Char)
find predicate p = head (p >-> filter predicate)
{-# INLINABLE find #-}

-- | Index into a text stream
index
    :: (Monad m, Integral a)
    => a-> Producer Text m () -> m (Maybe Char)
index n p = head (drop n p)
{-# INLINABLE index #-}



-- | Consume the first character from a stream of 'Text'
--
-- 'next' either fails with a 'Left' if the 'Producer' has no more characters or
-- succeeds with a 'Right' providing the next character and the remainder of the
-- 'Producer'.

nextChar
    :: (Monad m)
    => Producer Text m r
    -> m (Either r (Char, Producer Text m r))
nextChar = go
  where
    go p = do
        x <- next p
        case x of
            Left   r       -> return (Left r)
            Right (txt, p') -> case (T.uncons txt) of
                Nothing        -> go p'
                Just (c, txt') -> return (Right (c, yield txt' >> p'))
{-# INLINABLE nextChar #-}

-- | Draw one 'Char' from a stream of 'Text', returning 'Left' if the 'Producer' is empty

drawChar :: (Monad m) => Parser Text m (Maybe Char)
drawChar = do
    x <- PP.draw
    case x of
        Nothing  -> return Nothing
        Just txt -> case (T.uncons txt) of
            Nothing        -> drawChar
            Just (c, txt') -> do
                PP.unDraw txt'
                return (Just c)
{-# INLINABLE drawChar #-}

-- | Push back a 'Char' onto the underlying 'Producer'
unDrawChar :: (Monad m) => Char -> Parser Text m ()
unDrawChar c = modify (yield (T.singleton c) >>)
{-# INLINABLE unDrawChar #-}

{-| 'peekChar' checks the first 'Char' in the stream, but uses 'unDrawChar' to
    push the 'Char' back

> peekChar = do
>     x <- drawChar
>     case x of
>         Left  _  -> return ()
>         Right c -> unDrawChar c
>     return x

-}

peekChar :: (Monad m) => Parser Text m (Maybe Char)
peekChar = do
    x <- drawChar
    case x of
        Nothing  -> return ()
        Just c -> unDrawChar c
    return x
{-# INLINABLE peekChar #-}

{-| Check if the underlying 'Producer' has no more characters

    Note that this will skip over empty 'Text' chunks, unlike
    'PP.isEndOfInput' from @pipes-parse@, which would consider
    an empty 'Text' a valid bit of input.

> isEndOfChars = liftM isLeft peekChar
-}
isEndOfChars :: (Monad m) => Parser Text m Bool
isEndOfChars = do
    x <- peekChar
    return (case x of
        Nothing -> True
        Just _-> False )
{-# INLINABLE isEndOfChars #-}

-- | Splits a 'Producer' after the given number of characters
splitAt
    :: (Monad m, Integral n)
    => n
    -> Lens' (Producer Text m r)
             (Producer Text m (Producer Text m r))
splitAt n0 k p0 = fmap join (k (go n0 p0))
  where
    go 0 p = return p
    go n p = do
        x <- lift (next p)
        case x of
            Left   r       -> return (return r)
            Right (txt, p') -> do
                let len = fromIntegral (T.length txt)
                if (len <= n)
                    then do
                        yield txt
                        go (n - len) p'
                    else do
                        let (prefix, suffix) = T.splitAt (fromIntegral n) txt
                        yield prefix
                        return (yield suffix >> p')
{-# INLINABLE splitAt #-}


-- | Split a text stream in two, producing the longest
--   consecutive group of characters that satisfies the predicate
--   and returning the rest

span
    :: (Monad m)
    => (Char -> Bool)
    -> Lens' (Producer Text m r)
             (Producer Text m (Producer Text m r))
span predicate k p0 = fmap join (k (go p0))
  where
    go p = do
        x <- lift (next p)
        case x of
            Left   r       -> return (return r)
            Right (txt, p') -> do
                let (prefix, suffix) = T.span predicate txt
                if (T.null suffix)
                    then do
                        yield txt
                        go p'
                    else do
                        yield prefix
                        return (yield suffix >> p')
{-# INLINABLE span #-}

{-| Split a text stream in two, producing the longest
    consecutive group of characters that don't satisfy the predicate
-}
break
    :: (Monad m)
    => (Char -> Bool)
    -> Lens' (Producer Text m r)
             (Producer Text m (Producer Text m r))
break predicate = span (not . predicate)
{-# INLINABLE break #-}

{-| Improper lens that splits after the first group of equivalent Chars, as
    defined by the given equivalence relation
-}
groupBy
    :: (Monad m)
    => (Char -> Char -> Bool)
    -> Lens' (Producer Text m r)
             (Producer Text m (Producer Text m r))
groupBy equals k p0 = fmap join (k ((go p0))) where
    go p = do
        x <- lift (next p)
        case x of
            Left   r       -> return (return r)
            Right (txt, p') -> case T.uncons txt of
                Nothing      -> go p'
                Just (c, _) -> (yield txt >> p') ^. span (equals c)
{-# INLINABLE groupBy #-}

-- | Improper lens that splits after the first succession of identical 'Char' s
group :: Monad m
      => Lens' (Producer Text m r)
               (Producer Text m (Producer Text m r))
group = groupBy (==)
{-# INLINABLE group #-}

{-| Improper lens that splits a 'Producer' after the first word

    Unlike 'words', this does not drop leading whitespace
-}
word :: (Monad m)
     => Lens' (Producer Text m r)
              (Producer Text m (Producer Text m r))
word k p0 = fmap join (k (to p0))
  where
    to p = do
        p' <- p^.span isSpace
        p'^.break isSpace
{-# INLINABLE word #-}

line :: (Monad m)
     => Lens' (Producer Text m r)
              (Producer Text m (Producer Text m r))
line = break (== '\n')
{-# INLINABLE line #-}

-- | @(drop n)@ drops the first @n@ characters
drop :: (Monad m, Integral n)
     => n -> Producer Text m r -> Producer Text m r
drop n p = do
    p' <- lift $ runEffect (for (p ^. splitAt n) discard)
    p'
{-# INLINABLE drop #-}

-- | Drop characters until they fail the predicate
dropWhile :: (Monad m)
    => (Char -> Bool) -> Producer Text m r -> Producer Text m r
dropWhile predicate p = do
    p' <- lift $ runEffect (for (p ^. span predicate) discard)
    p'
{-# INLINABLE dropWhile #-}

-- | Intersperse a 'Char' in between the characters of stream of 'Text'
intersperse
    :: (Monad m) => Char -> Producer Text m r -> Producer Text m r
intersperse c = go0
  where
    go0 p = do
        x <- lift (next p)
        case x of
            Left   r       -> return r
            Right (txt, p') -> do
                yield (T.intersperse c txt)
                go1 p'
    go1 p = do
        x <- lift (next p)
        case x of
            Left   r       -> return r
            Right (txt, p') -> do
                yield (T.singleton c)
                yield (T.intersperse c txt)
                go1 p'
{-# INLINABLE intersperse #-}


-- | Improper lens from unpacked 'Word8's to packaged 'ByteString's
pack :: Monad m => Lens' (Producer Char m r) (Producer Text m r)
pack k p = fmap _unpack (k (_pack p))
{-# INLINABLE pack #-}

-- | Improper lens from packed 'ByteString's to unpacked 'Word8's
unpack :: Monad m => Lens' (Producer Text m r) (Producer Char m r)
unpack k p = fmap _pack (k (_unpack p))
{-# INLINABLE unpack #-}

_pack :: Monad m => Producer Char m r -> Producer Text m r
_pack p = folds step id done (p^.PG.chunksOf defaultChunkSize)
  where
    step diffAs w8 = diffAs . (w8:)

    done diffAs = T.pack (diffAs [])
{-# INLINABLE _pack #-}

_unpack :: Monad m => Producer Text m r -> Producer Char m r
_unpack p = for p (each . T.unpack)
{-# INLINABLE _unpack #-}

defaultChunkSize :: Int
defaultChunkSize = 16384 - (sizeOf (undefined :: Int) `shiftL` 1)


-- | 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)
chunksOf n k p0 = fmap concats (k (FreeT (go p0)))
  where
    go p = do
        x <- next p
        return $ case x of
            Left   r       -> Pure r
            Right (txt, p') -> Free $ do
                p'' <- (yield txt >> p') ^. splitAt n
                return $ FreeT (go p'')
{-# INLINABLE chunksOf #-}


{-| Split a text stream into sub-streams delimited by characters that satisfy the
    predicate
-}
splitsWith
    :: (Monad m)
    => (Char -> Bool)
    -> Producer Text m r -> FreeT (Producer Text m) m r
splitsWith predicate p0 = FreeT (go0 p0)
  where
    go0 p = do
        x <- next p
        case x of
            Left   r       -> return (Pure r)
            Right (txt, p') ->
                if (T.null txt)
                then go0 p'
                else return $ Free $ do
                    p'' <-  (yield txt >> p') ^. span (not . predicate)
                    return $ FreeT (go1 p'')
    go1 p = do
        x <- nextChar p
        return $ case x of
            Left   r      -> Pure r
            Right (_, p') -> Free $ do
                    p'' <- p' ^. span (not . predicate)
                    return $ FreeT (go1 p'')
{-# INLINABLE splitsWith #-}

-- | 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)
splits c k p =
          fmap (intercalates (yield (T.singleton c))) (k (splitsWith (c ==) p))
{-# INLINABLE splits #-}

{-| Isomorphism between a stream of 'Text' and groups of equivalent 'Char's , using the
    given equivalence relation
-}
groupsBy
    :: Monad m
    => (Char -> Char -> Bool)
    -> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
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)
                      Right (bs, p') -> case T.uncons bs of
                             Nothing      -> go p'
                             Just (c, _) -> do return $ Free $ do
                                                 p'' <- (yield bs >> p')^.span (equals c)
                                                 return $ FreeT (go p'')
{-# INLINABLE groupsBy #-}


-- | Like 'groupsBy', where the equality predicate is ('==')
groups
    :: Monad m
    => Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groups = groupsBy (==)
{-# INLINABLE groups #-}



{-| Split a text stream into 'FreeT'-delimited lines
-}
lines
    :: (Monad m) => Lens' (Producer Text m r)  (FreeT (Producer Text m) m r)
lines k p = fmap _unlines (k (_lines p))
{-# INLINABLE lines #-}

unlines
    :: Monad m
    => Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
unlines k p = fmap _lines (k (_unlines p))
{-# INLINABLE unlines #-}

_lines :: Monad m
             => Producer Text m r -> FreeT (Producer Text m) m r
_lines p0 = FreeT (go0 p0)
    where
      go0 p = do
              x <- next p
              case x of
                  Left   r       -> return (Pure r)
                  Right (txt, p') ->
                      if (T.null txt)
                      then go0 p'
                      else return $ Free $ go1 (yield txt >> p')
      go1 p = do
              p' <- p ^. break ('\n' ==)
              return $ FreeT $ do
                  x  <- nextChar p'
                  case x of
                      Left   r      -> return $ Pure r
                      Right (_, p'') -> go0 p''
{-# INLINABLE _lines #-}

_unlines :: Monad m
         => FreeT (Producer Text m) m r -> Producer Text m r
_unlines = concats . maps (<* yield (T.singleton '\n'))
{-# INLINABLE _unlines #-}

-- | Split a text stream into 'FreeT'-delimited words. Note that 
-- roundtripping with e.g. @over words id@ eliminates extra space
-- characters as with @Prelude.unwords . Prelude.words@
words
    :: (Monad m) => Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
words k p = fmap _unwords (k (_words p))
{-# INLINABLE words #-}

unwords
    :: Monad m
    => Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
unwords k p = fmap _words (k (_unwords p))
{-# INLINABLE unwords #-}

_words :: (Monad m) => Producer Text m r -> FreeT (Producer Text m) m r
_words p = FreeT $ do
        x <- next (dropWhile isSpace p)
        return $ case x of
            Left   r       -> Pure r
            Right (bs, p') -> Free $ do
                p'' <-  (yield bs >> p') ^. break isSpace
                return (_words p'')
{-# INLINABLE _words #-}

_unwords :: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
_unwords = intercalates (yield $ T.singleton ' ')
{-# INLINABLE _unwords #-}


{-| 'intercalate' concatenates the 'FreeT'-delimited text streams after
    interspersing a text stream in between them
-}
intercalate
    :: (Monad m)
    => Producer Text m () -> FreeT (Producer Text m) m r -> Producer Text m r
intercalate p0 = go0
  where
    go0 f = do
        x <- lift (runFreeT f)
        case x of
            Pure r -> return r
            Free p -> do
                f' <- p
                go1 f'
    go1 f = do
        x <- lift (runFreeT f)
        case x of
            Pure r -> return r
            Free p -> do
                p0
                f' <- p
                go1 f'
{-# INLINABLE intercalate #-}



{- $reexports

    @Data.Text@ re-exports the 'Text' type.

    @Pipes.Parse@ re-exports 'input', 'concat', 'FreeT' (the type) and the 'Parse' synonym.
-}


type Lens' a b =  forall f . Functor f => (b -> f b) -> (a -> f a)