diff options
author | michaelt <what_is_it_to_do_anything@yahoo.com> | 2014-02-05 00:42:35 -0500 |
---|---|---|
committer | michaelt <what_is_it_to_do_anything@yahoo.com> | 2014-02-05 00:42:35 -0500 |
commit | 167f880504e05b19d3487c7ba701afa9633a2f41 (patch) | |
tree | 23eecc37d471915254d6ef6f3314e14b6bb2719f | |
parent | 4da91c37355b3d688c9dfc6f92ae92266ad4e883 (diff) | |
download | text-pipes-167f880504e05b19d3487c7ba701afa9633a2f41.tar.gz text-pipes-167f880504e05b19d3487c7ba701afa9633a2f41.tar.zst text-pipes-167f880504e05b19d3487c7ba701afa9633a2f41.zip |
scrapped stdinLn etc. Improved haddocks
-rw-r--r-- | Pipes/Text.hs | 103 |
1 files changed, 29 insertions, 74 deletions
diff --git a/Pipes/Text.hs b/Pipes/Text.hs index 796f672..bbf200f 100644 --- a/Pipes/Text.hs +++ b/Pipes/Text.hs | |||
@@ -66,11 +66,9 @@ module Pipes.Text ( | |||
66 | , stdin | 66 | , stdin |
67 | , fromHandle | 67 | , fromHandle |
68 | , readFile | 68 | , readFile |
69 | , stdinLn | ||
70 | 69 | ||
71 | -- * Consumers | 70 | -- * Consumers |
72 | , stdout | 71 | , stdout |
73 | , stdoutLn | ||
74 | , toHandle | 72 | , toHandle |
75 | , writeFile | 73 | , writeFile |
76 | 74 | ||
@@ -275,27 +273,6 @@ readFile :: MonadSafe m => FilePath -> Producer Text m () | |||
275 | readFile file = Safe.withFile file IO.ReadMode fromHandle | 273 | readFile file = Safe.withFile file IO.ReadMode fromHandle |
276 | {-# INLINE readFile #-} | 274 | {-# INLINE readFile #-} |
277 | 275 | ||
278 | {-| Crudely stream lines of input from stdin in the style of Pipes.Prelude. | ||
279 | This is for testing in ghci etc.; obviously it will be unsound if used to recieve | ||
280 | the contents of immense files with few newlines. | ||
281 | |||
282 | >>> let safely = runSafeT . runEffect | ||
283 | >>> safely $ for Text.stdinLn (lift . lift . print . T.length) | ||
284 | hello | ||
285 | 5 | ||
286 | world | ||
287 | 5 | ||
288 | |||
289 | -} | ||
290 | stdinLn :: MonadIO m => Producer' Text m () | ||
291 | stdinLn = go where | ||
292 | go = do | ||
293 | eof <- liftIO (IO.hIsEOF IO.stdin) | ||
294 | unless eof $ do | ||
295 | txt <- liftIO (T.hGetLine IO.stdin) | ||
296 | yield txt | ||
297 | go | ||
298 | {-# INLINABLE stdinLn #-} | ||
299 | 276 | ||
300 | {-| Stream text to 'stdout' | 277 | {-| Stream text to 'stdout' |
301 | 278 | ||
@@ -319,20 +296,6 @@ stdout = go | |||
319 | Right () -> go | 296 | Right () -> go |
320 | {-# INLINABLE stdout #-} | 297 | {-# INLINABLE stdout #-} |
321 | 298 | ||
322 | stdoutLn :: (MonadIO m) => Consumer' Text m () | ||
323 | stdoutLn = go | ||
324 | where | ||
325 | go = do | ||
326 | str <- await | ||
327 | x <- liftIO $ try (T.putStrLn str) | ||
328 | case x of | ||
329 | Left (G.IOError { G.ioe_type = G.ResourceVanished | ||
330 | , G.ioe_errno = Just ioe }) | ||
331 | | Errno ioe == ePIPE | ||
332 | -> return () | ||
333 | Left e -> liftIO (throwIO e) | ||
334 | Right () -> go | ||
335 | {-# INLINABLE stdoutLn #-} | ||
336 | 299 | ||
337 | {-| Convert a text stream into a 'Handle' | 300 | {-| Convert a text stream into a 'Handle' |
338 | 301 | ||
@@ -723,8 +686,9 @@ isEndOfChars = do | |||
723 | {-# INLINABLE isEndOfChars #-} | 686 | {-# INLINABLE isEndOfChars #-} |
724 | 687 | ||
725 | 688 | ||
726 | -- | An improper lens into a stream of 'ByteString' expected to be UTF-8 encoded; the associated | 689 | {- | An improper lens into a stream of 'ByteString' expected to be UTF-8 encoded; the associated |
727 | -- stream of Text ends by returning a stream of ByteStrings beginning at the point of failure. | 690 | stream of Text ends by returning a stream of ByteStrings beginning at the point of failure. |
691 | -} | ||
728 | 692 | ||
729 | decodeUtf8 :: Monad m => Lens' (Producer ByteString m r) | 693 | decodeUtf8 :: Monad m => Lens' (Producer ByteString m r) |
730 | (Producer Text m (Producer ByteString m r)) | 694 | (Producer Text m (Producer ByteString m r)) |
@@ -1010,7 +974,6 @@ lines = Data.Profunctor.dimap _lines (fmap _unlines) | |||
1010 | {-# INLINABLE lines #-} | 974 | {-# INLINABLE lines #-} |
1011 | 975 | ||
1012 | 976 | ||
1013 | |||
1014 | -- | Split a text stream into 'FreeT'-delimited words | 977 | -- | Split a text stream into 'FreeT'-delimited words |
1015 | words | 978 | words |
1016 | :: (Monad m) => Iso' (Producer Text m r) (FreeT (Producer Text m) m r) | 979 | :: (Monad m) => Iso' (Producer Text m r) (FreeT (Producer Text m) m r) |
@@ -1090,6 +1053,16 @@ unwords = intercalate (yield $ T.singleton ' ') | |||
1090 | @Pipes.Parse@ re-exports 'input', 'concat', 'FreeT' (the type) and the 'Parse' synonym. | 1053 | @Pipes.Parse@ re-exports 'input', 'concat', 'FreeT' (the type) and the 'Parse' synonym. |
1091 | -} | 1054 | -} |
1092 | 1055 | ||
1056 | {- | Use a 'Codec' as a pipes-style 'Lens' into a byte stream; the available 'Codec' s are | ||
1057 | 'utf8', 'utf16_le', 'utf16_be', 'utf32_le', 'utf32_be' . The 'Codec' concept and the | ||
1058 | individual 'Codec' definitions follow the enumerator and conduit libraries. | ||
1059 | |||
1060 | Utf8 is handled differently in this library -- without the use of 'unsafePerformIO' &co | ||
1061 | to catch 'Text' exceptions; but the same 'mypipe ^. codec utf8' interface can be used. | ||
1062 | 'mypipe ^. decodeUtf8' should be the same, but has a somewhat more direct and thus perhaps | ||
1063 | better implementation. | ||
1064 | |||
1065 | -} | ||
1093 | codec :: Monad m => Codec -> Lens' (Producer ByteString m r) (Producer Text m (Producer ByteString m r)) | 1066 | codec :: Monad m => Codec -> Lens' (Producer ByteString m r) (Producer Text m (Producer ByteString m r)) |
1094 | codec (Codec _ enc dec) k p0 = fmap (\p -> join (for p (yield . fst . enc))) | 1067 | codec (Codec _ enc dec) k p0 = fmap (\p -> join (for p (yield . fst . enc))) |
1095 | (k (decoder (dec B.empty) p0) ) where | 1068 | (k (decoder (dec B.empty) p0) ) where |
@@ -1104,9 +1077,13 @@ codec (Codec _ enc dec) k p0 = fmap (\p -> join (for p (yield . fst . enc))) | |||
1104 | return r) | 1077 | return r) |
1105 | Right (chunk,p1) -> decoder (dec chunk) p1 | 1078 | Right (chunk,p1) -> decoder (dec chunk) p1 |
1106 | 1079 | ||
1107 | -- decodeUtf8 k p0 = fmap (\p -> join (for p (yield . TE.encodeUtf8))) | 1080 | {- | ascii and latin encodings only represent a small fragment of 'Text'; thus we cannot |
1108 | -- (k (go B.empty PI.streamDecodeUtf8 p0)) where | 1081 | use the pipes 'Lens' style to work with them. Rather we simply define functions |
1082 | each way. | ||
1109 | 1083 | ||
1084 | 'encodeAscii' : Reduce as much of your stream of 'Text' actually is ascii to a byte stream, | ||
1085 | returning the rest of the 'Text' at the first non-ascii 'Char' | ||
1086 | -} | ||
1110 | encodeAscii :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r) | 1087 | encodeAscii :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r) |
1111 | encodeAscii = go where | 1088 | encodeAscii = go where |
1112 | go p = do echunk <- lift (next p) | 1089 | go p = do echunk <- lift (next p) |
@@ -1121,7 +1098,9 @@ encodeAscii = go where | |||
1121 | then go p' | 1098 | then go p' |
1122 | else return $ do yield unsafe | 1099 | else return $ do yield unsafe |
1123 | p' | 1100 | p' |
1124 | 1101 | {- | Reduce as much of your stream of 'Text' actually is iso8859 or latin1 to a byte stream, | |
1102 | returning the rest of the 'Text' upon hitting any non-latin 'Char' | ||
1103 | -} | ||
1125 | encodeIso8859_1 :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r) | 1104 | encodeIso8859_1 :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r) |
1126 | encodeIso8859_1 = go where | 1105 | encodeIso8859_1 = go where |
1127 | go p = do etxt <- lift (next p) | 1106 | go p = do etxt <- lift (next p) |
@@ -1137,6 +1116,9 @@ encodeIso8859_1 = go where | |||
1137 | else return $ do yield unsafe | 1116 | else return $ do yield unsafe |
1138 | p' | 1117 | p' |
1139 | 1118 | ||
1119 | {- | Reduce a byte stream to a corresponding stream of ascii chars, returning the | ||
1120 | unused 'ByteString' upon hitting an un-ascii byte. | ||
1121 | -} | ||
1140 | decodeAscii :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r) | 1122 | decodeAscii :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r) |
1141 | decodeAscii = go where | 1123 | decodeAscii = go where |
1142 | go p = do echunk <- lift (next p) | 1124 | go p = do echunk <- lift (next p) |
@@ -1152,7 +1134,9 @@ decodeAscii = go where | |||
1152 | else return $ do yield unsafe | 1134 | else return $ do yield unsafe |
1153 | p' | 1135 | p' |
1154 | 1136 | ||
1155 | 1137 | {- | Reduce a byte stream to a corresponding stream of ascii chars, returning the | |
1138 | unused 'ByteString' upon hitting the rare un-latinizable byte. | ||
1139 | -} | ||
1156 | decodeIso8859_1 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r) | 1140 | decodeIso8859_1 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r) |
1157 | decodeIso8859_1 = go where | 1141 | decodeIso8859_1 = go where |
1158 | go p = do echunk <- lift (next p) | 1142 | go p = do echunk <- lift (next p) |
@@ -1170,34 +1154,5 @@ decodeIso8859_1 = go where | |||
1170 | 1154 | ||
1171 | 1155 | ||
1172 | 1156 | ||
1173 | {- | 1157 | |
1174 | ascii :: Codec | ||
1175 | ascii = Codec name enc (toDecoding dec) where | ||
1176 | name = T.pack "ASCII" | ||
1177 | enc text = (bytes, extra) where | ||
1178 | (safe, unsafe) = T.span (\c -> ord c <= 0x7F) text | ||
1179 | bytes = B8.pack (T.unpack safe) | ||
1180 | extra = if T.null unsafe | ||
1181 | then Nothing | ||
1182 | else Just (EncodeException ascii (T.head unsafe), unsafe) | ||
1183 | |||
1184 | dec bytes = (text, extra) where | ||
1185 | (safe, unsafe) = B.span (<= 0x7F) bytes | ||
1186 | text = T.pack (B8.unpack safe) | ||
1187 | extra = if B.null unsafe | ||
1188 | then Right B.empty | ||
1189 | else Left (DecodeException ascii (B.head unsafe), unsafe) | ||
1190 | |||
1191 | iso8859_1 :: Codec | ||
1192 | iso8859_1 = Codec name enc (toDecoding dec) where | ||
1193 | name = T.pack "ISO-8859-1" | ||
1194 | enc text = (bytes, extra) where | ||
1195 | (safe, unsafe) = T.span (\c -> ord c <= 0xFF) text | ||
1196 | bytes = B8.pack (T.unpack safe) | ||
1197 | extra = if T.null unsafe | ||
1198 | then Nothing | ||
1199 | else Just (EncodeException iso8859_1 (T.head unsafe), unsafe) | ||
1200 | |||
1201 | dec bytes = (T.pack (B8.unpack bytes), Right B.empty) | ||
1202 | -} | ||
1203 | \ No newline at end of file | 1158 | \ No newline at end of file |