{-# OPTIONS_GHC -fno-warn-orphans #-}
module Network.StreamSocket
( handleSocketError
, myrecv
) where
import Network.Stream
( Stream(..), ConnError(ErrorReset, ErrorMisc), Result
)
import Network.Socket
( Socket, getSocketOption, shutdown
, ShutdownCmd(ShutdownBoth), SocketOption(SoError)
)
import Network.Socket.ByteString (send, recv)
import qualified Network.Socket
( close )
import Network.HTTP.Base ( catchIO )
import Network.HTTP.Utils ( fromUTF8BS, toUTF8BS )
import Control.Monad (liftM)
import Control.Exception as Exception (IOException)
import System.IO.Error (isEOFError)
handleSocketError :: Socket -> IOException -> IO (Result a)
handleSocketError sk e =
do se <- getSocketOption sk SoError
case se of
0 -> ioError e
10054 -> return $ Left ErrorReset
_ -> return $ Left $ ErrorMisc $ show se
myrecv :: Socket -> Int -> IO String
myrecv sock len =
let handler e = if isEOFError e then return [] else ioError e
in catchIO (fmap fromUTF8BS (recv sock len)) handler
instance Stream Socket where
readBlock sk n = readBlockSocket sk n
readLine sk = readLineSocket sk
writeBlock sk str = writeBlockSocket sk str
close sk = do
shutdown sk ShutdownBoth
Network.Socket.close sk
closeOnEnd _sk _ = return ()
readBlockSocket :: Socket -> Int -> IO (Result String)
readBlockSocket sk n = (liftM Right $ fn n) `catchIO` (handleSocketError sk)
where
fn x = do { str <- myrecv sk x
; let len = length str
; if len < x
then ( fn (x-len) >>= \more -> return (str++more) )
else return str
}
readLineSocket :: Socket -> IO (Result String)
readLineSocket sk = (liftM Right $ fn "") `catchIO` (handleSocketError sk)
where
fn str = do
c <- myrecv sk 1
if null c || c == "\n"
then return (reverse str++c)
else fn (head c:str)
writeBlockSocket :: Socket -> String -> IO (Result ())
writeBlockSocket sk str = (liftM Right $ fn str) `catchIO` (handleSocketError sk)
where
fn [] = return ()
fn x = send sk (toUTF8BS x) >>= \i -> fn (drop i x)