{-# LANGUAGE CPP               #-}
{-# LANGUAGE FlexibleInstances #-}

#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy       #-}
#endif

-- | Input and output streams for file 'Handle's.
module System.IO.Streams.Handle
 ( -- * Handle conversions
   handleToInputStream
 , handleToOutputStream
 , handleToStreams
 , inputStreamToHandle
 , outputStreamToHandle
 , streamPairToHandle

   -- * Standard system handles
 , stdin
 , stdout
 , stderr
 ) where

------------------------------------------------------------------------------
import           Data.ByteString            (ByteString)
import qualified Data.ByteString            as S
import qualified GHC.IO.Handle              as H
import           System.IO                  (Handle, hFlush)
import qualified System.IO                  as IO
import           System.IO.Unsafe           (unsafePerformIO)
------------------------------------------------------------------------------
import           System.IO.Streams.Internal (InputStream, OutputStream, SP (..), lockingInputStream, lockingOutputStream, makeInputStream, makeOutputStream)


------------------------------------------------------------------------------
bUFSIZ :: Int
bUFSIZ :: Int
bUFSIZ = Int
32752


------------------------------------------------------------------------------
-- | Converts a read-only handle into an 'InputStream' of strict 'ByteString's.
--
-- Note that the wrapped handle is /not/ closed when it yields end-of-stream;
-- you can use 'System.IO.Streams.Combinators.atEndOfInput' to close the handle
-- if you would like this behaviour.
handleToInputStream :: Handle -> IO (InputStream ByteString)
handleToInputStream :: Handle -> IO (InputStream ByteString)
handleToInputStream Handle
h = IO (Maybe ByteString) -> IO (InputStream ByteString)
forall a. IO (Maybe a) -> IO (InputStream a)
makeInputStream IO (Maybe ByteString)
f
  where
    f :: IO (Maybe ByteString)
f = do
        ByteString
x <- Handle -> Int -> IO ByteString
S.hGetSome Handle
h Int
bUFSIZ
        Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ByteString -> IO (Maybe ByteString))
-> Maybe ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$! if ByteString -> Bool
S.null ByteString
x then Maybe ByteString
forall a. Maybe a
Nothing else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
x


------------------------------------------------------------------------------
-- | Converts a writable handle into an 'OutputStream' of strict 'ByteString's.
--
-- Note that the wrapped handle is /not/ closed when it receives end-of-stream;
-- you can use 'System.IO.Streams.Combinators.atEndOfOutput' to close the
-- handle if you would like this behaviour.
--
-- /Note/: to force the 'Handle' to be flushed, you can write a null string to
-- the returned 'OutputStream':
--
-- > Streams.write (Just "") os
handleToOutputStream :: Handle -> IO (OutputStream ByteString)
handleToOutputStream :: Handle -> IO (OutputStream ByteString)
handleToOutputStream Handle
h = (Maybe ByteString -> IO ()) -> IO (OutputStream ByteString)
forall a. (Maybe a -> IO ()) -> IO (OutputStream a)
makeOutputStream Maybe ByteString -> IO ()
f
  where
    f :: Maybe ByteString -> IO ()
f Maybe ByteString
Nothing  = Handle -> IO ()
hFlush Handle
h
    f (Just ByteString
x) = if ByteString -> Bool
S.null ByteString
x
                   then Handle -> IO ()
hFlush Handle
h
                   else Handle -> ByteString -> IO ()
S.hPut Handle
h ByteString
x


------------------------------------------------------------------------------
-- | Converts a readable and writable handle into an 'InputStream'/'OutputStream'
-- of strict 'ByteString's.
--
-- Note that the wrapped handle is /not/ closed when it receives
-- end-of-stream; you can use
-- 'System.IO.Streams.Combinators.atEndOfOutput' to close the handle
-- if you would like this behaviour.
--
-- /Note/: to force the 'Handle' to be flushed, you can write a null string to
-- the returned 'OutputStream':
--
-- > Streams.write (Just "") os
--
-- /Since: 1.3.4.0./
handleToStreams :: Handle
                -> IO (InputStream ByteString, OutputStream ByteString)
handleToStreams :: Handle -> IO (InputStream ByteString, OutputStream ByteString)
handleToStreams Handle
h = do
    InputStream ByteString
is <- Handle -> IO (InputStream ByteString)
handleToInputStream Handle
h
    OutputStream ByteString
os <- Handle -> IO (OutputStream ByteString)
handleToOutputStream Handle
h
    (InputStream ByteString, OutputStream ByteString)
-> IO (InputStream ByteString, OutputStream ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return ((InputStream ByteString, OutputStream ByteString)
 -> IO (InputStream ByteString, OutputStream ByteString))
-> (InputStream ByteString, OutputStream ByteString)
-> IO (InputStream ByteString, OutputStream ByteString)
forall a b. (a -> b) -> a -> b
$! (InputStream ByteString
is, OutputStream ByteString
os)


------------------------------------------------------------------------------
-- | Converts an 'InputStream' over bytestrings to a read-only 'Handle'. Note
-- that the generated handle is opened unbuffered in binary mode (i.e. no
-- newline translation is performed).
--
-- Note: the 'InputStream' passed into this function is wrapped in
-- 'lockingInputStream' to make it thread-safe.
--
-- /Since: 1.0.2.0./
inputStreamToHandle :: InputStream ByteString -> IO Handle
inputStreamToHandle :: InputStream ByteString -> IO Handle
inputStreamToHandle InputStream ByteString
is0 = do
    InputStream ByteString
is <- InputStream ByteString -> IO (InputStream ByteString)
forall a. InputStream a -> IO (InputStream a)
lockingInputStream InputStream ByteString
is0
    Handle
h <- InputStream ByteString
-> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
H.mkDuplexHandle InputStream ByteString
is FilePath
"*input-stream*" Maybe TextEncoding
forall a. Maybe a
Nothing (NewlineMode -> IO Handle) -> NewlineMode -> IO Handle
forall a b. (a -> b) -> a -> b
$! NewlineMode
H.noNewlineTranslation
    Handle -> BufferMode -> IO ()
H.hSetBuffering Handle
h BufferMode
H.NoBuffering
    Handle -> IO Handle
forall (m :: * -> *) a. Monad m => a -> m a
return Handle
h


------------------------------------------------------------------------------
-- | Converts an 'OutputStream' over bytestrings to a write-only 'Handle'. Note
-- that the 'Handle' will be opened in non-buffering mode; if you buffer the
-- 'OutputStream' using the 'Handle' buffering then @io-streams@ will copy the
-- 'Handle' buffer when sending 'ByteString' values to the output, which might
-- not be what you want.
--
-- When the output buffer, if used, is flushed (using 'System.IO.hFlush'), an
-- empty string is written to the provided 'OutputStream'.
--
-- /Note/: the 'OutputStream' passed into this function is wrapped in
-- 'lockingOutputStream' to make it thread-safe.
--
-- /Since: 1.0.2.0./
outputStreamToHandle :: OutputStream ByteString -> IO Handle
outputStreamToHandle :: OutputStream ByteString -> IO Handle
outputStreamToHandle OutputStream ByteString
os0 = do
    OutputStream ByteString
os <- OutputStream ByteString -> IO (OutputStream ByteString)
forall a. OutputStream a -> IO (OutputStream a)
lockingOutputStream OutputStream ByteString
os0
    Handle
h <- OutputStream ByteString
-> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
H.mkDuplexHandle OutputStream ByteString
os FilePath
"*output-stream*" Maybe TextEncoding
forall a. Maybe a
Nothing (NewlineMode -> IO Handle) -> NewlineMode -> IO Handle
forall a b. (a -> b) -> a -> b
$! NewlineMode
H.noNewlineTranslation
    Handle -> BufferMode -> IO ()
H.hSetBuffering Handle
h BufferMode
H.NoBuffering
    Handle -> IO Handle
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle -> IO Handle) -> Handle -> IO Handle
forall a b. (a -> b) -> a -> b
$! Handle
h


------------------------------------------------------------------------------
-- | Converts a pair of 'InputStream' and 'OutputStream' over bytestrings to a
-- read-write 'Handle'.
--
-- Note: the streams passed into this function are wrapped in
-- locking primitives to make them thread-safe.
--
-- /Since: 1.0.2.0./
streamPairToHandle :: InputStream ByteString -> OutputStream ByteString -> IO Handle
streamPairToHandle :: InputStream ByteString -> OutputStream ByteString -> IO Handle
streamPairToHandle InputStream ByteString
is0 OutputStream ByteString
os0 = do
    InputStream ByteString
is <- InputStream ByteString -> IO (InputStream ByteString)
forall a. InputStream a -> IO (InputStream a)
lockingInputStream InputStream ByteString
is0
    OutputStream ByteString
os <- OutputStream ByteString -> IO (OutputStream ByteString)
forall a. OutputStream a -> IO (OutputStream a)
lockingOutputStream OutputStream ByteString
os0
    Handle
h <- SP (InputStream ByteString) (OutputStream ByteString)
-> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
forall dev.
(IODevice dev, BufferedIO dev, Typeable dev) =>
dev -> FilePath -> Maybe TextEncoding -> NewlineMode -> IO Handle
H.mkDuplexHandle (InputStream ByteString
-> OutputStream ByteString
-> SP (InputStream ByteString) (OutputStream ByteString)
forall a b. a -> b -> SP a b
SP InputStream ByteString
is OutputStream ByteString
os) FilePath
"*stream*" Maybe TextEncoding
forall a. Maybe a
Nothing (NewlineMode -> IO Handle) -> NewlineMode -> IO Handle
forall a b. (a -> b) -> a -> b
$! NewlineMode
H.noNewlineTranslation
    Handle -> BufferMode -> IO ()
H.hSetBuffering Handle
h BufferMode
H.NoBuffering
    Handle -> IO Handle
forall (m :: * -> *) a. Monad m => a -> m a
return (Handle -> IO Handle) -> Handle -> IO Handle
forall a b. (a -> b) -> a -> b
$! Handle
h


------------------------------------------------------------------------------
-- | An 'InputStream' for 'IO.stdin'.
stdin :: InputStream ByteString
stdin :: InputStream ByteString
stdin = IO (InputStream ByteString) -> InputStream ByteString
forall a. IO a -> a
unsafePerformIO (Handle -> IO (InputStream ByteString)
handleToInputStream Handle
IO.stdin IO (InputStream ByteString)
-> (InputStream ByteString -> IO (InputStream ByteString))
-> IO (InputStream ByteString)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= InputStream ByteString -> IO (InputStream ByteString)
forall a. InputStream a -> IO (InputStream a)
lockingInputStream)
{-# NOINLINE stdin #-}


------------------------------------------------------------------------------
-- | An 'OutputStream' for 'IO.stdout'.
stdout :: OutputStream ByteString
stdout :: OutputStream ByteString
stdout = IO (OutputStream ByteString) -> OutputStream ByteString
forall a. IO a -> a
unsafePerformIO (Handle -> IO (OutputStream ByteString)
handleToOutputStream Handle
IO.stdout IO (OutputStream ByteString)
-> (OutputStream ByteString -> IO (OutputStream ByteString))
-> IO (OutputStream ByteString)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                          OutputStream ByteString -> IO (OutputStream ByteString)
forall a. OutputStream a -> IO (OutputStream a)
lockingOutputStream)
{-# NOINLINE stdout #-}


------------------------------------------------------------------------------
-- | An 'OutputStream' for 'IO.stderr'.
stderr :: OutputStream ByteString
stderr :: OutputStream ByteString
stderr = IO (OutputStream ByteString) -> OutputStream ByteString
forall a. IO a -> a
unsafePerformIO (Handle -> IO (OutputStream ByteString)
handleToOutputStream Handle
IO.stderr IO (OutputStream ByteString)
-> (OutputStream ByteString -> IO (OutputStream ByteString))
-> IO (OutputStream ByteString)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                          OutputStream ByteString -> IO (OutputStream ByteString)
forall a. OutputStream a -> IO (OutputStream a)
lockingOutputStream)
{-# NOINLINE stderr #-}