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