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