Socket Options

Simon Marlow simonmar at microsoft.com
Mon Jun 28 06:50:08 EDT 2004


On 26 June 2004 02:48, Glynn Clements wrote:

> 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 ()

I'm tempted to replace the current setSocketOption with this version.
Would anyone object?  Or perhaps we should include the new version under
a different name?

Cheers,
	Simon


More information about the Glasgow-haskell-users mailing list