aboutsummaryrefslogtreecommitdiffhomepage
path: root/Pipes/Text/IO.hs
blob: 43e636e798d703426285b51e2d481b83d3a2e37c (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
{-#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 
   ( 
   -- * Producers
   fromHandle
   , stdin
   , readFile
   -- * Consumers
   , toHandle
   , stdout
   , writeFile
   ) where

import qualified System.IO as IO
import Control.Exception (throwIO, try)
import Foreign.C.Error (Errno(Errno), ePIPE)
import qualified GHC.IO.Exception as G
import Data.Text (Text)
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 Prelude hiding (readFile, writeFile)


{-| 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 
    at the head of this module that this
    is  slower than @view utf8 (Pipes.ByteString.fromHandle h)@
    but uses the system encoding and has other nice @Data.Text.IO@ features
-}

fromHandle :: MonadIO m => IO.Handle -> Producer' Text m ()
fromHandle h =  go where
      go = do txt <- liftIO (T.hGetChunk h)
              if T.null txt then return ()
                            else do yield txt
                                    go 
{-# INLINABLE fromHandle#-}

-- | Stream text from 'stdin'
stdin :: MonadIO m => Producer' Text m ()
stdin = fromHandle IO.stdin
{-# INLINE stdin #-}


{-| Stream text from a file in the simple fashion of @Data.Text.IO@ 

>>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
MAIN = PUTSTRLN "HELLO WORLD"
-}

readFile :: MonadSafe m => FilePath -> Producer' Text m ()
readFile file = Safe.withFile file IO.ReadMode fromHandle
{-# INLINE readFile #-}


{-| Stream text to 'stdout'

    Unlike 'toHandle', 'stdout' gracefully terminates on a broken output pipe.

    Note: For best performance, it might be best just to use @(for source (liftIO . putStr))@ 
    instead of @(source >-> stdout)@ .
-}
stdout :: MonadIO m => Consumer' Text m ()
stdout = go
  where
    go = do
        txt <- await
        x  <- liftIO $ try (T.putStr txt)
        case x of
            Left (G.IOError { G.ioe_type  = G.ResourceVanished
                            , G.ioe_errno = Just ioe })
                 | Errno ioe == ePIPE
                     -> return ()
            Left  e  -> liftIO (throwIO e)
            Right () -> go
{-# INLINABLE stdout #-}


{-| Convert a text stream into a 'Handle'

    Note: again, for best performance, where possible use 
    @(for source (liftIO . hPutStr handle))@ instead of @(source >-> toHandle handle)@.
-}
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@.
writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
writeFile file = Safe.withFile file IO.WriteMode toHandle
{-# INLINE writeFile #-}