]> git.immae.eu Git - github/fretlink/text-pipes.git/blame - Pipes/Text/IO.hs
detritus
[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
e8336ba6 31import Pipes.Safe (MonadSafe(..))
bbdfd305 32import Prelude hiding (readFile, writeFile)
33
0ac0c414 34{- $textio
80a490ef 35 Where pipes @IO@ replaces lazy @IO@, @Producer Text IO r@ replaces lazy 'Text'.
0ac0c414 36 This module exports some convenient functions for producing and consuming
80a490ef 37 pipes 'Text' in @IO@, namely, 'readFile', 'writeFile', 'fromHandle', 'toHandle',
81074089 38 'stdin' and 'stdout'. Some caveats described below.
0ac0c414 39
4ea59a8b 40 The main points are as in
e1ed9621 41 <https://hackage.haskell.org/package/pipes-bytestring-1.0.0/docs/Pipes-ByteString.html Pipes.ByteString>:
4ea59a8b 42
e1ed9621 43 A 'Handle' can be associated with a 'Producer' or 'Consumer' according
4ea59a8b 44 as it is read or written to.
81074089 45
0ac0c414 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
56To 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
81074089 65 Finally, you can stream to and from 'stdin' and 'stdout' using the predefined 'stdin'
0ac0c414 66 and 'stdout' pipes, as with the following \"echo\" program:
67
68> main = runEffect $ Text.stdin >-> Text.stdout
69
81074089 70
0ac0c414 71-}
72
73
74{- $caveats
75
76 The operations exported here are a convenience, like the similar operations in
77 @Data.Text.IO@ (or rather, @Data.Text.Lazy.IO@, since, again, @Producer Text m r@ is
78 'effectful text' and something like the pipes equivalent of lazy Text.)
79
80 * Like the functions in @Data.Text.IO@, they attempt to work with the system encoding.
81
a4913c42 82 * Like the functions in @Data.Text.IO@, they significantly slower than ByteString operations. Where
0ac0c414 83 you know what encoding you are working with, use @Pipes.ByteString@ and @Pipes.Text.Encoding@ instead,
84 e.g. @view utf8 Bytes.stdin@ instead of @Text.stdin@
85
a4913c42 86 * Like the functions in @Data.Text.IO@ , they use Text exceptions, not the standard Pipes protocols.
0ac0c414 87
88 Something like
89
90> view utf8 . Bytes.fromHandle :: Handle -> Producer Text IO (Producer ByteString m ())
91
92 yields a stream of Text, and follows
93 standard pipes protocols by reverting to (i.e. returning) the underlying byte stream
94 upon reaching any decoding error. (See especially the pipes-binary package.)
95
96 By contrast, something like
97
98> Text.fromHandle :: Handle -> Producer Text IO ()
99
100 supplies a stream of text returning '()', which is convenient for many tasks,
101 but violates the pipes @pipes-binary@ approach to decoding errors and
102 throws an exception of the kind characteristic of the @text@ library instead.
103
104
105-}
bbdfd305 106
107{-| Convert a 'IO.Handle' into a text stream using a text size
327be763 108 determined by the good sense of the text library. Note with the remarks
109 at the head of this module that this
110 is slower than @view utf8 (Pipes.ByteString.fromHandle h)@
111 but uses the system encoding and has other nice @Data.Text.IO@ features
bbdfd305 112-}
113
3f76b550 114fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
bbdfd305 115fromHandle h = go where
116 go = do txt <- liftIO (T.hGetChunk h)
117 if T.null txt then return ()
118 else do yield txt
119 go
120{-# INLINABLE fromHandle#-}
121
327be763 122-- | Stream text from 'stdin'
3f76b550 123stdin :: MonadIO m => Producer Text m ()
327be763 124stdin = fromHandle IO.stdin
125{-# INLINE stdin #-}
126
bbdfd305 127
128{-| Stream text from a file in the simple fashion of @Data.Text.IO@
129
130>>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
131MAIN = PUTSTRLN "HELLO WORLD"
132-}
133
3f76b550 134readFile :: MonadSafe m => FilePath -> Producer Text m ()
bbdfd305 135readFile file = Safe.withFile file IO.ReadMode fromHandle
136{-# INLINE readFile #-}
137
138
139{-| Stream text to 'stdout'
140
141 Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
142
143 Note: For best performance, it might be best just to use @(for source (liftIO . putStr))@
144 instead of @(source >-> stdout)@ .
145-}
146stdout :: MonadIO m => Consumer' Text m ()
147stdout = go
148 where
149 go = do
150 txt <- await
151 x <- liftIO $ try (T.putStr txt)
152 case x of
153 Left (G.IOError { G.ioe_type = G.ResourceVanished
154 , G.ioe_errno = Just ioe })
155 | Errno ioe == ePIPE
156 -> return ()
157 Left e -> liftIO (throwIO e)
158 Right () -> go
159{-# INLINABLE stdout #-}
160
161
162{-| Convert a text stream into a 'Handle'
163
164 Note: again, for best performance, where possible use
165 @(for source (liftIO . hPutStr handle))@ instead of @(source >-> toHandle handle)@.
166-}
167toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
168toHandle h = for cat (liftIO . T.hPutStr h)
169{-# INLINABLE toHandle #-}
170
bbdfd305 171
172
173-- | Stream text into a file. Uses @pipes-safe@.
174writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
175writeFile file = Safe.withFile file IO.WriteMode toHandle
176{-# INLINE writeFile #-}