aboutsummaryrefslogtreecommitdiffhomepage
path: root/Pipes/Text.hs
diff options
context:
space:
mode:
authormichaelt <what_is_it_to_do_anything@yahoo.com>2014-01-14 22:05:12 -0500
committermichaelt <what_is_it_to_do_anything@yahoo.com>2014-01-14 22:05:12 -0500
commit3694350ac7b9c42fd64e0092a74cf0471a080058 (patch)
tree38ddadda59a3808422fc432d37b886c456adcb1d /Pipes/Text.hs
parentcd4fd5dd5405ad8e324f43ee2bc81822bdece16c (diff)
downloadtext-pipes-3694350ac7b9c42fd64e0092a74cf0471a080058.tar.gz
text-pipes-3694350ac7b9c42fd64e0092a74cf0471a080058.tar.zst
text-pipes-3694350ac7b9c42fd64e0092a74cf0471a080058.zip
Use clunky Data.Text.IO when bytestring is not explicit
Diffstat (limited to 'Pipes/Text.hs')
-rw-r--r--Pipes/Text.hs37
1 files changed, 23 insertions, 14 deletions
diff --git a/Pipes/Text.hs b/Pipes/Text.hs
index 74d2023..cf493e9 100644
--- a/Pipes/Text.hs
+++ b/Pipes/Text.hs
@@ -1,4 +1,4 @@
1{-# LANGUAGE RankNTypes, TypeFamilies #-} 1{-# LANGUAGE RankNTypes, TypeFamilies, BangPatterns #-}
2 2
3{-| This module provides @pipes@ utilities for \"text streams\", which are 3{-| This module provides @pipes@ utilities for \"text streams\", which are
4 streams of 'Text' chunks. The individual chunks are uniformly @strict@, but 4 streams of 'Text' chunks. The individual chunks are uniformly @strict@, but
@@ -206,30 +206,36 @@ import Prelude hiding (
206-- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's 206-- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's
207fromLazy :: (Monad m) => TL.Text -> Producer' Text m () 207fromLazy :: (Monad m) => TL.Text -> Producer' Text m ()
208fromLazy = foldrChunks (\e a -> yield e >> a) (return ()) 208fromLazy = foldrChunks (\e a -> yield e >> a) (return ())
209{-# INLINABLE fromLazy #-} 209{-# INLINE fromLazy #-}
210 210
211-- | Stream text from 'stdin' 211-- | Stream text from 'stdin'
212stdin :: MonadIO m => Producer Text m (Producer ByteString m ()) 212stdin :: MonadIO m => Producer Text m ()
213stdin = fromHandle IO.stdin 213stdin = fromHandle IO.stdin
214{-# INLINABLE stdin #-} 214{-# INLINE stdin #-}
215 215
216{-| Convert a 'IO.Handle' into a text stream using a text size 216{-| Convert a 'IO.Handle' into a text stream using a text size
217 determined by the good sense of the text library. 217 determined by the good sense of the text library; note that this
218 is distinctly slower than @decideUtf8 (Pipes.ByteString.fromHandle h)@
219 but uses the system encoding and has other `Data.Text.IO` features
218-} 220-}
219 221
220fromHandle :: MonadIO m => IO.Handle -> Producer Text m (Producer ByteString m ()) 222fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
221fromHandle h = decodeUtf8 (PB.fromHandle h) 223fromHandle h = go where
222{-# INLINE fromHandle#-} 224 go = do txt <- liftIO (T.hGetChunk h)
225 unless (T.null txt) $ do yield txt
226 go
227{-# INLINABLE fromHandle#-}
223 228
224{-| Stream text from a file using Pipes.Safe 229
230{-| Stream text from a file in the simple fashion of @Data.Text.IO@
225 231
226>>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout 232>>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
227MAIN = PUTSTRLN "HELLO WORLD" 233MAIN = PUTSTRLN "HELLO WORLD"
228-} 234-}
229 235
230readFile :: (MonadSafe m) => FilePath -> Producer Text m (Producer ByteString m ()) 236readFile :: MonadSafe m => FilePath -> Producer Text m ()
231readFile file = Safe.withFile file IO.ReadMode fromHandle 237readFile file = Safe.withFile file IO.ReadMode fromHandle
232{-# INLINABLE readFile #-} 238{-# INLINE readFile #-}
233 239
234{-| Stream lines of text from stdin (for testing in ghci etc.) 240{-| Stream lines of text from stdin (for testing in ghci etc.)
235 241
@@ -249,7 +255,7 @@ stdinLn = go where
249 txt <- liftIO (T.hGetLine IO.stdin) 255 txt <- liftIO (T.hGetLine IO.stdin)
250 yield txt 256 yield txt
251 go 257 go
252 258{-# INLINABLE stdinLn #-}
253 259
254{-| Stream text to 'stdout' 260{-| Stream text to 'stdout'
255 261
@@ -305,6 +311,7 @@ toHandle h = for cat (liftIO . T.hPutStr h)
305-- | Stream text into a file. Uses @pipes-safe@. 311-- | Stream text into a file. Uses @pipes-safe@.
306writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m () 312writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
307writeFile file = Safe.withFile file IO.WriteMode toHandle 313writeFile file = Safe.withFile file IO.WriteMode toHandle
314{-# INLINE writeFile #-}
308 315
309-- | Apply a transformation to each 'Char' in the stream 316-- | Apply a transformation to each 'Char' in the stream
310map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r 317map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
@@ -592,10 +599,10 @@ count c p = P.fold (+) 0 id (p >-> P.map (fromIntegral . T.count c))
592 599
593decodeUtf8 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r) 600decodeUtf8 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)
594decodeUtf8 = go B.empty PE.streamDecodeUtf8 where 601decodeUtf8 = go B.empty PE.streamDecodeUtf8 where
595 go carry dec0 p = do 602 go !carry dec0 p = do
596 x <- lift (next p) 603 x <- lift (next p)
597 case x of Left r -> if B.null carry 604 case x of Left r -> if B.null carry
598 then return (return r) -- all input was consumed 605 then return (return r) -- all bytestrinput was consumed
599 else return (do yield carry -- a potentially valid fragment remains 606 else return (do yield carry -- a potentially valid fragment remains
600 return r) 607 return r)
601 608
@@ -605,6 +612,8 @@ decodeUtf8 = go B.empty PE.streamDecodeUtf8 where
605 PE.Other text bs -> do yield text 612 PE.Other text bs -> do yield text
606 return (do yield bs -- an invalid blob remains 613 return (do yield bs -- an invalid blob remains
607 p') 614 p')
615{-# INLINABLE decodeUtf8 #-}
616
608 617
609-- | Splits a 'Producer' after the given number of characters 618-- | Splits a 'Producer' after the given number of characters
610splitAt 619splitAt