]> git.immae.eu Git - github/fretlink/text-pipes.git/blob - Pipes/Text/IO.hs
use new text-stream-decoding
[github/fretlink/text-pipes.git] / Pipes / Text / IO.hs
1 {-#LANGUAGE RankNTypes#-}
2
3 module Pipes.Text.IO
4 ( stdin
5 , stdout
6 , fromHandle
7 , toHandle
8 , readFile
9 , writeFile
10 ) where
11
12 import qualified System.IO as IO
13 import Control.Exception (throwIO, try)
14 import Foreign.C.Error (Errno(Errno), ePIPE)
15 import qualified GHC.IO.Exception as G
16 import Data.Text (Text)
17 import qualified Data.Text as T
18 import qualified Data.Text.IO as T
19 import Pipes
20 import qualified Pipes.Safe.Prelude as Safe
21 import qualified Pipes.Safe as Safe
22 import Pipes.Safe (MonadSafe(..), Base(..))
23 import Prelude hiding (readFile, writeFile)
24
25 -- | Stream text from 'stdin'
26 stdin :: MonadIO m => Producer Text m ()
27 stdin = fromHandle IO.stdin
28 {-# INLINE stdin #-}
29
30 {-| Convert a 'IO.Handle' into a text stream using a text size
31 determined by the good sense of the text library; note that this
32 is distinctly slower than @decideUtf8 (Pipes.ByteString.fromHandle h)@
33 but uses the system encoding and has other `Data.Text.IO` features
34 -}
35
36 fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
37 fromHandle h = go where
38 go = do txt <- liftIO (T.hGetChunk h)
39 if T.null txt then return ()
40 else do yield txt
41 go
42 {-# INLINABLE fromHandle#-}
43
44
45 {-| Stream text from a file in the simple fashion of @Data.Text.IO@
46
47 >>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
48 MAIN = PUTSTRLN "HELLO WORLD"
49 -}
50
51 readFile :: MonadSafe m => FilePath -> Producer Text m ()
52 readFile file = Safe.withFile file IO.ReadMode fromHandle
53 {-# INLINE readFile #-}
54
55
56 {-| Stream text to 'stdout'
57
58 Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
59
60 Note: For best performance, it might be best just to use @(for source (liftIO . putStr))@
61 instead of @(source >-> stdout)@ .
62 -}
63 stdout :: MonadIO m => Consumer' Text m ()
64 stdout = go
65 where
66 go = do
67 txt <- await
68 x <- liftIO $ try (T.putStr txt)
69 case x of
70 Left (G.IOError { G.ioe_type = G.ResourceVanished
71 , G.ioe_errno = Just ioe })
72 | Errno ioe == ePIPE
73 -> return ()
74 Left e -> liftIO (throwIO e)
75 Right () -> go
76 {-# INLINABLE stdout #-}
77
78
79 {-| Convert a text stream into a 'Handle'
80
81 Note: again, for best performance, where possible use
82 @(for source (liftIO . hPutStr handle))@ instead of @(source >-> toHandle handle)@.
83 -}
84 toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
85 toHandle h = for cat (liftIO . T.hPutStr h)
86 {-# INLINABLE toHandle #-}
87
88 {-# RULES "p >-> toHandle h" forall p h .
89 p >-> toHandle h = for p (\txt -> liftIO (T.hPutStr h txt))
90 #-}
91
92
93 -- | Stream text into a file. Uses @pipes-safe@.
94 writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
95 writeFile file = Safe.withFile file IO.WriteMode toHandle
96 {-# INLINE writeFile #-}