module Network.HaskellNet.Debug ( debugStream ) where import Network.HaskellNet.BSStream import qualified Data.ByteString.Char8 as BS import System.IO debugStream :: BSStream -> BSStream debugStream :: BSStream -> BSStream debugStream BSStream inner = BSStream inner { bsGetLine :: IO ByteString bsGetLine = BSStream -> IO ByteString debugBsGetLine BSStream inner , bsGet :: Int -> IO ByteString bsGet = BSStream -> Int -> IO ByteString debugBsGet BSStream inner , bsPut :: ByteString -> IO () bsPut = BSStream -> ByteString -> IO () debugBsPut BSStream inner } debugBsGetLine :: BSStream -> IO BS.ByteString debugBsGetLine :: BSStream -> IO ByteString debugBsGetLine BSStream s = do Handle -> String -> IO () hPutStr Handle stderr String "reading with bsGetLine..." Handle -> IO () hFlush Handle stderr ByteString l <- BSStream -> IO ByteString bsGetLine BSStream s Handle -> ByteString -> IO () BS.hPutStrLn Handle stderr ByteString l ByteString -> IO ByteString forall (m :: * -> *) a. Monad m => a -> m a return ByteString l debugBsGet :: BSStream -> Int -> IO BS.ByteString debugBsGet :: BSStream -> Int -> IO ByteString debugBsGet BSStream s Int len = do Handle -> String -> IO () hPutStr Handle stderr (String -> IO ()) -> String -> IO () forall a b. (a -> b) -> a -> b $ String "reading with bsGet "String -> String -> String forall a. [a] -> [a] -> [a] ++Int -> String forall a. Show a => a -> String show Int lenString -> String -> String forall a. [a] -> [a] -> [a] ++String "..." Handle -> IO () hFlush Handle stderr ByteString chunk <- BSStream -> Int -> IO ByteString bsGet BSStream s Int len Handle -> ByteString -> IO () BS.hPutStrLn Handle stderr ByteString chunk ByteString -> IO ByteString forall (m :: * -> *) a. Monad m => a -> m a return ByteString chunk debugBsPut :: BSStream -> BS.ByteString -> IO () debugBsPut :: BSStream -> ByteString -> IO () debugBsPut BSStream s ByteString str = do Handle -> String -> IO () hPutStr Handle stderr String "putting with bsPut (" Handle -> ByteString -> IO () BS.hPutStrLn Handle stderr ByteString str Handle -> String -> IO () hPutStr Handle stderr (String ")...") Handle -> IO () hFlush Handle stderr BSStream -> ByteString -> IO () bsPut BSStream s ByteString str BSStream -> IO () bsFlush BSStream s Handle -> String -> IO () hPutStrLn Handle stderr String "done" () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return ()