[Haskell-cafe] controlling timeout for Network.Socket.connect - how?

Belka lambda-belka at yandex.ru
Tue Feb 24 09:58:06 EST 2009


It's hard to belive, that nobody ever tackled/solved the subj. problem. I
still can delay a bit solving it, in hope somebody would share experience. 

Regards,
Belka


Belka wrote:
> 
> Hello, communion people!
> 
> I have a problem and ask for an advice. 
> I'm dealing with sockets on *Linux* platform (Network.Socket). The problem
> is that I can't fully control timeout for (connect :: Socket -> SockAddr
> -> IO ()) operation. 
> On my system the timeout is - 3 seconds - I want to be able to change that
> in run-time. Well I managed to find out how to make it LESS THAN 3 seconds
> - using System.Timeout. But how to make timeout bigger (for example 9
> seconds) is a mystery.
> (Notice: in order to achieve 9 seconds timeout - just repeating *connect*
> 3 times won't be effective for long-slow-way-connections. So it's not a
> solution.)
> 
> The source code of Network.Socket.connect, taken from darcs:
> ---------------------------------
> -- Connecting a socket
> --
> -- Make a connection to an already opened socket on a given machine
> -- and port.  assumes that we have already called createSocket,
> -- otherwise it will fail.
> --
> -- This is the dual to $bindSocket$.  The {\em server} process will
> -- usually bind to a port number, the {\em client} will then connect
> -- to the same port number.  Port numbers of user applications are
> -- normally agreed in advance, otherwise we must rely on some meta
> -- protocol for telling the other side what port number we have been
> -- allocated.
> 
> connect :: Socket	-- Unconnected Socket
> 	-> SockAddr 	-- Socket address stuff
> 	-> IO ()
> 
> connect sock@(MkSocket s _family _stype _protocol socketStatus) addr = do
>  modifyMVar_ socketStatus $ \currentStatus -> do
>  if currentStatus /= NotConnected 
>   then
>    ioError (userError ("connect: can't peform connect on socket in status
> " ++
>          show currentStatus))
>   else do
>    withSockAddr addr $ \p_addr sz -> do
> 
>    let  connectLoop = do
>        	   r <- c_connect s p_addr (fromIntegral sz)
>        	   if r == -1
>        	       then do 
> 		       rc <- c_getLastError
> 		       case rc of
> 		         10093 -> do -- WSANOTINITIALISED
> 			   withSocketsDo (return ())
> 	       	           r <- c_connect s p_addr (fromIntegral sz)
> 	       	           if r == -1
> 			    then (c_getLastError >>= throwSocketError "connect")
> 			    else return r
> 			 _ -> throwSocketError "connect" rc
>        	       else return r
> 
> 	connectBlocked = do 
> #if !defined(__HUGS__)
> 	   threadWaitWrite (fromIntegral s)
> #endif
> 	   err <- getSocketOption sock SoError
> 	   if (err == 0)
> 	   	then return 0
> 	   	else do ioError (errnoToIOError "connect" 
> 	   			(Errno (fromIntegral err))
> 	   			Nothing Nothing)
> 
>    connectLoop
>    return Connected
> 
> ---------------------------------
> I know that controlling timeout is somehow connected to select(2) (I'm
> currently investigating this matter...), but it's not in the Network or
> Network.Socket libs (but in the libs that they FFI with). 
> Hope I won't have to rewrite these low-level functions.... >__<
> Could anybody, please share some experience on how to adjust timeout for
> *connect*? 
> 
> Thanks in advance,
> Best regards,
> Belka
> 

-- 
View this message in context: http://www.nabble.com/controlling-timeout-for-Network.Socket.connect---how--tp22139581p22181071.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list