aboutsummaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--Data/Text/Pipes.hs863
-rw-r--r--LICENSE30
-rw-r--r--Setup.hs2
-rw-r--r--text-pipes.cabal33
4 files changed, 928 insertions, 0 deletions
diff --git a/Data/Text/Pipes.hs b/Data/Text/Pipes.hs
new file mode 100644
index 0000000..e9b5488
--- /dev/null
+++ b/Data/Text/Pipes.hs
@@ -0,0 +1,863 @@
1{-# LANGUAGE RankNTypes, TypeFamilies #-}
2
3{-| This module provides @pipes@ utilities for \"byte streams\", which are
4 streams of strict 'Text's chunks. Use byte streams to interact
5 with both 'IO.Handle's and lazy 'Text's.
6
7 To stream to or from 'IO.Handle's, use 'fromHandle' or 'toHandle'. For
8 example, the following program copies data from one file to another:
9
10> import Pipes
11> import qualified Pipes.Text as P
12> import System.IO
13>
14> main =
15> withFile "inFile.txt" ReadMode $ \hIn ->
16> withFile "outFile.txt" WriteMode $ \hOut ->
17> runEffect $ P.fromHandle hIn >-> P.toHandle hOut
18
19 You can stream to and from 'stdin' and 'stdout' using the predefined 'stdin'
20 and 'stdout' proxies, like in the following \"echo\" program:
21
22> main = runEffect $ P.stdin >-> P.stdout
23
24 You can also translate pure lazy 'TL.Text's to and from proxies:
25
26> import qualified Data.Text.Lazy as TL
27>
28> main = runEffect $ P.fromLazy (TL.pack "Hello, world!\n") >-> P.stdout
29
30 In addition, this module provides many functions equivalent to lazy
31 'Text' functions so that you can transform or fold byte streams. For
32 example, to stream only the first three lines of 'stdin' to 'stdout' you
33 would write:
34
35> import Pipes
36> import qualified Pipes.Text as PT
37> import qualified Pipes.Parse as PP
38>
39> main = runEffect $ takeLines 3 PB.stdin >-> PT.stdout
40> where
41> takeLines n = PB.unlines . PP.takeFree n . PT.lines
42
43 The above program will never bring more than one chunk (~ 32 KB) into
44 memory, no matter how long the lines are.
45
46 Note that functions in this library are designed to operate on streams that
47 are insensitive to chunk boundaries. This means that they may freely split
48 chunks into smaller chunks and /discard empty chunks/. However, they will
49 /never concatenate chunks/ in order to provide strict upper bounds on memory
50 usage.
51-}
52
53module Data.Text.Pipes (
54 -- * Producers
55 fromLazy,
56 stdin,
57 fromHandle,
58 readFile,
59 stdinLn,
60-- hGetSome,
61-- hGet,
62
63 -- * Servers
64-- hGetSomeN,
65-- hGetN,
66
67 -- * Consumers
68 stdout,
69 stdoutLn,
70 toHandle,
71 writeFile,
72
73 -- * Pipes
74 map,
75 concatMap,
76 take,
77 drop,
78 takeWhile,
79 dropWhile,
80 filter,
81-- elemIndices,
82-- findIndices,
83 scan,
84
85 -- * Folds
86 toLazy,
87 toLazyM,
88 fold,
89 head,
90 last,
91 null,
92 length,
93 any,
94 all,
95 maximum,
96 minimum,
97-- elem,
98-- notElem,
99 find,
100 index,
101-- elemIndex,
102-- findIndex,
103-- count,
104
105 -- * Splitters
106 splitAt,
107 chunksOf,
108 span,
109 break,
110 splitWith,
111 split,
112 groupBy,
113 group,
114 lines,
115 words,
116
117 -- * Transformations
118 intersperse,
119
120 -- * Joiners
121 intercalate,
122 unlines,
123 unwords,
124
125 -- * Low-level Parsers
126 -- $parse
127 nextByte,
128 drawByte,
129 unDrawByte,
130 peekByte,
131 isEndOfBytes,
132-- takeWhile',
133
134 -- * Re-exports
135 -- $reexports
136 module Data.Text,
137-- module Data.Word,
138 module Pipes.Parse
139 ) where
140
141import Control.Exception (throwIO, try)
142import Control.Monad (liftM, unless)
143import Control.Monad.Trans.State.Strict (StateT)
144import qualified Data.Text as T
145import qualified Data.Text.IO as T
146import Data.Text (Text)
147import qualified Data.Text.Lazy as TL
148import qualified Data.Text.Lazy.IO as TL
149import Data.Text.Lazy.Internal (foldrChunks, defaultChunkSize)
150import Data.ByteString.Unsafe (unsafeTake, unsafeDrop)
151import Data.Char (ord)
152import Data.Functor.Identity (Identity)
153import qualified Data.List as List
154import Foreign.C.Error (Errno(Errno), ePIPE)
155import qualified GHC.IO.Exception as G
156import Pipes
157import qualified Pipes.ByteString.Parse as PBP
158import Pipes.ByteString.Parse (
159 nextByte, drawByte, unDrawByte, peekByte, isEndOfBytes )
160import Pipes.Core (respond, Server')
161import qualified Pipes.Parse as PP
162import Pipes.Parse (input, concat, FreeT)
163import qualified Pipes.Safe.Prelude as Safe
164import qualified Pipes.Safe as Safe
165import Pipes.Safe (MonadSafe(..), Base(..))
166import qualified Pipes.Prelude as P
167import qualified System.IO as IO
168import Data.Char (isSpace)
169import Prelude hiding (
170 all,
171 any,
172 break,
173 concat,
174 concatMap,
175 drop,
176 dropWhile,
177 elem,
178 filter,
179 head,
180 last,
181 lines,
182 length,
183 map,
184 maximum,
185 minimum,
186 notElem,
187 null,
188 readFile,
189 span,
190 splitAt,
191 take,
192 takeWhile,
193 unlines,
194 unwords,
195 words,
196 writeFile )
197
198-- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's
199fromLazy :: (Monad m) => TL.Text -> Producer' Text m ()
200fromLazy = foldrChunks (\e a -> yield e >> a) (return ())
201{-# INLINABLE fromLazy #-}
202
203-- | Stream bytes from 'stdin'
204stdin :: MonadIO m => Producer' Text m ()
205stdin = fromHandle IO.stdin
206{-# INLINABLE stdin #-}
207
208-- | Convert a 'IO.Handle' into a byte stream using a default chunk size
209fromHandle :: MonadIO m => IO.Handle -> Producer' Text m ()
210fromHandle h = go where
211 go = do txt <- liftIO (T.hGetChunk h)
212 unless (T.null txt) $ do yield txt
213 go
214{-# INLINABLE fromHandle#-}
215
216readFile :: (MonadSafe m, Base m ~ IO) => FilePath -> Producer' Text m ()
217readFile file = Safe.withFile file IO.ReadMode fromHandle
218{-# INLINABLE readFile #-}
219
220stdinLn :: MonadIO m => Producer' Text m ()
221stdinLn = go
222 where
223 go = do
224 eof <- liftIO (IO.hIsEOF IO.stdin)
225 unless eof $ do
226 txt <- liftIO (T.hGetLine IO.stdin)
227 yield txt
228 go
229
230{-| Convert a handle into a byte stream using a fixed chunk size
231
232 'hGet' waits until exactly the requested number of bytes are available for
233 each chunk.
234-}
235-- hGet :: MonadIO m => Int -> IO.Handle -> Producer' Text m ()
236-- hGet size h = go where
237-- go = do
238-- eof <- liftIO (IO.hIsEOF h)
239-- if eof
240-- then return ()
241-- else do
242-- bs <- liftIO (T.hGet h size)
243-- yield bs
244-- go
245-- {-# INLINABLE hGet #-}
246
247{-| Like 'hGetSome', except you can vary the maximum chunk size for each request
248-}
249-- hGetSomeN :: MonadIO m => IO.Handle -> Int -> Server' Int Text m ()
250-- hGetSomeN h = go where
251-- go size = do
252-- eof <- liftIO (IO.hIsEOF h)
253-- if eof
254-- then return ()
255-- else do
256-- bs <- liftIO (T.hGetSome h size)
257-- size2 <- respond bs
258-- go size2
259-- {-# INLINABLE hGetSomeN #-}
260--
261-- -- | Like 'hGet', except you can vary the chunk size for each request
262-- hGetN :: MonadIO m => IO.Handle -> Int -> Server' Int Text m ()
263-- hGetN h = go where
264-- go size = do
265-- eof <- liftIO (IO.hIsEOF h)
266-- if eof
267-- then return ()
268-- else do
269-- bs <- liftIO (T.hGet h size)
270-- size2 <- respond bs
271-- go size2
272-- {-# INLINABLE hGetN #-}
273
274{-| Stream bytes to 'stdout'
275
276 Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
277
278 Note: For best performance, use @(for source (liftIO . putStr))@ instead of
279 @(source >-> stdout)@.
280-}
281stdout :: MonadIO m => Consumer' Text m ()
282stdout = go
283 where
284 go = do
285 txt <- await
286 x <- liftIO $ try (T.putStr txt)
287 case x of
288 Left (G.IOError { G.ioe_type = G.ResourceVanished
289 , G.ioe_errno = Just ioe })
290 | Errno ioe == ePIPE
291 -> return ()
292 Left e -> liftIO (throwIO e)
293 Right () -> go
294{-# INLINABLE stdout #-}
295
296stdoutLn :: (MonadIO m) => Consumer' Text m ()
297stdoutLn = go
298 where
299 go = do
300 str <- await
301 x <- liftIO $ try (T.putStrLn str)
302 case x of
303 Left (G.IOError { G.ioe_type = G.ResourceVanished
304 , G.ioe_errno = Just ioe })
305 | Errno ioe == ePIPE
306 -> return ()
307 Left e -> liftIO (throwIO e)
308 Right () -> go
309{-# INLINABLE stdoutLn #-}
310
311{-| Convert a byte stream into a 'Handle'
312
313 Note: For best performance, use @(for source (liftIO . hPutStr handle))@
314 instead of @(source >-> toHandle handle)@.
315-}
316toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
317toHandle h = for cat (liftIO . T.hPutStr h)
318{-# INLINABLE toHandle #-}
319
320writeFile :: (MonadSafe m, Base m ~ IO) => FilePath -> Consumer' Text m ()
321writeFile file = Safe.withFile file IO.WriteMode toHandle
322
323-- | Apply a transformation to each 'Char' in the stream
324map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
325map f = P.map (T.map f)
326{-# INLINABLE map #-}
327
328-- | Map a function over the byte stream and concatenate the results
329concatMap
330 :: (Monad m) => (Char -> Text) -> Pipe Text Text m r
331concatMap f = P.map (T.concatMap f)
332{-# INLINABLE concatMap #-}
333
334-- | @(take n)@ only allows @n@ bytes to pass
335take :: (Monad m, Integral a) => a -> Pipe Text Text m ()
336take n0 = go n0 where
337 go n
338 | n <= 0 = return ()
339 | otherwise = do
340 bs <- await
341 let len = fromIntegral (T.length bs)
342 if (len > n)
343 then yield (T.take (fromIntegral n) bs)
344 else do
345 yield bs
346 go (n - len)
347{-# INLINABLE take #-}
348
349-- | @(dropD n)@ drops the first @n@ bytes
350drop :: (Monad m, Integral a) => a -> Pipe Text Text m r
351drop n0 = go n0 where
352 go n
353 | n <= 0 = cat
354 | otherwise = do
355 bs <- await
356 let len = fromIntegral (T.length bs)
357 if (len >= n)
358 then do
359 yield (T.drop (fromIntegral n) bs)
360 cat
361 else go (n - len)
362{-# INLINABLE drop #-}
363
364-- | Take bytes until they fail the predicate
365takeWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m ()
366takeWhile predicate = go
367 where
368 go = do
369 bs <- await
370 let (prefix, suffix) = T.span predicate bs
371 if (T.null suffix)
372 then do
373 yield bs
374 go
375 else yield prefix
376{-# INLINABLE takeWhile #-}
377
378-- | Drop bytes until they fail the predicate
379dropWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
380dropWhile predicate = go where
381 go = do
382 bs <- await
383 case T.findIndex (not . predicate) bs of
384 Nothing -> go
385 Just i -> do
386 yield (T.drop i bs)
387 cat
388{-# INLINABLE dropWhile #-}
389
390-- | Only allows 'Char's to pass if they satisfy the predicate
391filter :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
392filter predicate = P.map (T.filter predicate)
393{-# INLINABLE filter #-}
394
395-- | Stream all indices whose elements match the given 'Char'
396-- elemIndices :: (Monad m, Num n) => Char -> Pipe Text n m r
397-- elemIndices w8 = findIndices (w8 ==)
398-- {-# INLINABLE elemIndices #-}
399
400-- | Stream all indices whose elements satisfy the given predicate
401-- findIndices :: (Monad m, Num n) => (Char -> Bool) -> Pipe Text n m r
402-- findIndices predicate = go 0
403-- where
404-- go n = do
405-- bs <- await
406-- each $ List.map (\i -> n + fromIntegral i) (T.findIndices predicate bs)
407-- go $! n + fromIntegral (T.length bs)
408-- {-# INLINABLE findIndices #-}
409
410-- | Strict left scan over the bytes
411scan
412 :: (Monad m)
413 => (Char -> Char -> Char) -> Char -> Pipe Text Text m r
414scan step begin = go begin
415 where
416 go w8 = do
417 bs <- await
418 let bs' = T.scanl step w8 bs
419 w8' = T.last bs'
420 yield bs'
421 go w8'
422{-# INLINABLE scan #-}
423
424{-| Fold a pure 'Producer' of strict 'Text's into a lazy
425 'TL.Text'
426-}
427toLazy :: Producer Text Identity () -> TL.Text
428toLazy = TL.fromChunks . P.toList
429{-# INLINABLE toLazy #-}
430
431{-| Fold an effectful 'Producer' of strict 'Text's into a lazy
432 'TL.Text'
433
434 Note: 'toLazyM' is not an idiomatic use of @pipes@, but I provide it for
435 simple testing purposes. Idiomatic @pipes@ style consumes the chunks
436 immediately as they are generated instead of loading them all into memory.
437-}
438toLazyM :: (Monad m) => Producer Text m () -> m TL.Text
439toLazyM = liftM TL.fromChunks . P.toListM
440{-# INLINABLE toLazyM #-}
441
442-- | Reduce the stream of bytes using a strict left fold
443fold
444 :: Monad m
445 => (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r
446fold step begin done = P.fold (\x bs -> T.foldl' step x bs) begin done
447{-# INLINABLE fold #-}
448
449-- | Retrieve the first 'Char'
450head :: (Monad m) => Producer Text m () -> m (Maybe Char)
451head = go
452 where
453 go p = do
454 x <- nextChar p
455 case x of
456 Left _ -> return Nothing
457 Right (w8, _) -> return (Just w8)
458{-# INLINABLE head #-}
459
460-- | Retrieve the last 'Char'
461last :: (Monad m) => Producer Text m () -> m (Maybe Char)
462last = go Nothing
463 where
464 go r p = do
465 x <- next p
466 case x of
467 Left () -> return r
468 Right (bs, p') ->
469 if (T.null bs)
470 then go r p'
471 else go (Just $ T.last bs) p'
472 -- TODO: Change this to 'unsafeLast' when bytestring-0.10.2.0
473 -- becomes more widespread
474{-# INLINABLE last #-}
475
476-- | Determine if the stream is empty
477null :: (Monad m) => Producer Text m () -> m Bool
478null = P.all T.null
479{-# INLINABLE null #-}
480
481-- | Count the number of bytes
482length :: (Monad m, Num n) => Producer Text m () -> m n
483length = P.fold (\n bs -> n + fromIntegral (T.length bs)) 0 id
484{-# INLINABLE length #-}
485
486-- | Fold that returns whether 'M.Any' received 'Char's satisfy the predicate
487any :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
488any predicate = P.any (T.any predicate)
489{-# INLINABLE any #-}
490
491-- | Fold that returns whether 'M.All' received 'Char's satisfy the predicate
492all :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
493all predicate = P.all (T.all predicate)
494{-# INLINABLE all #-}
495
496-- | Return the maximum 'Char' within a byte stream
497maximum :: (Monad m) => Producer Text m () -> m (Maybe Char)
498maximum = P.fold step Nothing id
499 where
500 step mw8 bs =
501 if (T.null bs)
502 then mw8
503 else Just $ case mw8 of
504 Nothing -> T.maximum bs
505 Just w8 -> max w8 (T.maximum bs)
506{-# INLINABLE maximum #-}
507
508-- | Return the minimum 'Char' within a byte stream
509minimum :: (Monad m) => Producer Text m () -> m (Maybe Char)
510minimum = P.fold step Nothing id
511 where
512 step mw8 bs =
513 if (T.null bs)
514 then mw8
515 else case mw8 of
516 Nothing -> Just (T.minimum bs)
517 Just w8 -> Just (min w8 (T.minimum bs))
518{-# INLINABLE minimum #-}
519
520-- | Determine whether any element in the byte stream matches the given 'Char'
521-- elem :: (Monad m) => Char -> Producer Text m () -> m Bool
522-- elem w8 = P.any (T.elem w8)
523-- {-# INLINABLE elem #-}
524--
525-- {-| Determine whether all elements in the byte stream do not match the given
526-- 'Char'
527-- -}
528-- notElem :: (Monad m) => Char -> Producer Text m () -> m Bool
529-- notElem w8 = P.all (T.notElem w8)
530-- {-# INLINABLE notElem #-}
531
532-- | Find the first element in the stream that matches the predicate
533find
534 :: (Monad m)
535 => (Char -> Bool) -> Producer Text m () -> m (Maybe Char)
536find predicate p = head (p >-> filter predicate)
537{-# INLINABLE find #-}
538
539-- | Index into a byte stream
540index
541 :: (Monad m, Integral a)
542 => a-> Producer Text m () -> m (Maybe Char)
543index n p = head (p >-> drop n)
544{-# INLINABLE index #-}
545
546-- | Find the index of an element that matches the given 'Char'
547-- elemIndex
548-- :: (Monad m, Num n) => Char -> Producer Text m () -> m (Maybe n)
549-- elemIndex w8 = findIndex (w8 ==)
550-- {-# INLINABLE elemIndex #-}
551
552-- | Store the first index of an element that satisfies the predicate
553-- findIndex
554-- :: (Monad m, Num n)
555-- => (Char -> Bool) -> Producer Text m () -> m (Maybe n)
556-- findIndex predicate p = P.head (p >-> findIndices predicate)
557-- {-# INLINABLE findIndex #-}
558--
559-- -- | Store a tally of how many elements match the given 'Char'
560-- count :: (Monad m, Num n) => Char -> Producer Text m () -> m n
561-- count w8 p = P.fold (+) 0 id (p >-> P.map (fromIntegral . T.count w8))
562-- {-# INLINABLE count #-}
563
564-- | Splits a 'Producer' after the given number of bytes
565splitAt
566 :: (Monad m, Integral n)
567 => n
568 -> Producer Text m r
569 -> Producer' Text m (Producer Text m r)
570splitAt = go
571 where
572 go 0 p = return p
573 go n p = do
574 x <- lift (next p)
575 case x of
576 Left r -> return (return r)
577 Right (bs, p') -> do
578 let len = fromIntegral (T.length bs)
579 if (len <= n)
580 then do
581 yield bs
582 go (n - len) p'
583 else do
584 let (prefix, suffix) = T.splitAt (fromIntegral n) bs
585 yield prefix
586 return (yield suffix >> p')
587{-# INLINABLE splitAt #-}
588
589-- | Split a byte stream into 'FreeT'-delimited byte streams of fixed size
590chunksOf
591 :: (Monad m, Integral n)
592 => n -> Producer Text m r -> FreeT (Producer Text m) m r
593chunksOf n p0 = PP.FreeT (go p0)
594 where
595 go p = do
596 x <- next p
597 return $ case x of
598 Left r -> PP.Pure r
599 Right (bs, p') -> PP.Free $ do
600 p'' <- splitAt n (yield bs >> p')
601 return $ PP.FreeT (go p'')
602{-# INLINABLE chunksOf #-}
603
604{-| Split a byte stream in two, where the first byte stream is the longest
605 consecutive group of bytes that satisfy the predicate
606-}
607span
608 :: (Monad m)
609 => (Char -> Bool)
610 -> Producer Text m r
611 -> Producer' Text m (Producer Text m r)
612span predicate = go
613 where
614 go p = do
615 x <- lift (next p)
616 case x of
617 Left r -> return (return r)
618 Right (bs, p') -> do
619 let (prefix, suffix) = T.span predicate bs
620 if (T.null suffix)
621 then do
622 yield bs
623 go p'
624 else do
625 yield prefix
626 return (yield suffix >> p')
627{-# INLINABLE span #-}
628
629{-| Split a byte stream in two, where the first byte stream is the longest
630 consecutive group of bytes that don't satisfy the predicate
631-}
632break
633 :: (Monad m)
634 => (Char -> Bool)
635 -> Producer Text m r
636 -> Producer Text m (Producer Text m r)
637break predicate = span (not . predicate)
638{-# INLINABLE break #-}
639
640{-| Split a byte stream into sub-streams delimited by bytes that satisfy the
641 predicate
642-}
643splitWith
644 :: (Monad m)
645 => (Char -> Bool)
646 -> Producer Text m r
647 -> PP.FreeT (Producer Text m) m r
648splitWith predicate p0 = PP.FreeT (go0 p0)
649 where
650 go0 p = do
651 x <- next p
652 case x of
653 Left r -> return (PP.Pure r)
654 Right (bs, p') ->
655 if (T.null bs)
656 then go0 p'
657 else return $ PP.Free $ do
658 p'' <- span (not . predicate) (yield bs >> p')
659 return $ PP.FreeT (go1 p'')
660 go1 p = do
661 x <- nextChar p
662 return $ case x of
663 Left r -> PP.Pure r
664 Right (_, p') -> PP.Free $ do
665 p'' <- span (not . predicate) p'
666 return $ PP.FreeT (go1 p'')
667{-# INLINABLE splitWith #-}
668
669-- | Split a byte stream using the given 'Char' as the delimiter
670split :: (Monad m)
671 => Char
672 -> Producer Text m r
673 -> FreeT (Producer Text m) m r
674split w8 = splitWith (w8 ==)
675{-# INLINABLE split #-}
676
677{-| Group a byte stream into 'FreeT'-delimited byte streams using the supplied
678 equality predicate
679-}
680groupBy
681 :: (Monad m)
682 => (Char -> Char -> Bool)
683 -> Producer Text m r
684 -> FreeT (Producer Text m) m r
685groupBy equal p0 = PP.FreeT (go p0)
686 where
687 go p = do
688 x <- next p
689 case x of
690 Left r -> return (PP.Pure r)
691 Right (bs, p') -> case (T.uncons bs) of
692 Nothing -> go p'
693 Just (w8, _) -> do
694 return $ PP.Free $ do
695 p'' <- span (equal w8) (yield bs >> p')
696 return $ PP.FreeT (go p'')
697{-# INLINABLE groupBy #-}
698
699-- | Group a byte stream into 'FreeT'-delimited byte streams of identical bytes
700group
701 :: (Monad m) => Producer Text m r -> FreeT (Producer Text m) m r
702group = groupBy (==)
703{-# INLINABLE group #-}
704
705{-| Split a byte stream into 'FreeT'-delimited lines
706
707 Note: This function is purely for demonstration purposes since it assumes a
708 particular encoding. You should prefer the 'Data.Text.Text' equivalent of
709 this function from the upcoming @pipes-text@ library.
710-}
711lines
712 :: (Monad m) => Producer Text m r -> FreeT (Producer Text m) m r
713lines p0 = PP.FreeT (go0 p0)
714 where
715 go0 p = do
716 x <- next p
717 case x of
718 Left r -> return (PP.Pure r)
719 Right (bs, p') ->
720 if (T.null bs)
721 then go0 p'
722 else return $ PP.Free $ go1 (yield bs >> p')
723 go1 p = do
724 p' <- break ('\n' ==) p
725 return $ PP.FreeT (go2 p')
726 go2 p = do
727 x <- nextChar p
728 return $ case x of
729 Left r -> PP.Pure r
730 Right (_, p') -> PP.Free (go1 p')
731{-# INLINABLE lines #-}
732nextChar = undefined
733{-| Split a byte stream into 'FreeT'-delimited words
734
735 Note: This function is purely for demonstration purposes since it assumes a
736 particular encoding. You should prefer the 'Data.Text.Text' equivalent of
737 this function from the upcoming @pipes-text@ library.
738-}
739words
740 :: (Monad m) => Producer Text m r -> FreeT (Producer Text m) m r
741words p0 = removeEmpty (splitWith isSpace p0)
742 where
743 removeEmpty f = PP.FreeT $ do
744 x <- PP.runFreeT f
745 case x of
746 PP.Pure r -> return (PP.Pure r)
747 PP.Free p -> do
748 y <- next p
749 case y of
750 Left f' -> PP.runFreeT (removeEmpty f')
751 Right (bs, p') -> return $ PP.Free $ do
752 yield bs
753 f' <- p'
754 return (removeEmpty f')
755{-# INLINABLE words #-}
756
757-- | Intersperse a 'Char' in between the bytes of the byte stream
758intersperse
759 :: (Monad m) => Char -> Producer Text m r -> Producer Text m r
760intersperse w8 = go0
761 where
762 go0 p = do
763 x <- lift (next p)
764 case x of
765 Left r -> return r
766 Right (bs, p') -> do
767 yield (T.intersperse w8 bs)
768 go1 p'
769 go1 p = do
770 x <- lift (next p)
771 case x of
772 Left r -> return r
773 Right (bs, p') -> do
774 yield (T.singleton w8)
775 yield (T.intersperse w8 bs)
776 go1 p'
777{-# INLINABLE intersperse #-}
778
779{-| 'intercalate' concatenates the 'FreeT'-delimited byte streams after
780 interspersing a byte stream in between them
781-}
782intercalate
783 :: (Monad m)
784 => Producer Text m ()
785 -> FreeT (Producer Text m) m r
786 -> Producer Text m r
787intercalate p0 = go0
788 where
789 go0 f = do
790 x <- lift (PP.runFreeT f)
791 case x of
792 PP.Pure r -> return r
793 PP.Free p -> do
794 f' <- p
795 go1 f'
796 go1 f = do
797 x <- lift (PP.runFreeT f)
798 case x of
799 PP.Pure r -> return r
800 PP.Free p -> do
801 p0
802 f' <- p
803 go1 f'
804{-# INLINABLE intercalate #-}
805
806{-| Join 'FreeT'-delimited lines into a byte stream
807
808 Note: This function is purely for demonstration purposes since it assumes a
809 particular encoding. You should prefer the 'Data.Text.Text' equivalent of
810 this function from the upcoming @pipes-text@ library.
811-}
812unlines
813 :: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
814unlines = go
815 where
816 go f = do
817 x <- lift (PP.runFreeT f)
818 case x of
819 PP.Pure r -> return r
820 PP.Free p -> do
821 f' <- p
822 yield $ T.singleton '\n'
823 go f'
824{-# INLINABLE unlines #-}
825
826{-| Join 'FreeT'-delimited words into a byte stream
827
828 Note: This function is purely for demonstration purposes since it assumes a
829 particular encoding. You should prefer the 'Data.Text.Text' equivalent of
830 this function from the upcoming @pipes-text@ library.
831-}
832unwords
833 :: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
834unwords = intercalate (yield $ T.pack " ")
835{-# INLINABLE unwords #-}
836
837{- $parse
838 The following parsing utilities are single-byte analogs of the ones found
839 in @pipes-parse@.
840-}
841
842{-| Take bytes until they fail the predicate
843
844 Unlike 'takeWhile', this 'PP.unDraw's unused bytes
845-}
846-- takeWhile'
847-- :: (Monad m)
848-- => (Char -> Bool)
849-- -> Pipe Text Text (StateT (Producer Text m r) m) ()
850-- takeWhile' = PBP.takeWhile
851-- {-# INLINABLE takeWhile' #-}
852-- {-# DEPRECATED takeWhile' "Use Pipes.Text.Parse.takeWhile instead" #-}
853
854{- $reexports
855 "Pipes.Text.Parse" re-exports 'nextByte', 'drawByte', 'unDrawByte',
856 'peekByte', and 'isEndOfBytes'.
857
858 @Data.Text@ re-exports the 'Text' type.
859
860 @Data.Word@ re-exports the 'Char' type.
861
862 @Pipes.Parse@ re-exports 'input', 'concat', and 'FreeT' (the type).
863-} \ No newline at end of file
diff --git a/LICENSE b/LICENSE
new file mode 100644
index 0000000..519dd59
--- /dev/null
+++ b/LICENSE
@@ -0,0 +1,30 @@
1Copyright (c) 2013, michaelt
2
3All rights reserved.
4
5Redistribution and use in source and binary forms, with or without
6modification, are permitted provided that the following conditions are met:
7
8 * Redistributions of source code must retain the above copyright
9 notice, this list of conditions and the following disclaimer.
10
11 * Redistributions in binary form must reproduce the above
12 copyright notice, this list of conditions and the following
13 disclaimer in the documentation and/or other materials provided
14 with the distribution.
15
16 * Neither the name of michaelt nor the names of other
17 contributors may be used to endorse or promote products derived
18 from this software without specific prior written permission.
19
20THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
23A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
24OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
25SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
26LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
27DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
28THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
29(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
30OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
diff --git a/Setup.hs b/Setup.hs
new file mode 100644
index 0000000..9a994af
--- /dev/null
+++ b/Setup.hs
@@ -0,0 +1,2 @@
1import Distribution.Simple
2main = defaultMain
diff --git a/text-pipes.cabal b/text-pipes.cabal
new file mode 100644
index 0000000..1d73a7b
--- /dev/null
+++ b/text-pipes.cabal
@@ -0,0 +1,33 @@
1-- Initial text-pipes.cabal generated by cabal init. For further
2-- documentation, see http://haskell.org/cabal/users-guide/
3
4name: text-pipes
5version: 0.1.0.0
6synopsis: Text pipes.
7-- description:
8homepage: github.com/michaelt/text-pipes
9license: BSD3
10license-file: LICENSE
11author: michaelt
12maintainer: what_is_it_to_do_anything@yahoo.com
13-- copyright:
14category: Text
15build-type: Simple
16-- extra-source-files:
17cabal-version: >=1.10
18
19library
20 exposed-modules: Data.Text.Pipes
21 -- other-modules:
22 other-extensions: RankNTypes
23 build-depends: base >= 4 && < 5 ,
24 transformers >= 0.2.0.0 && < 0.4,
25 pipes >=4.0 && < 4.2,
26 pipes-parse >=2.0 && < 2.1,
27 pipes-safe,
28 pipes-bytestring >= 1.0 && < 1.1,
29 transformers >= 0.3 && < 0.4,
30 text >=0.11 && < 0.12,
31 bytestring >=0.10 && < 0.11
32 -- hs-source-dirs:
33 default-language: Haskell2010 \ No newline at end of file