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