]> git.immae.eu Git - github/fretlink/text-pipes.git/blob - Pipes/Text/IO.hs
version 0.0.0.8 fwiw
[github/fretlink/text-pipes.git] / Pipes / Text / IO.hs
1 {-#LANGUAGE RankNTypes#-}
2
3
4 module Pipes.Text.IO
5 (
6 -- * Text IO
7 -- $textio
8
9 -- * Caveats
10 -- $caveats
11
12 -- * Producers
13 fromHandle
14 , stdin
15 , readFile
16 -- * Consumers
17 , toHandle
18 , stdout
19 , writeFile
20 ) where
21
22 import qualified System.IO as IO
23 import Control.Exception (throwIO, try)
24 import Foreign.C.Error (Errno(Errno), ePIPE)
25 import qualified GHC.IO.Exception as G
26 import Data.Text (Text)
27 import qualified Data.Text as T
28 import qualified Data.Text.IO as T
29 import Pipes
30 import qualified Pipes.Safe.Prelude as Safe
31 import qualified Pipes.Safe as Safe
32 import Pipes.Safe (MonadSafe(..), Base(..))
33 import Prelude hiding (readFile, writeFile)
34
35 {- $textio
36 Where pipes IO replaces lazy IO, @Producer Text m r@ replaces lazy 'Text'.
37 This module exports some convenient functions for producing and consuming
38 pipes 'Text' in IO, with caveats described below. The main points are as in
39 <https://hackage.haskell.org/package/pipes-bytestring-1.0.0/docs/Pipes-ByteString.html @Pipes.ByteString@>
40
41 An 'IO.Handle' can be associated with a 'Producer' or 'Consumer' according as it is read or written to.
42
43 To stream to or from 'IO.Handle's, one can use 'fromHandle' or 'toHandle'. For
44 example, the following program copies a document from one file to another:
45
46 > import Pipes
47 > import qualified Pipes.Text as Text
48 > import qualified Pipes.Text.IO as Text
49 > import System.IO
50 >
51 > main =
52 > withFile "inFile.txt" ReadMode $ \hIn ->
53 > withFile "outFile.txt" WriteMode $ \hOut ->
54 > runEffect $ Text.fromHandle hIn >-> Text.toHandle hOut
55
56 To stream from files, the following is perhaps more Prelude-like (note that it uses Pipes.Safe):
57
58 > import Pipes
59 > import qualified Pipes.Text as Text
60 > import qualified Pipes.Text.IO as Text
61 > import Pipes.Safe
62 >
63 > main = runSafeT $ runEffect $ Text.readFile "inFile.txt" >-> Text.writeFile "outFile.txt"
64
65 You can stream to and from 'stdin' and 'stdout' using the predefined 'stdin'
66 and 'stdout' pipes, as with the following \"echo\" program:
67
68 > main = runEffect $ Text.stdin >-> Text.stdout
69
70 -}
71
72
73 {- $caveats
74
75 The operations exported here are a convenience, like the similar operations in
76 @Data.Text.IO@ (or rather, @Data.Text.Lazy.IO@, since, again, @Producer Text m r@ is
77 'effectful text' and something like the pipes equivalent of lazy Text.)
78
79 * Like the functions in @Data.Text.IO@, they attempt to work with the system encoding.
80
81 * Like the functions in @Data.Text.IO@, they are slower than ByteString operations. Where
82 you know what encoding you are working with, use @Pipes.ByteString@ and @Pipes.Text.Encoding@ instead,
83 e.g. @view utf8 Bytes.stdin@ instead of @Text.stdin@
84
85 * Like the functions in @Data.Text.IO@ , they use Text exceptions.
86
87 Something like
88
89 > view utf8 . Bytes.fromHandle :: Handle -> Producer Text IO (Producer ByteString m ())
90
91 yields a stream of Text, and follows
92 standard pipes protocols by reverting to (i.e. returning) the underlying byte stream
93 upon reaching any decoding error. (See especially the pipes-binary package.)
94
95 By contrast, something like
96
97 > Text.fromHandle :: Handle -> Producer Text IO ()
98
99 supplies a stream of text returning '()', which is convenient for many tasks,
100 but violates the pipes @pipes-binary@ approach to decoding errors and
101 throws an exception of the kind characteristic of the @text@ library instead.
102
103
104 -}
105
106 {-| Convert a 'IO.Handle' into a text stream using a text size
107 determined by the good sense of the text library. Note with the remarks
108 at the head of this module that this
109 is slower than @view utf8 (Pipes.ByteString.fromHandle h)@
110 but uses the system encoding and has other nice @Data.Text.IO@ features
111 -}
112
113 fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
114 fromHandle h = go where
115 go = do txt <- liftIO (T.hGetChunk h)
116 if T.null txt then return ()
117 else do yield txt
118 go
119 {-# INLINABLE fromHandle#-}
120
121 -- | Stream text from 'stdin'
122 stdin :: MonadIO m => Producer Text m ()
123 stdin = fromHandle IO.stdin
124 {-# INLINE stdin #-}
125
126
127 {-| Stream text from a file in the simple fashion of @Data.Text.IO@
128
129 >>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
130 MAIN = PUTSTRLN "HELLO WORLD"
131 -}
132
133 readFile :: MonadSafe m => FilePath -> Producer Text m ()
134 readFile file = Safe.withFile file IO.ReadMode fromHandle
135 {-# INLINE readFile #-}
136
137
138 {-| Stream text to 'stdout'
139
140 Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
141
142 Note: For best performance, it might be best just to use @(for source (liftIO . putStr))@
143 instead of @(source >-> stdout)@ .
144 -}
145 stdout :: MonadIO m => Consumer' Text m ()
146 stdout = go
147 where
148 go = do
149 txt <- await
150 x <- liftIO $ try (T.putStr txt)
151 case x of
152 Left (G.IOError { G.ioe_type = G.ResourceVanished
153 , G.ioe_errno = Just ioe })
154 | Errno ioe == ePIPE
155 -> return ()
156 Left e -> liftIO (throwIO e)
157 Right () -> go
158 {-# INLINABLE stdout #-}
159
160
161 {-| Convert a text stream into a 'Handle'
162
163 Note: again, for best performance, where possible use
164 @(for source (liftIO . hPutStr handle))@ instead of @(source >-> toHandle handle)@.
165 -}
166 toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
167 toHandle h = for cat (liftIO . T.hPutStr h)
168 {-# INLINABLE toHandle #-}
169
170 {-# RULES "p >-> toHandle h" forall p h .
171 p >-> toHandle h = for p (\txt -> liftIO (T.hPutStr h txt))
172 #-}
173
174
175 -- | Stream text into a file. Uses @pipes-safe@.
176 writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
177 writeFile file = Safe.withFile file IO.WriteMode toHandle
178 {-# INLINE writeFile #-}