]> git.immae.eu Git - github/fretlink/text-pipes.git/blob - Pipes/Text/IO.hs
d30f13cc58b9f57c88ebf9388648c01bae323d1d
[github/fretlink/text-pipes.git] / Pipes / Text / IO.hs
1 {-#LANGUAGE RankNTypes#-}
2
3
4 module Pipes.Text.IO
5 (
6 -- * Simple line-based Text IO
7 -- $lineio
8
9 fromHandleLn
10 , toHandleLn
11 , stdinLn
12 , stdoutLn
13 , stdoutLn'
14 , readFileLn
15 , writeFileLn
16
17
18 -- * Simple streaming text IO
19 -- $textio
20
21 -- * Caveats
22 -- $caveats
23
24 -- * Producers
25 , fromHandle
26 , stdin
27 , readFile
28
29 -- * Consumers
30 , toHandle
31 , stdout
32 , writeFile
33
34 -- * Re-exports
35 , MonadSafe(..)
36 , runSafeT
37 , runSafeP
38 , Safe.withFile
39 ) where
40
41 import qualified System.IO as IO
42 import Control.Exception (throwIO, try)
43 import Foreign.C.Error (Errno(Errno), ePIPE)
44 import qualified GHC.IO.Exception as G
45 import Data.Text (Text)
46 import qualified Data.Text as T
47 import qualified Data.Text.IO as T
48 import Pipes
49 import qualified Pipes.Safe.Prelude as Safe
50 import Pipes.Safe (MonadSafe(..), runSafeT, runSafeP)
51 import Prelude hiding (readFile, writeFile)
52
53 {- $lineio
54 Line-based operations are marked with a final \-@Ln@, like 'stdinLn', 'readFileLn'. They are
55 drop-in replacements for the line-based operations in @Pipes.Prelude@ and
56 @Pipes.Safe.Prelude@ - the final \-@Ln@ being added where necessary.
57 With them, one is producing, piping and consuming semantically significant individual texts,
58 understood as lines, just as one would pipe 'Int's. The standard materials from @Pipes@ and @Pipes.Prelude@ and
59 @Data.Text@ are all you need to interact with these lines as you read or write them.
60 You can use these operations without using any of the other material in this package.
61
62 Thus, to take a trivial case, here we upper-case three lines from standard input and write
63 them to a file.
64
65 >>> import Pipes
66 >>> import qualified Pipes.Prelude as P
67 >>> import qualified Pipes.Text.IO as Text
68 >>> import qualified Data.Text as T
69 >>> Text.runSafeT $ runEffect $ Text.stdinLn >-> P.take 3 >-> P.map T.toUpper >-> Text.writeFileLn "threelines.txt"
70 one<Enter>
71 two<Enter>
72 three<Enter>
73 >>> :! cat "threelines.txt"
74 ONE
75 TWO
76 THREE
77
78 The point of view is very much that of @Pipes.Prelude@ and the user who needs no more
79 can use them ignoring the rest of this package.
80
81 The line-based operations are, however, subject to a number of caveats.
82 First, where they read from a handle, they will of course happily
83 accumulate indefinitely long lines. This is likely to be legitimate for input
84 typed in by a user, and for locally produced log files and other known material, but
85 otherwise not. See the post on
86 <http://www.haskellforall.com/2013/09/perfect-streaming-using-pipes-bytestring.html perfect streaming>
87 to see why @pipes-bytestring@ and this package take a different approach. Furthermore,
88 like those in @Data.Text.IO@, the operations use the system encoding and @T.hGetLine@
89 and thus are slower than the \'official\' route, which would use bytestring IO and
90 the encoding and decoding functions in @Pipes.Text.Encoding@. Finally, they will generate
91 text exceptions after the fashion of @Data.Text.Encoding@ rather than returning the
92 undigested bytes in the style of @Pipes.Text.Encoding@
93
94 -}
95
96
97 {-| Read separate lines of 'Text' from 'IO.stdin' using 'T.getLine'
98 This function will accumulate indefinitely long strict 'Text's. See the caveats above.
99
100 Terminates on end of input
101 -}
102 stdinLn :: MonadIO m => Producer' T.Text m ()
103 stdinLn = fromHandleLn IO.stdin
104 {-# INLINABLE stdinLn #-}
105
106
107 {-| Write 'String's to 'IO.stdout' using 'putStrLn'
108
109 Unlike 'toHandle', 'stdoutLn' gracefully terminates on a broken output pipe
110 -}
111 stdoutLn :: MonadIO m => Consumer' T.Text m ()
112 stdoutLn = go
113 where
114 go = do
115 str <- await
116 x <- liftIO $ try (T.putStrLn str)
117 case x of
118 Left (G.IOError { G.ioe_type = G.ResourceVanished
119 , G.ioe_errno = Just ioe })
120 | Errno ioe == ePIPE
121 -> return ()
122 Left e -> liftIO (throwIO e)
123 Right () -> go
124 {-# INLINABLE stdoutLn #-}
125
126 {-| Write lines of 'Text's to 'IO.stdout'.
127
128 This does not handle a broken output pipe, but has a polymorphic return
129 value.
130 -}
131 stdoutLn' :: MonadIO m => Consumer' T.Text m r
132 stdoutLn' = for cat (\str -> liftIO (T.putStrLn str))
133 {-# INLINABLE stdoutLn' #-}
134
135 {-# RULES
136 "p >-> stdoutLn'" forall p .
137 p >-> stdoutLn' = for p (\str -> liftIO (T.putStrLn str))
138 #-}
139
140 {-| Read separate lines of 'Text' from a 'IO.Handle' using 'T.hGetLine'.
141 This operation will accumulate indefinitely large strict texts. See the caveats above.
142
143 Terminates on end of input
144 -}
145 fromHandleLn :: MonadIO m => IO.Handle -> Producer' Text m ()
146 fromHandleLn h = go where
147 getLine :: IO (Either G.IOException Text)
148 getLine = try (T.hGetLine h)
149
150 go = do txt <- liftIO getLine
151 case txt of
152 Left e -> return ()
153 Right y -> do yield y
154 go
155 {-# INLINABLE fromHandleLn #-}
156
157 -- to do: investigate differences from the above:
158 -- fromHandleLn :: MonadIO m => IO.Handle -> Producer' T.Text m ()
159 -- fromHandleLn h = go
160 -- where
161 -- go = do
162 -- eof <- liftIO $ IO.hIsEOF h
163 -- unless eof $ do
164 -- str <- liftIO $ T.hGetLine h
165 -- yield str
166 -- go
167 -- {-# INLINABLE fromHandleLn #-}
168
169
170 -- | Write separate lines of 'Text' to a 'IO.Handle' using 'T.hPutStrLn'
171 toHandleLn :: MonadIO m => IO.Handle -> Consumer' T.Text m r
172 toHandleLn handle = for cat (\str -> liftIO (T.hPutStrLn handle str))
173 {-# INLINABLE toHandleLn #-}
174
175 {-# RULES
176 "p >-> toHandleLn handle" forall p handle .
177 p >-> toHandleLn handle = for p (\str -> liftIO (T.hPutStrLn handle str))
178 #-}
179
180
181 {-| Stream separate lines of text from a file. This operation will accumulate
182 indefinitely long strict text chunks. See the caveats above.
183 -}
184 readFileLn :: MonadSafe m => FilePath -> Producer Text m ()
185 readFileLn file = Safe.withFile file IO.ReadMode fromHandleLn
186 {-# INLINE readFileLn #-}
187
188
189
190 {-| Write lines to a file, automatically opening and closing the file as
191 necessary
192 -}
193 writeFileLn :: (MonadSafe m) => FilePath -> Consumer' Text m r
194 writeFileLn file = Safe.withFile file IO.WriteMode toHandleLn
195 {-# INLINABLE writeFileLn #-}
196
197
198
199 {- $textio
200 Where pipes @IO@ replaces lazy @IO@, @Producer Text IO r@ replaces lazy 'Text'.
201 The official IO of this package and the pipes ecosystem generally would use the
202 IO functions in @Pipes.ByteString@ and the encoding and decoding material in
203 @Pipes.Text.Encoding@.
204
205 The streaming functions exported here, namely, 'readFile', 'writeFile', 'fromHandle', 'toHandle',
206 'stdin' and 'stdout' simplify this and use the system encoding on the model of @Data.Text.IO@
207 and @Data.Text.Lazy.IO@ Some caveats described below.
208
209 The main points are as in
210 <https://hackage.haskell.org/package/pipes-bytestring-1.0.0/docs/Pipes-ByteString.html Pipes.ByteString>:
211
212 A 'Handle' can be associated with a 'Producer' or 'Consumer' according
213 as it is read or written to.
214
215 > import Pipes
216 > import qualified Pipes.Text as Text
217 > import qualified Pipes.Text.IO as Text
218 > import System.IO
219 >
220 > main =
221 > withFile "inFile.txt" ReadMode $ \hIn ->
222 > withFile "outFile.txt" WriteMode $ \hOut ->
223 > runEffect $ Text.fromHandle hIn >-> Text.toHandle hOut
224
225 To stream from files, the following is perhaps more Prelude-like (note that it uses Pipes.Safe):
226
227 > import Pipes
228 > import qualified Pipes.Text as Text
229 > import qualified Pipes.Text.IO as Text
230 > import Pipes.Safe
231 >
232 > main = runSafeT $ runEffect $ Text.readFile "inFile.txt" >-> Text.writeFile "outFile.txt"
233
234 Finally, you can stream to and from 'stdin' and 'stdout' using the predefined 'stdin'
235 and 'stdout' pipes, as with the following \"echo\" program:
236
237 > main = runEffect $ Text.stdin >-> Text.stdout
238
239 These programs, unlike the corresponding programs written with the line-based functions,
240 will pass along a 1 terabyte line without affecting memory use.
241
242 -}
243
244
245 {- $caveats
246
247 The operations exported here are a convenience, like the similar operations in
248 @Data.Text.IO@ (or rather, @Data.Text.Lazy.IO@, since, again, @Producer Text m r@ is
249 'effectful text' and something like the pipes equivalent of lazy Text.)
250
251 * Like the functions in @Data.Text.IO@, they attempt to work with the system encoding.
252
253 * Like the functions in @Data.Text.IO@, they significantly slower than ByteString operations. Where
254 you know what encoding you are working with, use @Pipes.ByteString@ and @Pipes.Text.Encoding@ instead,
255 e.g. @view utf8 Bytes.stdin@ instead of @Text.stdin@
256
257 * Like the functions in @Data.Text.IO@ , they use Text exceptions, not the standard Pipes protocols.
258
259 -}
260
261 {-| Convert a 'IO.Handle' into a text stream using a text size
262 determined by the good sense of the text library. Note with the remarks
263 at the head of this module that this
264 is slower than @view utf8 (Pipes.ByteString.fromHandle h)@
265 but uses the system encoding and has other nice @Data.Text.IO@ features
266 -}
267
268 fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
269 fromHandle h = go where
270 go = do txt <- liftIO (T.hGetChunk h)
271 if T.null txt then return ()
272 else do yield txt
273 go
274 {-# INLINABLE fromHandle#-}
275
276
277 -- | Stream text from 'stdin'
278 stdin :: MonadIO m => Producer Text m ()
279 stdin = fromHandle IO.stdin
280 {-# INLINE stdin #-}
281
282
283 {-| Stream text from a file in the simple fashion of @Data.Text.IO@
284
285 >>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
286 MAIN = PUTSTRLN "HELLO WORLD"
287 -}
288
289 readFile :: MonadSafe m => FilePath -> Producer Text m ()
290 readFile file = Safe.withFile file IO.ReadMode fromHandle
291 {-# INLINE readFile #-}
292
293
294
295 {-| Stream text to 'stdout'
296
297 Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
298
299 Note: For best performance, it might be best just to use @(for source (liftIO . putStr))@
300 instead of @(source >-> stdout)@ .
301 -}
302 stdout :: MonadIO m => Consumer' Text m ()
303 stdout = go
304 where
305 go = do
306 txt <- await
307 x <- liftIO $ try (T.putStr txt)
308 case x of
309 Left (G.IOError { G.ioe_type = G.ResourceVanished
310 , G.ioe_errno = Just ioe })
311 | Errno ioe == ePIPE
312 -> return ()
313 Left e -> liftIO (throwIO e)
314 Right () -> go
315 {-# INLINABLE stdout #-}
316
317
318 {-| Convert a text stream into a 'Handle'
319
320 Note: again, for best performance, where possible use
321 @(for source (liftIO . hPutStr handle))@ instead of @(source >-> toHandle handle)@.
322 -}
323 toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
324 toHandle h = for cat (liftIO . T.hPutStr h)
325 {-# INLINABLE toHandle #-}
326
327
328
329 -- | Stream text into a file. Uses @pipes-safe@.
330 writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
331 writeFile file = Safe.withFile file IO.WriteMode toHandle
332 {-# INLINE writeFile #-}