
Rich Neswold wrote:
On 12/13/06, Thorkil Naur
wrote: I am not an expert on sockets, but I have both a Linux installation and a PPC Mac OS X 10.4 with both ghc-6.4.1 and ghc-6.6. So if you allow me some additional details (such as complete program texts), perhaps I can perform some useful experiments under your conductance.
I can reproduce it with the following:
module Main where
import Control.Exception import Network.Socket import System.IO
allocSocket :: IO Socket allocSocket = do { s <- socket AF_INET Datagram 0 ; handle (\e -> sClose s >> throwIO e) $ do { connect s (SockAddrInet 6802 0x7f000001) ; return s } }
main :: IO () main = withSocketsDo $ do { s <- allocSocket ; getChar ; sClose s }
If you run the program on OSX, you can check the bound address while it's waiting for a keystroke. Type "netstat -an -f inet | grep 6802" to see. I get:
udp4 0 0 127.0.0.1.61704 127.0.0.1.6802
which is correct. When I run this program on Linux/i386, I get:
udp 0 0 (anonymized):33412 1.0.0.127:6802 ESTABLISHED
(I removed my IP address.) The second bound address, however, is wrong: the octets are in the wrong order. Notice, though, that the port number is correct!
Thanks for looking into this!
It does expect the address to be in network byte order instead of host byte order, which is usually done using htons and htonl. This seems to do what you want (running SUSE 10.1 on an Intel box): {-# OPTIONS -fglasgow-exts #-} module Main where import Control.Exception import Network.Socket import System.IO import Data.Word(Word32) foreign import ccall unsafe "htonl" htonl :: Word32 -> Word32 allocSocket :: IO Socket allocSocket = do { s <- socket AF_INET Datagram 0 ; handle (\e -> sClose s >> throwIO e) $ do { connect s (SockAddrInet 6802 (htonl 0x7f000001)) ; return s } } main :: IO () main = withSocketsDo $ do { s <- allocSocket ; getChar ; sClose s } The main change is with importing "htonl" to convert to the right byte ordering (the other is adding the OPTIONS comment). I'm not that familiar with GHC yet, so maybe there is something that does this that is also available outside this module that I'm unaware of. It seems that iNADDR_ANY uses this internally to get the proper address format. It also looks like 6802 is converted into a PortNumber behind the scenes, which involves using htons, making it correct on both machines. Mark