{-# LANGUAGE RankNTypes #-}

module Pipes.Text.IO
  ( -- * Simple streaming text IO
    -- $textio

    -- * Caveats
    -- $caveats

    -- * Producers
    fromHandle,
    stdin,
    readFile,

    -- * Consumers
    toHandle,
    stdout,
    writeFile,

    -- * Re-exports
    MonadSafe (..),
    runSafeT,
    runSafeP,
    Safe.withFile,
  )
where

import Control.Exception (throwIO, try)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Foreign.C.Error (Errno (Errno), ePIPE)
import qualified GHC.IO.Exception as G
import Pipes
import Pipes.Safe (MonadSafe (..), runSafeP, runSafeT)
import qualified Pipes.Safe.Prelude as Safe
import qualified System.IO as IO
import Prelude hiding (readFile, writeFile)

-- $textio
--    Where pipes @IO@ replaces lazy @IO@, @Producer Text IO r@ replaces lazy 'Text'.
--    The official IO of this package and the pipes ecosystem generally would use the
--    IO functions in @Pipes.ByteString@ and the encoding and decoding material in
--    @Pipes.Text.Encoding@.
--
--    The streaming functions exported here, namely, 'readFile', 'writeFile', 'fromHandle', 'toHandle',
--    'stdin' and 'stdout' simplify this and use the system encoding on the model of @Data.Text.IO@
--    and @Data.Text.Lazy.IO@  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
--
--    These programs, unlike the corresponding programs written with the line-based functions,
--    will pass along a 1 terabyte line without affecting memory use.

-- $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.

-- | 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 :: Handle -> Producer Text m ()
fromHandle Handle
h = Producer Text m ()
forall x' x. Proxy x' x () Text m ()
go
  where
    go :: Proxy x' x () Text m ()
go = do
      Text
txt <- IO Text -> Proxy x' x () Text m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> IO Text
T.hGetChunk Handle
h)
      if Text -> Bool
T.null Text
txt
        then () -> Proxy x' x () Text m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        else do
          Text -> forall x' x. Proxy x' x () Text m ()
forall (m :: * -> *) a. Functor m => a -> Producer' a m ()
yield Text
txt
          Proxy x' x () Text m ()
go
          Proxy x' x () Text m ()
go
{-# INLINEABLE fromHandle #-}

-- | Stream text from 'stdin'
stdin :: MonadIO m => Producer Text m ()
stdin :: Producer Text m ()
stdin = Handle -> Producer Text m ()
forall (m :: * -> *). MonadIO m => Handle -> Producer Text m ()
fromHandle Handle
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 :: FilePath -> Producer Text m ()
readFile FilePath
file = FilePath
-> IOMode -> (Handle -> Producer Text m ()) -> Producer Text m ()
forall (m :: * -> *) r.
MonadSafe m =>
FilePath -> IOMode -> (Handle -> m r) -> m r
Safe.withFile FilePath
file IOMode
IO.ReadMode Handle -> Producer Text m ()
forall (m :: * -> *). MonadIO m => Handle -> Producer Text m ()
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 :: Consumer' Text m ()
stdout = Proxy () Text y' y m ()
Consumer' Text m ()
go
  where
    go :: Proxy () Text y' y m ()
go = do
      Text
txt <- Proxy () Text y' y m Text
forall (m :: * -> *) a. Functor m => Consumer' a m a
await
      Either IOException ()
x <- IO (Either IOException ())
-> Proxy () Text y' y m (Either IOException ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either IOException ())
 -> Proxy () Text y' y m (Either IOException ()))
-> IO (Either IOException ())
-> Proxy () Text y' y m (Either IOException ())
forall a b. (a -> b) -> a -> b
$ IO () -> IO (Either IOException ())
forall e a. Exception e => IO a -> IO (Either e a)
try (Text -> IO ()
T.putStr Text
txt)
      case Either IOException ()
x of
        Left
          G.IOError
            { ioe_type :: IOException -> IOErrorType
G.ioe_type = IOErrorType
G.ResourceVanished,
              ioe_errno :: IOException -> Maybe CInt
G.ioe_errno = Just CInt
ioe
            }
            | CInt -> Errno
Errno CInt
ioe Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
ePIPE ->
              () -> Proxy () Text y' y m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Left IOException
e -> IO () -> Proxy () Text y' y m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO IOException
e)
        Right () -> Proxy () Text y' y m ()
go
{-# INLINEABLE 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 :: Handle -> Consumer' Text m r
toHandle Handle
h = Proxy () Text () Text m r
-> (Text -> Proxy () Text y' y m ()) -> Proxy () Text y' y m r
forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for Proxy () Text () Text m r
forall (m :: * -> *) a r. Functor m => Pipe a a m r
cat (IO () -> Proxy () Text y' y m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Proxy () Text y' y m ())
-> (Text -> IO ()) -> Text -> Proxy () Text y' y m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Text -> IO ()
T.hPutStr Handle
h)
{-# INLINEABLE toHandle #-}

-- | Stream text into a file. Uses @pipes-safe@.
writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
writeFile :: FilePath -> Consumer' Text m ()
writeFile FilePath
file = FilePath
-> IOMode
-> (Handle -> Proxy () Text y' y m ())
-> Proxy () Text y' y m ()
forall (m :: * -> *) r.
MonadSafe m =>
FilePath -> IOMode -> (Handle -> m r) -> m r
Safe.withFile FilePath
file IOMode
IO.WriteMode Handle -> Proxy () Text y' y m ()
forall (m :: * -> *) r. MonadIO m => Handle -> Consumer' Text m r
toHandle
{-# INLINE writeFile #-}