aboutsummaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authormichaelt <what_is_it_to_do_anything@yahoo.com>2016-02-06 17:09:45 -0500
committermichaelt <what_is_it_to_do_anything@yahoo.com>2016-02-06 17:09:45 -0500
commit5f3c3763ec355affc1b3219c9c6a072d36349ce3 (patch)
tree295144aedc361fce0e384221e1b2729fc1a85879
parentb6f8504f1bbd2c388af30752ff32c52a48644706 (diff)
downloadtext-pipes-5f3c3763ec355affc1b3219c9c6a072d36349ce3.tar.gz
text-pipes-5f3c3763ec355affc1b3219c9c6a072d36349ce3.tar.zst
text-pipes-5f3c3763ec355affc1b3219c9c6a072d36349ce3.zip
separated line-based material
-rw-r--r--Pipes/Prelude/Text.hs173
-rw-r--r--Pipes/Text/IO.hs158
-rw-r--r--pipes-text.cabal4
3 files changed, 176 insertions, 159 deletions
diff --git a/Pipes/Prelude/Text.hs b/Pipes/Prelude/Text.hs
new file mode 100644
index 0000000..faa096c
--- /dev/null
+++ b/Pipes/Prelude/Text.hs
@@ -0,0 +1,173 @@
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
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"
47one<Enter>
48two<Enter>
49three<Enter>
50>>> :! cat "threelines.txt"
51ONE
52TWO
53THREE
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-}
79stdinLn :: MonadIO m => Producer' T.Text m ()
80stdinLn = 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-}
88stdoutLn :: MonadIO m => Consumer' T.Text m ()
89stdoutLn = 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-}
108stdoutLn' :: MonadIO m => Consumer' T.Text m r
109stdoutLn' = 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-}
122fromHandleLn :: MonadIO m => IO.Handle -> Producer' Text m ()
123fromHandleLn 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'
148toHandleLn :: MonadIO m => IO.Handle -> Consumer' T.Text m r
149toHandleLn 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-}
161readFileLn :: MonadSafe m => FilePath -> Producer Text m ()
162readFileLn 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-}
170writeFileLn :: (MonadSafe m) => FilePath -> Consumer' Text m r
171writeFileLn file = Safe.withFile file IO.WriteMode toHandleLn
172{-# INLINABLE writeFileLn #-}
173
diff --git a/Pipes/Text/IO.hs b/Pipes/Text/IO.hs
index d30f13c..2a34be7 100644
--- a/Pipes/Text/IO.hs
+++ b/Pipes/Text/IO.hs
@@ -3,17 +3,6 @@
3 3
4module Pipes.Text.IO 4module Pipes.Text.IO
5 ( 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
17 6
18 -- * Simple streaming text IO 7 -- * Simple streaming text IO
19 -- $textio 8 -- $textio
@@ -22,7 +11,7 @@ module Pipes.Text.IO
22 -- $caveats 11 -- $caveats
23 12
24 -- * Producers 13 -- * Producers
25 , fromHandle 14 fromHandle
26 , stdin 15 , stdin
27 , readFile 16 , readFile
28 17
@@ -50,151 +39,6 @@ import qualified Pipes.Safe.Prelude as Safe
50import Pipes.Safe (MonadSafe(..), runSafeT, runSafeP) 39import Pipes.Safe (MonadSafe(..), runSafeT, runSafeP)
51import Prelude hiding (readFile, writeFile) 40import Prelude hiding (readFile, writeFile)
52 41
53{- $lineio
54 Line-based operations are marked with a final \-@Ln@, like 'stdinLn', 'readFileLn'. They are
55 drop-in replacements for the line-based operations in @Pipes.Prelude@ and
56 @Pipes.Safe.Prelude@ - the final \-@Ln@ being added where necessary.
57 With them, one is producing, piping and consuming semantically significant individual texts,
58 understood as lines, just as one would pipe 'Int's. The standard materials from @Pipes@ and @Pipes.Prelude@ and
59 @Data.Text@ are all you need to interact with these lines as you read or write them.
60 You can use these operations without using any of the other material in this package.
61
62 Thus, to take a trivial case, here we upper-case three lines from standard input and write
63 them to a file.
64
65>>> import Pipes
66>>> import qualified Pipes.Prelude as P
67>>> import qualified Pipes.Text.IO as Text
68>>> import qualified Data.Text as T
69>>> Text.runSafeT $ runEffect $ Text.stdinLn >-> P.take 3 >-> P.map T.toUpper >-> Text.writeFileLn "threelines.txt"
70one<Enter>
71two<Enter>
72three<Enter>
73>>> :! cat "threelines.txt"
74ONE
75TWO
76THREE
77
78 The point of view is very much that of @Pipes.Prelude@ and the user who needs no more
79 can use them ignoring the rest of this package.
80
81 The line-based operations are, however, subject to a number of caveats.
82 First, where they read from a handle, they will of course happily
83 accumulate indefinitely long lines. This is likely to be legitimate for input
84 typed in by a user, and for locally produced log files and other known material, but
85 otherwise not. See the post on
86 <http://www.haskellforall.com/2013/09/perfect-streaming-using-pipes-bytestring.html perfect streaming>
87 to see why @pipes-bytestring@ and this package take a different approach. Furthermore,
88 like those in @Data.Text.IO@, the operations use the system encoding and @T.hGetLine@
89 and thus are slower than the \'official\' route, which would use bytestring IO and
90 the encoding and decoding functions in @Pipes.Text.Encoding@. Finally, they will generate
91 text exceptions after the fashion of @Data.Text.Encoding@ rather than returning the
92 undigested bytes in the style of @Pipes.Text.Encoding@
93
94-}
95
96
97{-| Read separate lines of 'Text' from 'IO.stdin' using 'T.getLine'
98 This function will accumulate indefinitely long strict 'Text's. See the caveats above.
99
100 Terminates on end of input
101-}
102stdinLn :: MonadIO m => Producer' T.Text m ()
103stdinLn = fromHandleLn IO.stdin
104{-# INLINABLE stdinLn #-}
105
106
107{-| Write 'String's to 'IO.stdout' using 'putStrLn'
108
109 Unlike 'toHandle', 'stdoutLn' gracefully terminates on a broken output pipe
110-}
111stdoutLn :: MonadIO m => Consumer' T.Text m ()
112stdoutLn = go
113 where
114 go = do
115 str <- await
116 x <- liftIO $ try (T.putStrLn str)
117 case x of
118 Left (G.IOError { G.ioe_type = G.ResourceVanished
119 , G.ioe_errno = Just ioe })
120 | Errno ioe == ePIPE
121 -> return ()
122 Left e -> liftIO (throwIO e)
123 Right () -> go
124{-# INLINABLE stdoutLn #-}
125
126{-| Write lines of 'Text's to 'IO.stdout'.
127
128 This does not handle a broken output pipe, but has a polymorphic return
129 value.
130-}
131stdoutLn' :: MonadIO m => Consumer' T.Text m r
132stdoutLn' = for cat (\str -> liftIO (T.putStrLn str))
133{-# INLINABLE stdoutLn' #-}
134
135{-# RULES
136 "p >-> stdoutLn'" forall p .
137 p >-> stdoutLn' = for p (\str -> liftIO (T.putStrLn str))
138 #-}
139
140{-| Read separate lines of 'Text' from a 'IO.Handle' using 'T.hGetLine'.
141 This operation will accumulate indefinitely large strict texts. See the caveats above.
142
143 Terminates on end of input
144-}
145fromHandleLn :: MonadIO m => IO.Handle -> Producer' Text m ()
146fromHandleLn h = go where
147 getLine :: IO (Either G.IOException Text)
148 getLine = try (T.hGetLine h)
149
150 go = do txt <- liftIO getLine
151 case txt of
152 Left e -> return ()
153 Right y -> do yield y
154 go
155{-# INLINABLE fromHandleLn #-}
156
157-- to do: investigate differences from the above:
158-- fromHandleLn :: MonadIO m => IO.Handle -> Producer' T.Text m ()
159-- fromHandleLn h = go
160-- where
161-- go = do
162-- eof <- liftIO $ IO.hIsEOF h
163-- unless eof $ do
164-- str <- liftIO $ T.hGetLine h
165-- yield str
166-- go
167-- {-# INLINABLE fromHandleLn #-}
168
169
170-- | Write separate lines of 'Text' to a 'IO.Handle' using 'T.hPutStrLn'
171toHandleLn :: MonadIO m => IO.Handle -> Consumer' T.Text m r
172toHandleLn handle = for cat (\str -> liftIO (T.hPutStrLn handle str))
173{-# INLINABLE toHandleLn #-}
174
175{-# RULES
176 "p >-> toHandleLn handle" forall p handle .
177 p >-> toHandleLn handle = for p (\str -> liftIO (T.hPutStrLn handle str))
178 #-}
179
180
181{-| Stream separate lines of text from a file. This operation will accumulate
182 indefinitely long strict text chunks. See the caveats above.
183-}
184readFileLn :: MonadSafe m => FilePath -> Producer Text m ()
185readFileLn file = Safe.withFile file IO.ReadMode fromHandleLn
186{-# INLINE readFileLn #-}
187
188
189
190{-| Write lines to a file, automatically opening and closing the file as
191 necessary
192-}
193writeFileLn :: (MonadSafe m) => FilePath -> Consumer' Text m r
194writeFileLn file = Safe.withFile file IO.WriteMode toHandleLn
195{-# INLINABLE writeFileLn #-}
196
197
198 42
199{- $textio 43{- $textio
200 Where pipes @IO@ replaces lazy @IO@, @Producer Text IO r@ replaces lazy 'Text'. 44 Where pipes @IO@ replaces lazy @IO@, @Producer Text IO r@ replaces lazy 'Text'.
diff --git a/pipes-text.cabal b/pipes-text.cabal
index bd58457..fe77644 100644
--- a/pipes-text.cabal
+++ b/pipes-text.cabal
@@ -1,5 +1,5 @@
1name: pipes-text 1name: pipes-text
2version: 0.0.1.0 2version: 0.0.2.0
3synopsis: Text pipes. 3synopsis: Text pipes.
4description: * This organization of the package follows the rule 4description: * This organization of the package follows the rule
5 . 5 .
@@ -48,5 +48,5 @@ library
48 ghc-options: -O2 48 ghc-options: -O2
49 49
50 if !flag(noio) 50 if !flag(noio)
51 exposed-modules: Pipes.Text.IO, Pipes.Text.Tutorial 51 exposed-modules: Pipes.Text.IO, Pipes.Text.Tutorial, Pipes.Prelude.Text
52 build-depends: text >=0.11.3 && < 1.3 52 build-depends: text >=0.11.3 && < 1.3