]> git.immae.eu Git - github/fretlink/text-pipes.git/blobdiff - Pipes/Text/IO.hs
Merge pull request #18 from sid-kap/text_lines
[github/fretlink/text-pipes.git] / Pipes / Text / IO.hs
index 92500c3743865ed206c4f085944ee203d1c2b124..51c69265a04ac49a9aaa047cf7b1952242efdc40 100644 (file)
@@ -1,38 +1,20 @@
 {-#LANGUAGE RankNTypes#-}
--- | The operations exported here are a convenience, like the similar operations in 
---   @Data.Text.IO@ , or rather, @Data.Text.Lazy.IO@, since @Producer Text m r@ is
---   'effectful text' and something like the pipes equivalent of lazy Text.
---
---   * Like the functions in @Data.Text.IO@, they attempt to work with the system encoding. 
---   
---   * Like the functions in @Data.Text.IO@, they are slower than ByteString operations. Where
---      you know what encoding you are working with, use @Pipes.ByteString@ and @Pipes.Text.Encoding@ instead,
---      e.g. @view utf8 Bytes.stdin@ instead of @Text.stdin@
---   
---   * Like the functions in  @Data.Text.IO@ , they use Text exceptions. 
---
---  Something like 
---  
---   >  view utf8 . Bytes.fromHandle :: Handle -> Producer Text IO (Producer ByteString m ()) 
--- 
---  yields a stream of Text, and follows
---  standard pipes protocols by reverting to (i.e. returning) the underlying byte stream
---  upon reaching any decoding error. (See especially the pipes-binary package.) 
---
--- By contrast, something like 
--- 
---  > Text.fromHandle :: Handle -> Producer Text IO () 
--- 
--- supplies a stream of text returning '()', which is convenient for many tasks, 
--- but violates the pipes @pipes-binary@ approach to decoding errors and 
--- throws an exception of the kind characteristic of the @text@ library instead.
+
 
 module Pipes.Text.IO 
    ( 
+   -- * Text IO
+   -- $textio
+   
+   -- * Caveats
+   -- $caveats
+   
    -- * Producers
    fromHandle
+   , fromHandleLn
    , stdin
    , readFile
+   , readFileLn
    -- * Consumers
    , toHandle
    , stdout
@@ -48,10 +30,81 @@ import qualified Data.Text as T
 import qualified Data.Text.IO as T
 import Pipes
 import qualified Pipes.Safe.Prelude as Safe
-import qualified Pipes.Safe as Safe
-import Pipes.Safe (MonadSafe(..), Base(..))
+import Pipes.Safe (MonadSafe(..))
 import Prelude hiding (readFile, writeFile)
 
+{- $textio
+    Where pipes @IO@ replaces lazy @IO@, @Producer Text IO r@ replaces lazy 'Text'. 
+    This module exports some convenient functions for producing and consuming 
+    pipes 'Text' in @IO@, namely, 'readFile', 'writeFile', 'fromHandle', 'toHandle', 
+    'stdin' and 'stdout'.  Some caveats described below. 
+    
+    The main points are as in 
+    <https://hackage.haskell.org/package/pipes-bytestring-1.0.0/docs/Pipes-ByteString.html Pipes.ByteString>:
+    
+    A 'Handle' can be associated with a 'Producer' or 'Consumer' according 
+    as it is read or written to.
+    
+> import Pipes
+> import qualified Pipes.Text as Text
+> import qualified Pipes.Text.IO as Text
+> import System.IO
+>
+> main =
+>     withFile "inFile.txt"  ReadMode  $ \hIn  ->
+>     withFile "outFile.txt" WriteMode $ \hOut ->
+>     runEffect $ Text.fromHandle hIn >-> Text.toHandle hOut
+
+To stream from files, the following is perhaps more Prelude-like (note that it uses Pipes.Safe):
+
+> import Pipes
+> import qualified Pipes.Text as Text
+> import qualified Pipes.Text.IO as Text
+> import Pipes.Safe
+>
+> main = runSafeT $ runEffect $ Text.readFile "inFile.txt" >-> Text.writeFile "outFile.txt"
+
+    Finally, you can stream to and from 'stdin' and 'stdout' using the predefined 'stdin'
+    and 'stdout' pipes, as with the following \"echo\" program:
+
+> main = runEffect $ Text.stdin >-> Text.stdout
+
+
+-}
+
+
+{- $caveats
+
+    The operations exported here are a convenience, like the similar operations in 
+    @Data.Text.IO@  (or rather, @Data.Text.Lazy.IO@, since, again, @Producer Text m r@ is
+    'effectful text' and something like the pipes equivalent of lazy Text.)
+
+    * Like the functions in @Data.Text.IO@, they attempt to work with the system encoding. 
+  
+    * Like the functions in @Data.Text.IO@, they significantly slower than ByteString operations. Where
+       you know what encoding you are working with, use @Pipes.ByteString@ and @Pipes.Text.Encoding@ instead,
+       e.g. @view utf8 Bytes.stdin@ instead of @Text.stdin@
+  
+    * Like the functions in  @Data.Text.IO@ , they use Text exceptions, not the standard Pipes protocols. 
+
+   Something like 
+>  view utf8 . Bytes.fromHandle :: Handle -> Producer Text IO (Producer ByteString m ()) 
+
+   yields a stream of Text, and follows
+   standard pipes protocols by reverting to (i.e. returning) the underlying byte stream
+   upon reaching any decoding error. (See especially the pipes-binary package.) 
+
+  By contrast, something like 
+
+> Text.fromHandle :: Handle -> Producer Text IO () 
+
+  supplies a stream of text returning '()', which is convenient for many tasks, 
+  but violates the pipes @pipes-binary@ approach to decoding errors and 
+  throws an exception of the kind characteristic of the @text@ library instead.
+
+
+-}
 
 {-| Convert a 'IO.Handle' into a text stream using a text size 
     determined by the good sense of the text library. Note with the remarks 
@@ -68,6 +121,19 @@ fromHandle h =  go where
                                     go 
 {-# INLINABLE fromHandle#-}
 
+
+fromHandleLn :: MonadIO m => IO.Handle -> Producer Text m ()
+fromHandleLn h =  go where
+      getLine :: IO (Either G.IOException Text)
+      getLine = try (T.hGetLine h)
+
+      go = do txt <- liftIO getLine
+              case txt of
+                Left e  -> return ()
+                Right y -> do yield y
+                              go
+{-# INLINABLE fromHandleLn #-}
+
 -- | Stream text from 'stdin'
 stdin :: MonadIO m => Producer Text m ()
 stdin = fromHandle IO.stdin
@@ -85,6 +151,13 @@ readFile file = Safe.withFile file IO.ReadMode fromHandle
 {-# INLINE readFile #-}
 
 
+{-| Stream lines of text from a file
+-}
+readFileLn :: MonadSafe m => FilePath -> Producer Text m ()
+readFileLn file = Safe.withFile file IO.ReadMode fromHandleLn
+{-# INLINE readFileLn #-}
+
+
 {-| Stream text to 'stdout'
 
     Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.
@@ -117,9 +190,6 @@ toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
 toHandle h = for cat (liftIO . T.hPutStr h)
 {-# INLINABLE toHandle #-}
 
-{-# RULES "p >-> toHandle h" forall p h .
-        p >-> toHandle h = for p (\txt -> liftIO (T.hPutStr h txt))
-  #-}
 
 
 -- | Stream text into a file. Uses @pipes-safe@.