{-# LANGUAGE CPP #-}
#include "HsNetDef.h"
module Network.Socket.Shutdown (
ShutdownCmd(..)
, shutdown
, gracefulClose
) where
import qualified Control.Exception as E
import Foreign.Marshal.Alloc (mallocBytes, free)
import Control.Concurrent (threadDelay)
import Network.Socket.Buffer
import Network.Socket.Imports
import Network.Socket.Internal
import Network.Socket.Types
data ShutdownCmd = ShutdownReceive
| ShutdownSend
| ShutdownBoth
sdownCmdToInt :: ShutdownCmd -> CInt
sdownCmdToInt ShutdownReceive = 0
sdownCmdToInt ShutdownSend = 1
sdownCmdToInt ShutdownBoth = 2
shutdown :: Socket -> ShutdownCmd -> IO ()
shutdown s stype = void $ withFdSocket s $ \fd ->
throwSocketErrorIfMinus1Retry_ "Network.Socket.shutdown" $
c_shutdown fd $ sdownCmdToInt stype
foreign import CALLCONV unsafe "shutdown"
c_shutdown :: CInt -> CInt -> IO CInt
gracefulClose :: Socket -> Int -> IO ()
gracefulClose s tmout = sendRecvFIN `E.finally` close s
where
sendRecvFIN = do
shutdown s ShutdownSend
E.bracket (mallocBytes bufSize) free $ \buf -> do
{-# SCC "" #-} recvEOFloop buf
clock = 200
recvEOFloop buf = loop 0
where
loop delay = do
r <- recvBufNoWait s buf bufSize
let delay' = delay + clock
when (r == -1 && delay' < tmout) $ do
threadDelay (clock * 1000)
loop delay'
bufSize = 1024