On 12/13/06, Thorkil Naur <[EMAIL PROTECTED]> 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!

--
Rich

AIM : rnezzy
ICQ : 174908475
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to