]> git.immae.eu Git - github/fretlink/text-pipes.git/blob - Pipes/Text/IO.hs
92500c3743865ed206c4f085944ee203d1c2b124
[github/fretlink/text-pipes.git] / Pipes / Text / IO.hs
1 {-#LANGUAGE RankNTypes#-}
2 -- | The operations exported here are a convenience, like the similar operations in
3 -- @Data.Text.IO@ , or rather, @Data.Text.Lazy.IO@, since @Producer Text m r@ is
4 -- 'effectful text' and something like the pipes equivalent of lazy Text.
5 --
6 -- * Like the functions in @Data.Text.IO@, they attempt to work with the system encoding.
7 --
8 -- * Like the functions in @Data.Text.IO@, they are slower than ByteString operations. Where
9 -- you know what encoding you are working with, use @Pipes.ByteString@ and @Pipes.Text.Encoding@ instead,
10 -- e.g. @view utf8 Bytes.stdin@ instead of @Text.stdin@
11 --
12 -- * Like the functions in @Data.Text.IO@ , they use Text exceptions.
13 --
14 -- Something like
15 --
16 -- > view utf8 . Bytes.fromHandle :: Handle -> Producer Text IO (Producer ByteString m ())
17 --
18 -- yields a stream of Text, and follows
19 -- standard pipes protocols by reverting to (i.e. returning) the underlying byte stream
20 -- upon reaching any decoding error. (See especially the pipes-binary package.)
21 --
22 -- By contrast, something like
23 --
24 -- > Text.fromHandle :: Handle -> Producer Text IO ()
25 --
26 -- supplies a stream of text returning '()', which is convenient for many tasks,
27 -- but violates the pipes @pipes-binary@ approach to decoding errors and
28 -- throws an exception of the kind characteristic of the @text@ library instead.
29
30 module Pipes.Text.IO
31 (
32 -- * Producers
33 fromHandle
34 , stdin
35 , readFile
36 -- * Consumers
37 , toHandle
38 , stdout
39 , writeFile
40 ) where
41
42 import qualified System.IO as IO
43 import Control.Exception (throwIO, try)
44 import Foreign.C.Error (Errno(Errno), ePIPE)
45 import qualified GHC.IO.Exception as G
46 import Data.Text (Text)
47 import qualified Data.Text as T
48 import qualified Data.Text.IO as T
49 import Pipes
50 import qualified Pipes.Safe.Prelude as Safe
51 import qualified Pipes.Safe as Safe
52 import Pipes.Safe (MonadSafe(..), Base(..))
53 import Prelude hiding (readFile, writeFile)
54
55
56 {-| Convert a 'IO.Handle' into a text stream using a text size
57 determined by the good sense of the text library. Note with the remarks
58 at the head of this module that this
59 is slower than @view utf8 (Pipes.ByteString.fromHandle h)@
60 but uses the system encoding and has other nice @Data.Text.IO@ features
61 -}
62
63 fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
64 fromHandle h = go where
65 go = do txt <- liftIO (T.hGetChunk h)
66 if T.null txt then return ()
67 else do yield txt
68 go
69 {-# INLINABLE fromHandle#-}
70
71 -- | Stream text from 'stdin'
72 stdin :: MonadIO m => Producer Text m ()
73 stdin = fromHandle IO.stdin
74 {-# INLINE stdin #-}
75
76
77 {-| Stream text from a file in the simple fashion of @Data.Text.IO@
78
79 >>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
80 MAIN = PUTSTRLN "HELLO WORLD"
81 -}
82
83 readFile :: MonadSafe m => FilePath -> Producer Text m ()
84 readFile file = Safe.withFile file IO.ReadMode fromHandle
85 {-# INLINE readFile #-}
86
87
88 {-| Stream text to 'stdout'
89
90 Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
91
92 Note: For best performance, it might be best just to use @(for source (liftIO . putStr))@
93 instead of @(source >-> stdout)@ .
94 -}
95 stdout :: MonadIO m => Consumer' Text m ()
96 stdout = go
97 where
98 go = do
99 txt <- await
100 x <- liftIO $ try (T.putStr txt)
101 case x of
102 Left (G.IOError { G.ioe_type = G.ResourceVanished
103 , G.ioe_errno = Just ioe })
104 | Errno ioe == ePIPE
105 -> return ()
106 Left e -> liftIO (throwIO e)
107 Right () -> go
108 {-# INLINABLE stdout #-}
109
110
111 {-| Convert a text stream into a 'Handle'
112
113 Note: again, for best performance, where possible use
114 @(for source (liftIO . hPutStr handle))@ instead of @(source >-> toHandle handle)@.
115 -}
116 toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
117 toHandle h = for cat (liftIO . T.hPutStr h)
118 {-# INLINABLE toHandle #-}
119
120 {-# RULES "p >-> toHandle h" forall p h .
121 p >-> toHandle h = for p (\txt -> liftIO (T.hPutStr h txt))
122 #-}
123
124
125 -- | Stream text into a file. Uses @pipes-safe@.
126 writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
127 writeFile file = Safe.withFile file IO.WriteMode toHandle
128 {-# INLINE writeFile #-}