]> git.immae.eu Git - github/fretlink/text-pipes.git/blame_incremental - Pipes/Text/IO.hs
bump for pipes-4.4
[github/fretlink/text-pipes.git] / Pipes / Text / IO.hs
... / ...
CommitLineData
1{-#LANGUAGE RankNTypes#-}
2
3
4module Pipes.Text.IO
5 (
6
7 -- * Simple streaming text IO
8 -- $textio
9
10 -- * Caveats
11 -- $caveats
12
13 -- * Producers
14 fromHandle
15 , stdin
16 , readFile
17
18 -- * Consumers
19 , toHandle
20 , stdout
21 , writeFile
22
23 -- * Re-exports
24 , MonadSafe(..)
25 , runSafeT
26 , runSafeP
27 , Safe.withFile
28 ) where
29
30import qualified System.IO as IO
31import Control.Exception (throwIO, try)
32import Foreign.C.Error (Errno(Errno), ePIPE)
33import qualified GHC.IO.Exception as G
34import Data.Text (Text)
35import qualified Data.Text as T
36import qualified Data.Text.IO as T
37import Pipes
38import qualified Pipes.Safe.Prelude as Safe
39import Pipes.Safe (MonadSafe(..), runSafeT, runSafeP)
40import Prelude hiding (readFile, writeFile)
41
42
43{- $textio
44 Where pipes @IO@ replaces lazy @IO@, @Producer Text IO r@ replaces lazy 'Text'.
45 The official IO of this package and the pipes ecosystem generally would use the
46 IO functions in @Pipes.ByteString@ and the encoding and decoding material in
47 @Pipes.Text.Encoding@.
48
49 The streaming functions exported here, namely, 'readFile', 'writeFile', 'fromHandle', 'toHandle',
50 'stdin' and 'stdout' simplify this and use the system encoding on the model of @Data.Text.IO@
51 and @Data.Text.Lazy.IO@ Some caveats described below.
52
53 The main points are as in
54 <https://hackage.haskell.org/package/pipes-bytestring-1.0.0/docs/Pipes-ByteString.html Pipes.ByteString>:
55
56 A 'Handle' can be associated with a 'Producer' or 'Consumer' according
57 as it is read or written to.
58
59> import Pipes
60> import qualified Pipes.Text as Text
61> import qualified Pipes.Text.IO as Text
62> import System.IO
63>
64> main =
65> withFile "inFile.txt" ReadMode $ \hIn ->
66> withFile "outFile.txt" WriteMode $ \hOut ->
67> runEffect $ Text.fromHandle hIn >-> Text.toHandle hOut
68
69To stream from files, the following is perhaps more Prelude-like (note that it uses Pipes.Safe):
70
71> import Pipes
72> import qualified Pipes.Text as Text
73> import qualified Pipes.Text.IO as Text
74> import Pipes.Safe
75>
76> main = runSafeT $ runEffect $ Text.readFile "inFile.txt" >-> Text.writeFile "outFile.txt"
77
78 Finally, you can stream to and from 'stdin' and 'stdout' using the predefined 'stdin'
79 and 'stdout' pipes, as with the following \"echo\" program:
80
81> main = runEffect $ Text.stdin >-> Text.stdout
82
83 These programs, unlike the corresponding programs written with the line-based functions,
84 will pass along a 1 terabyte line without affecting memory use.
85
86-}
87
88
89{- $caveats
90
91 The operations exported here are a convenience, like the similar operations in
92 @Data.Text.IO@ (or rather, @Data.Text.Lazy.IO@, since, again, @Producer Text m r@ is
93 'effectful text' and something like the pipes equivalent of lazy Text.)
94
95 * Like the functions in @Data.Text.IO@, they attempt to work with the system encoding.
96
97 * Like the functions in @Data.Text.IO@, they significantly slower than ByteString operations. Where
98 you know what encoding you are working with, use @Pipes.ByteString@ and @Pipes.Text.Encoding@ instead,
99 e.g. @view utf8 Bytes.stdin@ instead of @Text.stdin@
100
101 * Like the functions in @Data.Text.IO@ , they use Text exceptions, not the standard Pipes protocols.
102
103-}
104
105{-| Convert a 'IO.Handle' into a text stream using a text size
106 determined by the good sense of the text library. Note with the remarks
107 at the head of this module that this
108 is slower than @view utf8 (Pipes.ByteString.fromHandle h)@
109 but uses the system encoding and has other nice @Data.Text.IO@ features
110-}
111
112fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
113fromHandle h = go where
114 go = do txt <- liftIO (T.hGetChunk h)
115 if T.null txt then return ()
116 else do yield txt
117 go
118{-# INLINABLE fromHandle#-}
119
120
121-- | Stream text from 'stdin'
122stdin :: MonadIO m => Producer Text m ()
123stdin = fromHandle IO.stdin
124{-# INLINE stdin #-}
125
126
127{-| Stream text from a file in the simple fashion of @Data.Text.IO@
128
129>>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
130MAIN = PUTSTRLN "HELLO WORLD"
131-}
132
133readFile :: MonadSafe m => FilePath -> Producer Text m ()
134readFile file = Safe.withFile file IO.ReadMode fromHandle
135{-# INLINE readFile #-}
136
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
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 #-}