]> git.immae.eu Git - github/fretlink/text-pipes.git/blame - Pipes/Prelude/Text.hs
little attoparsec example repaired
[github/fretlink/text-pipes.git] / Pipes / Prelude / Text.hs
CommitLineData
5f3c3763 1{-#LANGUAGE RankNTypes#-}
2
3
4module 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
18import qualified System.IO as IO
19import Control.Exception (throwIO, try)
20import Foreign.C.Error (Errno(Errno), ePIPE)
21import qualified GHC.IO.Exception as G
22import Data.Text (Text)
23import qualified Data.Text as T
24import qualified Data.Text.IO as T
25import Pipes
26import qualified Pipes.Safe.Prelude as Safe
27import Pipes.Safe (MonadSafe(..), runSafeT, runSafeP)
28import Prelude hiding (readFile, writeFile)
29
30{- $lineio
c3e06dbc 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,
f328ae9e 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
c3e06dbc 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.
5f3c3763 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"
48one<Enter>
49two<Enter>
50three<Enter>
51>>> :! cat "threelines.txt"
52ONE
53TWO
54THREE
55
f328ae9e 56 The point of view is very much that of @Pipes.Prelude@. It would still be the same even if
c3e06dbc 57 we did something a bit more sophisticated, like run an ordinary attoparsec 'Text' parser on
58 each line, as is frequently desirable. Here we run
59 a minimal attoparsec number parser, @scientific@, on separate lines of standard input,
cca039ba 60 dropping bad parses with @P.concat@:
61
5cfcd499 62>>> import qualified Data.Attoparsec.Text as A
63>>> P.toListM $ Text.stdinLn >-> P.map (A.parseOnly A.scientific) >-> P.concat >-> P.take 3
cca039ba 641<Enter>
652<Enter>
66bad<Enter>
673<Enter>
68[1.0,2.0,3.0]
69
5f3c3763 70
71 The line-based operations are, however, subject to a number of caveats.
72 First, where they read from a handle, they will of course happily
73 accumulate indefinitely long lines. This is likely to be legitimate for input
74 typed in by a user, and for locally produced log files and other known material, but
75 otherwise not. See the post on
76 <http://www.haskellforall.com/2013/09/perfect-streaming-using-pipes-bytestring.html perfect streaming>
77 to see why @pipes-bytestring@ and this package take a different approach. Furthermore,
78 like those in @Data.Text.IO@, the operations use the system encoding (and @T.hGetLine@)
79 and thus are slower than the \'official\' route, which would use bytestring IO and
80 the encoding and decoding functions in @Pipes.Text.Encoding@. Finally, they will generate
81 text exceptions after the fashion of @Data.Text.Encoding@ rather than returning the
82 undigested bytes in the style of @Pipes.Text.Encoding@
83
84-}
85
86
87{-| Read separate lines of 'Text' from 'IO.stdin' using 'T.getLine'
88 This function will accumulate indefinitely long strict 'Text's. See the caveats above.
89
90 Terminates on end of input
91-}
92stdinLn :: MonadIO m => Producer' T.Text m ()
93stdinLn = fromHandleLn IO.stdin
94{-# INLINABLE stdinLn #-}
95
96
c3e06dbc 97{-| Write 'Text' lines to 'IO.stdout' using 'putStrLn'
5f3c3763 98
99 Unlike 'toHandle', 'stdoutLn' gracefully terminates on a broken output pipe
100-}
101stdoutLn :: MonadIO m => Consumer' T.Text m ()
102stdoutLn = go
103 where
104 go = do
105 str <- await
106 x <- liftIO $ try (T.putStrLn str)
107 case x of
108 Left (G.IOError { G.ioe_type = G.ResourceVanished
109 , G.ioe_errno = Just ioe })
110 | Errno ioe == ePIPE
111 -> return ()
112 Left e -> liftIO (throwIO e)
113 Right () -> go
114{-# INLINABLE stdoutLn #-}
115
c3e06dbc 116{-| Write lines of 'Text' to 'IO.stdout'.
5f3c3763 117
118 This does not handle a broken output pipe, but has a polymorphic return
119 value.
120-}
121stdoutLn' :: MonadIO m => Consumer' T.Text m r
122stdoutLn' = for cat (\str -> liftIO (T.putStrLn str))
123{-# INLINABLE stdoutLn' #-}
124
125{-# RULES
126 "p >-> stdoutLn'" forall p .
127 p >-> stdoutLn' = for p (\str -> liftIO (T.putStrLn str))
128 #-}
129
130{-| Read separate lines of 'Text' from a 'IO.Handle' using 'T.hGetLine'.
131 This operation will accumulate indefinitely large strict texts. See the caveats above.
132
133 Terminates on end of input
134-}
135fromHandleLn :: MonadIO m => IO.Handle -> Producer' Text m ()
136fromHandleLn h = go where
137 getLine :: IO (Either G.IOException Text)
138 getLine = try (T.hGetLine h)
139
140 go = do txt <- liftIO getLine
141 case txt of
142 Left e -> return ()
143 Right y -> do yield y
144 go
145{-# INLINABLE fromHandleLn #-}
146
147-- to do: investigate differences from the above:
148-- fromHandleLn :: MonadIO m => IO.Handle -> Producer' T.Text m ()
149-- fromHandleLn h = go
150-- where
151-- go = do
152-- eof <- liftIO $ IO.hIsEOF h
153-- unless eof $ do
154-- str <- liftIO $ T.hGetLine h
155-- yield str
156-- go
157-- {-# INLINABLE fromHandleLn #-}
158
159
160-- | Write separate lines of 'Text' to a 'IO.Handle' using 'T.hPutStrLn'
161toHandleLn :: MonadIO m => IO.Handle -> Consumer' T.Text m r
162toHandleLn handle = for cat (\str -> liftIO (T.hPutStrLn handle str))
163{-# INLINABLE toHandleLn #-}
164
165{-# RULES
166 "p >-> toHandleLn handle" forall p handle .
167 p >-> toHandleLn handle = for p (\str -> liftIO (T.hPutStrLn handle str))
168 #-}
169
170
171{-| Stream separate lines of text from a file. This operation will accumulate
172 indefinitely long strict text chunks. See the caveats above.
173-}
174readFileLn :: MonadSafe m => FilePath -> Producer Text m ()
175readFileLn file = Safe.withFile file IO.ReadMode fromHandleLn
176{-# INLINE readFileLn #-}
177
178
179
180{-| Write lines to a file, automatically opening and closing the file as
181 necessary
182-}
183writeFileLn :: (MonadSafe m) => FilePath -> Consumer' Text m r
184writeFileLn file = Safe.withFile file IO.WriteMode toHandleLn
185{-# INLINABLE writeFileLn #-}
186