Socket Options
Glynn Clements
glynn.clements at virgin.net
Fri Jun 25 21:47:51 EDT 2004
Peter Simons wrote:
> the Network module provides the data type SocketOption. I am
> particularly interested in setting the RecvTimeOut and
> SendTimeOut values, but I wonder how to set them. The
> function
>
> setSocketOption :: Socket -> SocketOption -> Int -> IO ()
>
> allows me only 'Int' parameters, but the kernel expects a
> struct timeval here -- or more accurately, a pointer to one.
> Do I really have to engage in FFI pointer wizardry here, or
> is there a simpler way to set these values?
You can't set the send/receive timeouts using that function; it always
passes a C int (with the optlen parameter set to sizeof(int)). You
would have to re-write it with a more flexible interface, e.g.:
> import Foreign
> import Foreign.C
> import Network.Socket hiding (setSocketOption)
>
> foreign import CALLCONV unsafe "setsockopt"
> c_setsockopt :: CInt -> CInt -> CInt -> Ptr () -> CInt -> IO CInt
>
> setSocketOption :: (Storable a) => Socket
> -> SocketOption -- Option Name
> -> a -- Option Value
> -> IO ()
> setSocketOption (MkSocket s _ _ _ _) so v = do
> with v $ \ptr_v -> do
> throwErrnoIfMinus1_ "setSocketOption" $
> c_setsockopt s (socketOptLevel so) (packSocketOption so) (castPtr ptr_v)
> (fromIntegral (sizeOf v))
> return ()
Note: neither socketOptLevel nor packSocketOption are exported from
Network.Socket, so you would need to copy those (or just pass a pair
of integers instead of the SocketOption).
> Am I even supposed to set them, or is there a better way to
> specify general I/O timeouts than on the socket level?
Non-blocking I/O and select/poll; although I don't know how well that
is supported.
--
Glynn Clements <glynn.clements at virgin.net>
More information about the Glasgow-haskell-users
mailing list