]> git.immae.eu Git - github/fretlink/text-pipes.git/blob - Pipes/Prelude/Text.hs
ee3e1047e39d358658942bf0d72844727002a413
[github/fretlink/text-pipes.git] / Pipes / Prelude / Text.hs
1 {-#LANGUAGE RankNTypes#-}
2
3
4 module Pipes.Prelude.Text
5 (
6 -- * Simple line-based Text IO
7 -- $lineio
8
9 fromHandleLn
10 , toHandleLn
11 , stdinLn
12 , stdoutLn
13 , stdoutLn'
14 , readFileLn
15 , writeFileLn
16 ) where
17
18 import qualified System.IO as IO
19 import Control.Exception (throwIO, try)
20 import Foreign.C.Error (Errno(Errno), ePIPE)
21 import qualified GHC.IO.Exception as G
22 import Data.Text (Text)
23 import qualified Data.Text as T
24 import qualified Data.Text.IO as T
25 import Pipes
26 import qualified Pipes.Safe.Prelude as Safe
27 import Pipes.Safe (MonadSafe(..), runSafeT, runSafeP)
28 import Prelude hiding (readFile, writeFile)
29
30 {- $lineio
31 Line-based operations are marked with a final \-@Ln@, like 'stdinLn', 'readFileLn', etc.
32 They are drop-in 'Text' replacements for the corresponding 'String' operations in
33 @Pipes.Prelude@ and @Pipes.Safe.Prelude@ - a final \-@Ln@ being added where necessary.
34 In using them, one is producing and consuming semantically significant individual texts,
35 understood as lines, just as one would produce or pipe 'Int's or 'Char's or anything else.
36 Thus, the standard materials from @Pipes@ and @Pipes.Prelude@ and
37 @Data.Text@ are all you need to work with them, and
38 you can use these operations without using any of the other modules in this package.
39
40 Thus, to take a trivial case, here we upper-case three lines from standard input and write
41 them to a file.
42
43 >>> import Pipes
44 >>> import qualified Pipes.Prelude as P
45 >>> import qualified Pipes.Prelude.Text as Text
46 >>> import qualified Data.Text as T
47 >>> Text.runSafeT $ runEffect $ Text.stdinLn >-> P.take 3 >-> P.map T.toUpper >-> Text.writeFileLn "threelines.txt"
48 one<Enter>
49 two<Enter>
50 three<Enter>
51 >>> :! cat "threelines.txt"
52 ONE
53 TWO
54 THREE
55
56 Here @runSafeT@ from @Pipes.Safe@ just makes sure to close any handles opened in its scope.
57 Otherwise the point of view is very much that of @Pipes.Prelude@, substituting @Text@ for @String@.
58 It would still be the same even if
59 we did something a bit more sophisticated, like run an ordinary attoparsec 'Text' parser on
60 each line, as is frequently desirable. Here we use
61 a minimal attoparsec number parser, @scientific@, on separate lines of standard input,
62 dropping bad parses with @P.concat@:
63
64 >>> import Data.Attoparsec.Text (parseOnly, scientific)
65 >>> P.toListM $ Text.stdinLn >-> P.takeWhile (/= "quit") >-> P.map (parseOnly scientific) >-> P.concat
66 1<Enter>
67 2<Enter>
68 bad<Enter>
69 3<Enter>
70 quit<Enter>
71 [1.0,2.0,3.0]
72
73 The line-based operations are, however, subject to a number of caveats.
74 First, where they read from a handle, they will of course happily
75 accumulate indefinitely long lines. This is likely to be legitimate for input
76 typed in by a user, and for locally produced files of known characteristics, but
77 otherwise not. See the post on
78 <http://www.haskellforall.com/2013/09/perfect-streaming-using-pipes-bytestring.html perfect streaming>
79 to see why @pipes-bytestring@ and this package, outside this module, take a different approach.
80 Furthermore, the line-based operations,
81 like those in @Data.Text.IO@, use the system encoding (and @T.hGetLine@)
82 and thus are slower than the \'official\' route, which would use the very fast
83 bytestring IO operations from @Pipes.ByteString@ and
84 encoding and decoding functions in @Pipes.Text.Encoding@. Finally, the line-based
85 operations will generate text exceptions after the fashion of
86 @Data.Text.Encoding@, rather than returning the undigested bytes in the
87 style of @Pipes.Text.Encoding@.
88
89 -}
90
91
92 {-| Read separate lines of 'Text' from 'IO.stdin' using 'T.getLine'
93 This function will accumulate indefinitely long strict 'Text's. See the caveats above.
94
95 Terminates on end of input
96 -}
97 stdinLn :: MonadIO m => Producer' T.Text m ()
98 stdinLn = fromHandleLn IO.stdin
99 {-# INLINABLE stdinLn #-}
100
101
102 {-| Write 'Text' lines to 'IO.stdout' using 'putStrLn'
103
104 Unlike 'toHandle', 'stdoutLn' gracefully terminates on a broken output pipe
105 -}
106 stdoutLn :: MonadIO m => Consumer' T.Text m ()
107 stdoutLn = go
108 where
109 go = do
110 str <- await
111 x <- liftIO $ try (T.putStrLn str)
112 case x of
113 Left (G.IOError { G.ioe_type = G.ResourceVanished
114 , G.ioe_errno = Just ioe })
115 | Errno ioe == ePIPE
116 -> return ()
117 Left e -> liftIO (throwIO e)
118 Right () -> go
119 {-# INLINABLE stdoutLn #-}
120
121 {-| Write lines of 'Text' to 'IO.stdout'.
122
123 This does not handle a broken output pipe, but has a polymorphic return
124 value.
125 -}
126 stdoutLn' :: MonadIO m => Consumer' T.Text m r
127 stdoutLn' = for cat (\str -> liftIO (T.putStrLn str))
128 {-# INLINABLE stdoutLn' #-}
129
130 {-# RULES
131 "p >-> stdoutLn'" forall p .
132 p >-> stdoutLn' = for p (\str -> liftIO (T.putStrLn str))
133 #-}
134
135 {-| Read separate lines of 'Text' from a 'IO.Handle' using 'T.hGetLine'.
136 This operation will accumulate indefinitely large strict texts. See the caveats above.
137
138 Terminates on end of input
139 -}
140 fromHandleLn :: MonadIO m => IO.Handle -> Producer' Text m ()
141 fromHandleLn h = go where
142 getLine :: IO (Either G.IOException Text)
143 getLine = try (T.hGetLine h)
144
145 go = do txt <- liftIO getLine
146 case txt of
147 Left e -> return ()
148 Right y -> do yield y
149 go
150 {-# INLINABLE fromHandleLn #-}
151
152 -- to do: investigate differences from the above:
153 -- fromHandleLn :: MonadIO m => IO.Handle -> Producer' T.Text m ()
154 -- fromHandleLn h = go
155 -- where
156 -- go = do
157 -- eof <- liftIO $ IO.hIsEOF h
158 -- unless eof $ do
159 -- str <- liftIO $ T.hGetLine h
160 -- yield str
161 -- go
162 -- {-# INLINABLE fromHandleLn #-}
163
164
165 -- | Write separate lines of 'Text' to a 'IO.Handle' using 'T.hPutStrLn'
166 toHandleLn :: MonadIO m => IO.Handle -> Consumer' T.Text m r
167 toHandleLn handle = for cat (\str -> liftIO (T.hPutStrLn handle str))
168 {-# INLINABLE toHandleLn #-}
169
170 {-# RULES
171 "p >-> toHandleLn handle" forall p handle .
172 p >-> toHandleLn handle = for p (\str -> liftIO (T.hPutStrLn handle str))
173 #-}
174
175
176 {-| Stream separate lines of text from a file. This operation will accumulate
177 indefinitely long strict text chunks. See the caveats above.
178 -}
179 readFileLn :: MonadSafe m => FilePath -> Producer Text m ()
180 readFileLn file = Safe.withFile file IO.ReadMode fromHandleLn
181 {-# INLINE readFileLn #-}
182
183
184
185 {-| Write lines to a file, automatically opening and closing the file as
186 necessary
187 -}
188 writeFileLn :: (MonadSafe m) => FilePath -> Consumer' Text m r
189 writeFileLn file = Safe.withFile file IO.WriteMode toHandleLn
190 {-# INLINABLE writeFileLn #-}
191