-- |This module provides a byte string \"stream\" interface.  This
-- interface provides some common operations on a value which
-- supports reading and writing byte strings.
module Network.HaskellNet.BSStream
    ( BSStream(..)
    , handleToStream
    )
where

import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
import System.IO

-- |A byte string stream.
data BSStream =
    BSStream { BSStream -> IO ByteString
bsGetLine :: IO ByteString
             -- ^Read a line from the stream.  Should return the line
             -- which was read, including the newline.
             , BSStream -> Int -> IO ByteString
bsGet :: Int -> IO ByteString
             -- ^Read the specified number of bytes from the stream.
             -- Should block until the requested bytes can be read.
             , BSStream -> ByteString -> IO ()
bsPut :: ByteString -> IO ()
             -- ^Write the specified byte string to the stream.
             -- Should flush the stream after writing.
             , BSStream -> IO ()
bsFlush :: IO ()
             -- ^Flush the stream.
             , BSStream -> IO ()
bsClose :: IO ()
             -- ^Close the stream.
             , BSStream -> IO Bool
bsIsOpen :: IO Bool
             -- ^Is the stream open?
             , BSStream -> Int -> IO Bool
bsWaitForInput :: Int -> IO Bool
             -- ^Is data available?
             }

-- |Build a byte string stream which operates on a 'Handle'.
handleToStream :: Handle -> BSStream
handleToStream :: Handle -> BSStream
handleToStream Handle
h =
    BSStream :: IO ByteString
-> (Int -> IO ByteString)
-> (ByteString -> IO ())
-> IO ()
-> IO ()
-> IO Bool
-> (Int -> IO Bool)
-> BSStream
BSStream { bsGetLine :: IO ByteString
bsGetLine = Handle -> IO ByteString
BS.hGetLine Handle
h
             , bsGet :: Int -> IO ByteString
bsGet = Handle -> Int -> IO ByteString
BS.hGet Handle
h
             , bsPut :: ByteString -> IO ()
bsPut = \ByteString
s -> Handle -> ByteString -> IO ()
BS.hPut Handle
h ByteString
s IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hFlush Handle
h
             , bsFlush :: IO ()
bsFlush = Handle -> IO ()
hFlush Handle
h
             , bsClose :: IO ()
bsClose = do
                 Bool
op <- Handle -> IO Bool
hIsOpen Handle
h
                 if Bool
op then (Handle -> IO ()
hClose Handle
h) else () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
             , bsIsOpen :: IO Bool
bsIsOpen = Handle -> IO Bool
hIsOpen Handle
h
             , bsWaitForInput :: Int -> IO Bool
bsWaitForInput = Handle -> Int -> IO Bool
hWaitForInput Handle
h
             }