module Network.HaskellNet.BSStream
( BSStream(..)
, handleToStream
)
where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
import System.IO
data BSStream =
BSStream { BSStream -> IO ByteString
bsGetLine :: IO ByteString
, BSStream -> Int -> IO ByteString
bsGet :: Int -> IO ByteString
, BSStream -> ByteString -> IO ()
bsPut :: ByteString -> IO ()
, BSStream -> IO ()
bsFlush :: IO ()
, BSStream -> IO ()
bsClose :: IO ()
, BSStream -> IO Bool
bsIsOpen :: IO Bool
, BSStream -> Int -> IO Bool
bsWaitForInput :: Int -> IO Bool
}
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
}