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