]> git.immae.eu Git - github/fretlink/text-pipes.git/blame - Pipes/Text/IO.hs
docs wibbles
[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
14 , stdin
bbdfd305 15 , readFile
327be763 16 -- * Consumers
17 , toHandle
18 , stdout
bbdfd305 19 , writeFile
20 ) where
21
22import qualified System.IO as IO
23import Control.Exception (throwIO, try)
24import Foreign.C.Error (Errno(Errno), ePIPE)
25import qualified GHC.IO.Exception as G
26import Data.Text (Text)
27import qualified Data.Text as T
28import qualified Data.Text.IO as T
29import Pipes
30import qualified Pipes.Safe.Prelude as Safe
31import qualified Pipes.Safe as Safe
32import Pipes.Safe (MonadSafe(..), Base(..))
33import Prelude hiding (readFile, writeFile)
34
0ac0c414 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
4ea59a8b 38 pipes 'Text' in IO, with caveats described below.
0ac0c414 39
4ea59a8b 40 The main points are as in
41 <https://hackage.haskell.org/package/pipes-bytestring-1.0.0/docs/Pipes-ByteString.html Pipes.ByteString>
42
43 An 'IO.Handle' can be associated with a 'Producer' or 'Consumer' according
44 as it is read or written to.
0ac0c414 45
46 To stream to or from 'IO.Handle's, one can use 'fromHandle' or 'toHandle'. For
47 example, the following program copies a document from one file to another:
48
49> import Pipes
50> import qualified Pipes.Text as Text
51> import qualified Pipes.Text.IO as Text
52> import System.IO
53>
54> main =
55> withFile "inFile.txt" ReadMode $ \hIn ->
56> withFile "outFile.txt" WriteMode $ \hOut ->
57> runEffect $ Text.fromHandle hIn >-> Text.toHandle hOut
58
59To stream from files, the following is perhaps more Prelude-like (note that it uses Pipes.Safe):
60
61> import Pipes
62> import qualified Pipes.Text as Text
63> import qualified Pipes.Text.IO as Text
64> import Pipes.Safe
65>
66> main = runSafeT $ runEffect $ Text.readFile "inFile.txt" >-> Text.writeFile "outFile.txt"
67
68 You can stream to and from 'stdin' and 'stdout' using the predefined 'stdin'
69 and 'stdout' pipes, as with the following \"echo\" program:
70
71> main = runEffect $ Text.stdin >-> Text.stdout
72
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
84 * Like the functions in @Data.Text.IO@, they are slower than ByteString operations. Where
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
88 * Like the functions in @Data.Text.IO@ , they use Text exceptions.
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
327be763 124-- | Stream text from 'stdin'
3f76b550 125stdin :: MonadIO m => Producer Text m ()
327be763 126stdin = fromHandle IO.stdin
127{-# INLINE stdin #-}
128
bbdfd305 129
130{-| Stream text from a file in the simple fashion of @Data.Text.IO@
131
132>>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
133MAIN = PUTSTRLN "HELLO WORLD"
134-}
135
3f76b550 136readFile :: MonadSafe m => FilePath -> Producer Text m ()
bbdfd305 137readFile file = Safe.withFile file IO.ReadMode fromHandle
138{-# INLINE readFile #-}
139
140
141{-| Stream text to 'stdout'
142
143 Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
144
145 Note: For best performance, it might be best just to use @(for source (liftIO . putStr))@
146 instead of @(source >-> stdout)@ .
147-}
148stdout :: MonadIO m => Consumer' Text m ()
149stdout = go
150 where
151 go = do
152 txt <- await
153 x <- liftIO $ try (T.putStr txt)
154 case x of
155 Left (G.IOError { G.ioe_type = G.ResourceVanished
156 , G.ioe_errno = Just ioe })
157 | Errno ioe == ePIPE
158 -> return ()
159 Left e -> liftIO (throwIO e)
160 Right () -> go
161{-# INLINABLE stdout #-}
162
163
164{-| Convert a text stream into a 'Handle'
165
166 Note: again, for best performance, where possible use
167 @(for source (liftIO . hPutStr handle))@ instead of @(source >-> toHandle handle)@.
168-}
169toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
170toHandle h = for cat (liftIO . T.hPutStr h)
171{-# INLINABLE toHandle #-}
172
173{-# RULES "p >-> toHandle h" forall p h .
174 p >-> toHandle h = for p (\txt -> liftIO (T.hPutStr h txt))
175 #-}
176
177
178-- | Stream text into a file. Uses @pipes-safe@.
179writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
180writeFile file = Safe.withFile file IO.WriteMode toHandle
181{-# INLINE writeFile #-}