]> git.immae.eu Git - github/fretlink/text-pipes.git/blob - Pipes/Prelude/Text.hs
remarks in pipes-prelude-text
[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. They are
32 drop-in replacements for the line-based operations in @Pipes.Prelude@ and
33 @Pipes.Safe.Prelude@ - the final \-@Ln@ being added where necessary.
34 With them, one is producing, piping 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 interact with these lines as you read or write them, and
38 you can use these operations without using any of the other material 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.Text.IO 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 The point of view is very much that of @Pipes.Prelude@. It would still be the same even if
57 we did something more sophisticated, like run an ordinary attoparsec 'Text' parser on
58 each separate line with @Pipes.Prelude.map ()* , as is frequently reasonable. Here we admit
59 three values from standard input that pass the standard attoparsec @scientific@ number parser,
60 dropping bad parses with @P.concat@:
61
62 >>> P.toListM $ stdinLn >-> P.map (A.parseOnly A.scientific) >-> P.concat >-> P.take 3
63 1<Enter>
64 2<Enter>
65 bad<Enter>
66 3<Enter>
67 [1.0,2.0,3.0]
68
69
70 The line-based operations are, however, subject to a number of caveats.
71 First, where they read from a handle, they will of course happily
72 accumulate indefinitely long lines. This is likely to be legitimate for input
73 typed in by a user, and for locally produced log files and other known material, but
74 otherwise not. See the post on
75 <http://www.haskellforall.com/2013/09/perfect-streaming-using-pipes-bytestring.html perfect streaming>
76 to see why @pipes-bytestring@ and this package take a different approach. Furthermore,
77 like those in @Data.Text.IO@, the operations use the system encoding (and @T.hGetLine@)
78 and thus are slower than the \'official\' route, which would use bytestring IO and
79 the encoding and decoding functions in @Pipes.Text.Encoding@. Finally, they will generate
80 text exceptions after the fashion of @Data.Text.Encoding@ rather than returning the
81 undigested bytes in the style of @Pipes.Text.Encoding@
82
83 -}
84
85
86 {-| Read separate lines of 'Text' from 'IO.stdin' using 'T.getLine'
87 This function will accumulate indefinitely long strict 'Text's. See the caveats above.
88
89 Terminates on end of input
90 -}
91 stdinLn :: MonadIO m => Producer' T.Text m ()
92 stdinLn = fromHandleLn IO.stdin
93 {-# INLINABLE stdinLn #-}
94
95
96 {-| Write 'String's to 'IO.stdout' using 'putStrLn'
97
98 Unlike 'toHandle', 'stdoutLn' gracefully terminates on a broken output pipe
99 -}
100 stdoutLn :: MonadIO m => Consumer' T.Text m ()
101 stdoutLn = go
102 where
103 go = do
104 str <- await
105 x <- liftIO $ try (T.putStrLn str)
106 case x of
107 Left (G.IOError { G.ioe_type = G.ResourceVanished
108 , G.ioe_errno = Just ioe })
109 | Errno ioe == ePIPE
110 -> return ()
111 Left e -> liftIO (throwIO e)
112 Right () -> go
113 {-# INLINABLE stdoutLn #-}
114
115 {-| Write lines of 'Text's to 'IO.stdout'.
116
117 This does not handle a broken output pipe, but has a polymorphic return
118 value.
119 -}
120 stdoutLn' :: MonadIO m => Consumer' T.Text m r
121 stdoutLn' = for cat (\str -> liftIO (T.putStrLn str))
122 {-# INLINABLE stdoutLn' #-}
123
124 {-# RULES
125 "p >-> stdoutLn'" forall p .
126 p >-> stdoutLn' = for p (\str -> liftIO (T.putStrLn str))
127 #-}
128
129 {-| Read separate lines of 'Text' from a 'IO.Handle' using 'T.hGetLine'.
130 This operation will accumulate indefinitely large strict texts. See the caveats above.
131
132 Terminates on end of input
133 -}
134 fromHandleLn :: MonadIO m => IO.Handle -> Producer' Text m ()
135 fromHandleLn h = go where
136 getLine :: IO (Either G.IOException Text)
137 getLine = try (T.hGetLine h)
138
139 go = do txt <- liftIO getLine
140 case txt of
141 Left e -> return ()
142 Right y -> do yield y
143 go
144 {-# INLINABLE fromHandleLn #-}
145
146 -- to do: investigate differences from the above:
147 -- fromHandleLn :: MonadIO m => IO.Handle -> Producer' T.Text m ()
148 -- fromHandleLn h = go
149 -- where
150 -- go = do
151 -- eof <- liftIO $ IO.hIsEOF h
152 -- unless eof $ do
153 -- str <- liftIO $ T.hGetLine h
154 -- yield str
155 -- go
156 -- {-# INLINABLE fromHandleLn #-}
157
158
159 -- | Write separate lines of 'Text' to a 'IO.Handle' using 'T.hPutStrLn'
160 toHandleLn :: MonadIO m => IO.Handle -> Consumer' T.Text m r
161 toHandleLn handle = for cat (\str -> liftIO (T.hPutStrLn handle str))
162 {-# INLINABLE toHandleLn #-}
163
164 {-# RULES
165 "p >-> toHandleLn handle" forall p handle .
166 p >-> toHandleLn handle = for p (\str -> liftIO (T.hPutStrLn handle str))
167 #-}
168
169
170 {-| Stream separate lines of text from a file. This operation will accumulate
171 indefinitely long strict text chunks. See the caveats above.
172 -}
173 readFileLn :: MonadSafe m => FilePath -> Producer Text m ()
174 readFileLn file = Safe.withFile file IO.ReadMode fromHandleLn
175 {-# INLINE readFileLn #-}
176
177
178
179 {-| Write lines to a file, automatically opening and closing the file as
180 necessary
181 -}
182 writeFileLn :: (MonadSafe m) => FilePath -> Consumer' Text m r
183 writeFileLn file = Safe.withFile file IO.WriteMode toHandleLn
184 {-# INLINABLE writeFileLn #-}
185