I'm trying to set the receive timeout on a socket constructed with the Network.Socket module. Here's a code snippet:
import Network.Socket
host = "127.0.0.1"
port = PortNumber 3000
main = do
  addrinfos <- getAddrInfo Nothing (Just host) (Just port)
  let serveraddr = head addrinfos
  sock <- socket (addrFamily serveraddr) Stream defaultProtocol
  setSocketOption sock RecvTimeOut 120000000
  connect sock (addrAddress serveraddr)
  msg <- recv sock 1024
  putStrLn msg
  sClose sock
The setSocketOption line throws an exception:
*** Exception: setSocketOption: invalid argument (Invalid argument)
setSocketOption only accepts Int arguments for settings, but not all of the socket options want an Int. Specifically RecvTimeOut and SendTimeOut expect a struct timeval. Is there another way to set these options from haskell?
I'm running GHC 7.4.2 on OSX 10.8.1
EDIT:
Network.Socket.Options seems like the best solution here, and getting it to compile on OSX turned out to require only a tiny pull request. As of version 0.2.0.1, network-socket-options now compiles on OSX. 
EDIT 2:
No luck with Network.Socket.Options. The setRecvTimeout function doesn't seem to have any effect on OSX. I ended up using timeout from the System.Timeout package as a workaround.
msg <- timeout 120000000 $ recv sock 1024
                I read about Haskell and struct definitions from here: http://therning.org/magnus/archives/315 . The struct timeval definition from the MSDN here (Its the same struct on GNU and probably on OSX): http://msdn.microsoft.com/en-us/library/windows/desktop/ms740560(v=vs.85).aspx
the time C-header:
...
typedef struct timeval {
    long tv_sec;
    long tv_usec;
} timeval;
....
It seems like you need to define some kind of struct constructor in Haskell. Or a complete binding to the time headers like that(taken from http://hackage.haskell.org/packages/archive/bindings-common/0.1.4/doc/html/src/CTypes.html ) :
                module CTypes where
import Foreign
import Foreign.C
-- time.h
data Tm = Tm {
    tm'sec,
    tm'min,
    tm'hour,
    tm'mday,
    tm'mon,
    tm'year,
    tm'wday,
    tm'yday,
    tm'isdst :: CInt
   }
instance Storable Tm where
    sizeOf _ = fromIntegral size_of_tm
    alignment = sizeOf
    peek p =
        with 0 $ \p1 -> with 0 $ \p2 -> with 0 $ \p3 ->
        with 0 $ \p4 -> with 0 $ \p5 -> with 0 $ \p6 ->
        with 0 $ \p7 -> with 0 $ \p8 -> with 0 $ \p9 ->
        c2hs_tm p p1 p2 p3 p4 p5 p6 p7 p8 p9 >>
        peek p1 >>= \v1 -> peek p2 >>= \v2 -> peek p3 >>= \v3 ->
        peek p4 >>= \v4 -> peek p5 >>= \v5 -> peek p6 >>= \v6 ->
        peek p7 >>= \v7 -> peek p8 >>= \v8 -> peek p9 >>= \v9 ->
        return $ Tm v1 v2 v3 v4 v5 v6 v7 v8 v9
    poke p (Tm v1 v2 v3 v4 v5 v6 v7 v8 v9) =
        hs2c_tm p v1 v2 v3 v4 v5 v6 v7 v8 v9
foreign import ccall size_of_tm :: CInt
foreign import ccall hs2c_tm
    :: Ptr Tm -> CInt -> CInt -> CInt -> CInt ->
       CInt -> CInt -> CInt -> CInt -> CInt -> IO ()
foreign import ccall c2hs_tm
    :: Ptr Tm -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt ->
       Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt ->
       Ptr CInt -> IO ()
-- sys/time.h
data Timeval = Timeval {timeval'tv_sec, timeval'tv_usec :: CLong}
instance Storable Timeval where
    sizeOf _ = fromIntegral size_of_timeval
    alignment = sizeOf
    peek p =
        with 0 $ \p1 ->
        with 0 $ \p2 ->
        c2hs_timeval p p1 p2 >>
        peek p1 >>= \v1 ->
        peek p2 >>= \v2 ->
        return $ Timeval {timeval'tv_sec = v1, timeval'tv_usec = v2}
    poke p v = hs2c_timeval p (timeval'tv_sec v) (timeval'tv_usec v)
foreign import ccall "size_of_timeval" size_of_timeval
    :: CInt
foreign import ccall "hs2c_timeval" hs2c_timeval
    :: Ptr Timeval -> CLong -> CLong -> IO ()
foreign import ccall "c2hs_timeval" c2hs_timeval
    :: Ptr Timeval -> Ptr CLong -> Ptr CLong -> IO ()
A stripped down to the necessary version would be:
module CTypes where
import Foreign
import Foreign.C
-- sys/time.h
data Timeval = Timeval {timeval'tv_sec, timeval'tv_usec :: CLong}
You should then be able to initialize a timeval struct by:
timeval <- Timeval { tv_sec=120 , tv_usec=0 }
I hope that helps a bit...
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With