diff options
author | michaelt <what_is_it_to_do_anything@yahoo.com> | 2014-01-25 22:28:32 -0500 |
---|---|---|
committer | michaelt <what_is_it_to_do_anything@yahoo.com> | 2014-01-25 22:28:32 -0500 |
commit | 1677dc12093a9b128ba17085125e807c3e2b3d5a (patch) | |
tree | 58a0e52b58906c293c2967d2ad346eeb0f57cdec /Pipes | |
parent | 64e03122e6ecc4898cb1b193cdcf3b26d3e71b14 (diff) | |
download | text-pipes-1677dc12093a9b128ba17085125e807c3e2b3d5a.tar.gz text-pipes-1677dc12093a9b128ba17085125e807c3e2b3d5a.tar.zst text-pipes-1677dc12093a9b128ba17085125e807c3e2b3d5a.zip |
reformatted exports fwiw
Diffstat (limited to 'Pipes')
-rw-r--r-- | Pipes/Text.hs | 177 |
1 files changed, 100 insertions, 77 deletions
diff --git a/Pipes/Text.hs b/Pipes/Text.hs index 99e4ed6..4df2b5d 100644 --- a/Pipes/Text.hs +++ b/Pipes/Text.hs | |||
@@ -1,4 +1,4 @@ | |||
1 | {-# LANGUAGE RankNTypes, TypeFamilies, BangPatterns #-} | 1 | {-# LANGUAGE RankNTypes, TypeFamilies, BangPatterns, CPP #-} |
2 | #if __GLASGOW_HASKELL__ >= 702 | 2 | #if __GLASGOW_HASKELL__ >= 702 |
3 | {-# LANGUAGE Trustworthy #-} | 3 | {-# LANGUAGE Trustworthy #-} |
4 | #endif | 4 | #endif |
@@ -62,84 +62,95 @@ To stream from files, the following is perhaps more Prelude-like (note that it u | |||
62 | 62 | ||
63 | module Pipes.Text ( | 63 | module Pipes.Text ( |
64 | -- * Producers | 64 | -- * Producers |
65 | fromLazy, | 65 | fromLazy |
66 | stdin, | 66 | , stdin |
67 | fromHandle, | 67 | , fromHandle |
68 | readFile, | 68 | , readFile |
69 | stdinLn, | 69 | , stdinLn |
70 | 70 | ||
71 | -- * Consumers | 71 | -- * Consumers |
72 | stdout, | 72 | , stdout |
73 | stdoutLn, | 73 | , stdoutLn |
74 | toHandle, | 74 | , toHandle |
75 | writeFile, | 75 | , writeFile |
76 | 76 | ||
77 | -- * Pipes | 77 | -- * Pipes |
78 | map, | 78 | , map |
79 | concatMap, | 79 | , concatMap |
80 | take, | 80 | , take |
81 | drop, | 81 | , drop |
82 | takeWhile, | 82 | , takeWhile |
83 | dropWhile, | 83 | , dropWhile |
84 | filter, | 84 | , filter |
85 | scan, | 85 | , scan |
86 | encodeUtf8, | 86 | , encodeUtf8 |
87 | pack, | 87 | , pack |
88 | unpack, | 88 | , unpack |
89 | toCaseFold, | 89 | , toCaseFold |
90 | toLower, | 90 | , toLower |
91 | toUpper, | 91 | , toUpper |
92 | stripStart, | 92 | , stripStart |
93 | 93 | ||
94 | -- * Folds | 94 | -- * Folds |
95 | toLazy, | 95 | , toLazy |
96 | toLazyM, | 96 | , toLazyM |
97 | foldChars, | 97 | , foldChars |
98 | head, | 98 | , head |
99 | last, | 99 | , last |
100 | null, | 100 | , null |
101 | length, | 101 | , length |
102 | any, | 102 | , any |
103 | all, | 103 | , all |
104 | maximum, | 104 | , maximum |
105 | minimum, | 105 | , minimum |
106 | find, | 106 | , find |
107 | index, | 107 | , index |
108 | count, | 108 | , count |
109 | |||
110 | -- * Primitive Character Parsers | ||
111 | -- $parse | ||
112 | , nextChar | ||
113 | , drawChar | ||
114 | , unDrawChar | ||
115 | , peekChar | ||
116 | , isEndOfChars, | ||
117 | |||
118 | -- * Parsing Lenses | ||
119 | splitAt | ||
120 | , span | ||
121 | , break | ||
122 | , groupBy | ||
123 | , group | ||
124 | -- , word | ||
125 | -- , line | ||
126 | , decodeUtf8 | ||
127 | , decode | ||
128 | |||
129 | -- * FreeT Splitters | ||
130 | , chunksOf | ||
131 | , splitsWith | ||
132 | , split | ||
133 | -- , groupsBy | ||
134 | -- , groups | ||
135 | , lines | ||
136 | , words | ||
137 | |||
109 | 138 | ||
110 | -- * Splitters | ||
111 | splitAt, | ||
112 | chunksOf, | ||
113 | span, | ||
114 | break, | ||
115 | splitWith, | ||
116 | split, | ||
117 | groupBy, | ||
118 | group, | ||
119 | lines, | ||
120 | words, | ||
121 | decodeUtf8, | ||
122 | decode, | ||
123 | -- * Transformations | 139 | -- * Transformations |
124 | intersperse, | 140 | , intersperse |
141 | -- , packChars | ||
125 | 142 | ||
126 | -- * Joiners | 143 | -- * Joiners |
127 | intercalate, | 144 | , intercalate |
128 | unlines, | 145 | , unlines |
129 | unwords, | 146 | , unwords |
130 | 147 | -- * Re-exports | |
131 | -- * Character Parsers | ||
132 | -- $parse | ||
133 | nextChar, | ||
134 | drawChar, | ||
135 | unDrawChar, | ||
136 | peekChar, | ||
137 | isEndOfChars, | ||
138 | |||
139 | -- * Re-exports | ||
140 | -- $reexports | 148 | -- $reexports |
141 | module Data.Text, | 149 | , module Data.ByteString |
142 | module Pipes.Parse | 150 | , module Data.Text |
151 | , module Data.Profunctor | ||
152 | , module Data.Word | ||
153 | , module Pipes.Parse | ||
143 | ) where | 154 | ) where |
144 | 155 | ||
145 | import Control.Exception (throwIO, try) | 156 | import Control.Exception (throwIO, try) |
@@ -158,20 +169,21 @@ import Data.ByteString.Unsafe (unsafeTake, unsafeDrop) | |||
158 | import Data.ByteString (ByteString) | 169 | import Data.ByteString (ByteString) |
159 | import qualified Data.ByteString as B | 170 | import qualified Data.ByteString as B |
160 | import Data.Char (ord, isSpace) | 171 | import Data.Char (ord, isSpace) |
172 | import Data.Functor.Constant (Constant(Constant, getConstant)) | ||
161 | import Data.Functor.Identity (Identity) | 173 | import Data.Functor.Identity (Identity) |
174 | import Data.Profunctor (Profunctor) | ||
175 | import qualified Data.Profunctor | ||
162 | import qualified Data.List as List | 176 | import qualified Data.List as List |
163 | import Foreign.C.Error (Errno(Errno), ePIPE) | 177 | import Foreign.C.Error (Errno(Errno), ePIPE) |
164 | import qualified GHC.IO.Exception as G | 178 | import qualified GHC.IO.Exception as G |
165 | import Pipes | 179 | import Pipes |
166 | import qualified Pipes.ByteString as PB | 180 | import qualified Pipes.ByteString as PB |
167 | import qualified Pipes.ByteString as PBP | ||
168 | import qualified Pipes.Text.Internal as PE | 181 | import qualified Pipes.Text.Internal as PE |
169 | import Pipes.Text.Internal (Codec(..)) | 182 | import Pipes.Text.Internal (Codec(..)) |
170 | import Pipes.Text.Parse ( | 183 | import Pipes.Text.Parse (nextChar, drawChar, unDrawChar, peekChar, isEndOfChars ) |
171 | nextChar, drawChar, unDrawChar, peekChar, isEndOfChars ) | ||
172 | import Pipes.Core (respond, Server') | 184 | import Pipes.Core (respond, Server') |
173 | import qualified Pipes.Parse as PP | 185 | import qualified Pipes.Parse as PP |
174 | import Pipes.Parse ( FreeT) | 186 | import Pipes.Parse (Parser, concats, intercalates, FreeT) |
175 | import qualified Pipes.Safe.Prelude as Safe | 187 | import qualified Pipes.Safe.Prelude as Safe |
176 | import qualified Pipes.Safe as Safe | 188 | import qualified Pipes.Safe as Safe |
177 | import Pipes.Safe (MonadSafe(..), Base(..)) | 189 | import Pipes.Safe (MonadSafe(..), Base(..)) |
@@ -179,6 +191,7 @@ import qualified Pipes.Prelude as P | |||
179 | import qualified System.IO as IO | 191 | import qualified System.IO as IO |
180 | import Data.Char (isSpace) | 192 | import Data.Char (isSpace) |
181 | import Data.Word (Word8) | 193 | import Data.Word (Word8) |
194 | |||
182 | import Prelude hiding ( | 195 | import Prelude hiding ( |
183 | all, | 196 | all, |
184 | any, | 197 | any, |
@@ -318,6 +331,15 @@ writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m () | |||
318 | writeFile file = Safe.withFile file IO.WriteMode toHandle | 331 | writeFile file = Safe.withFile file IO.WriteMode toHandle |
319 | {-# INLINE writeFile #-} | 332 | {-# INLINE writeFile #-} |
320 | 333 | ||
334 | |||
335 | type Lens' a b = forall f . Functor f => (b -> f b) -> (a -> f a) | ||
336 | |||
337 | type Iso' a b = forall f p . (Functor f, Profunctor p) => p b (f b) -> p a (f a) | ||
338 | |||
339 | (^.) :: a -> ((b -> Constant b b) -> (a -> Constant b a)) -> b | ||
340 | a ^. lens = getConstant (lens Constant a) | ||
341 | |||
342 | |||
321 | -- | Apply a transformation to each 'Char' in the stream | 343 | -- | Apply a transformation to each 'Char' in the stream |
322 | map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r | 344 | map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r |
323 | map f = P.map (T.map f) | 345 | map f = P.map (T.map f) |
@@ -508,7 +530,7 @@ foldChars | |||
508 | :: Monad m | 530 | :: Monad m |
509 | => (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r | 531 | => (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r |
510 | foldChars step begin done = P.fold (T.foldl' step) begin done | 532 | foldChars step begin done = P.fold (T.foldl' step) begin done |
511 | {-# INLINABLE fold #-} | 533 | {-# INLINABLE foldChars #-} |
512 | 534 | ||
513 | -- | Retrieve the first 'Char' | 535 | -- | Retrieve the first 'Char' |
514 | head :: (Monad m) => Producer Text m () -> m (Maybe Char) | 536 | head :: (Monad m) => Producer Text m () -> m (Maybe Char) |
@@ -579,6 +601,7 @@ minimum = P.fold step Nothing id | |||
579 | Just c -> Just (min c (T.minimum txt)) | 601 | Just c -> Just (min c (T.minimum txt)) |
580 | {-# INLINABLE minimum #-} | 602 | {-# INLINABLE minimum #-} |
581 | 603 | ||
604 | |||
582 | -- | Find the first element in the stream that matches the predicate | 605 | -- | Find the first element in the stream that matches the predicate |
583 | find | 606 | find |
584 | :: (Monad m) | 607 | :: (Monad m) |
@@ -699,12 +722,12 @@ break predicate = span (not . predicate) | |||
699 | {-| Split a text stream into sub-streams delimited by characters that satisfy the | 722 | {-| Split a text stream into sub-streams delimited by characters that satisfy the |
700 | predicate | 723 | predicate |
701 | -} | 724 | -} |
702 | splitWith | 725 | splitsWith |
703 | :: (Monad m) | 726 | :: (Monad m) |
704 | => (Char -> Bool) | 727 | => (Char -> Bool) |
705 | -> Producer Text m r | 728 | -> Producer Text m r |
706 | -> PP.FreeT (Producer Text m) m r | 729 | -> PP.FreeT (Producer Text m) m r |
707 | splitWith predicate p0 = PP.FreeT (go0 p0) | 730 | splitsWith predicate p0 = PP.FreeT (go0 p0) |
708 | where | 731 | where |
709 | go0 p = do | 732 | go0 p = do |
710 | x <- next p | 733 | x <- next p |
@@ -723,14 +746,14 @@ splitWith predicate p0 = PP.FreeT (go0 p0) | |||
723 | Right (_, p') -> PP.Free $ do | 746 | Right (_, p') -> PP.Free $ do |
724 | p'' <- span (not . predicate) p' | 747 | p'' <- span (not . predicate) p' |
725 | return $ PP.FreeT (go1 p'') | 748 | return $ PP.FreeT (go1 p'') |
726 | {-# INLINABLE splitWith #-} | 749 | {-# INLINABLE splitsWith #-} |
727 | 750 | ||
728 | -- | Split a text stream using the given 'Char' as the delimiter | 751 | -- | Split a text stream using the given 'Char' as the delimiter |
729 | split :: (Monad m) | 752 | split :: (Monad m) |
730 | => Char | 753 | => Char |
731 | -> Producer Text m r | 754 | -> Producer Text m r |
732 | -> FreeT (Producer Text m) m r | 755 | -> FreeT (Producer Text m) m r |
733 | split c = splitWith (c ==) | 756 | split c = splitsWith (c ==) |
734 | {-# INLINABLE split #-} | 757 | {-# INLINABLE split #-} |
735 | 758 | ||
736 | {-| Group a text stream into 'FreeT'-delimited text streams using the supplied | 759 | {-| Group a text stream into 'FreeT'-delimited text streams using the supplied |