[Haskell-cafe] Network.Socket error in MacOS 10.5?

Johan Tibell johan.tibell at gmail.com
Wed Aug 26 14:07:39 EDT 2009


On Wed, Aug 26, 2009 at 6:33 PM, kenny lu<haskellmail at gmail.com> wrote:
> Hi,
>
> I encountered a problem with Network.Socket in MacOS 10.5
> Here is the code that I am testing,
>
> -----------------------------------------
> -----------------------------------------
> module Main where
>
> import qualified Network.Socket as Socket
>
> main :: IO ()
> main =
>     do { (hostname, _) <- Socket.getNameInfo [] True False
> (Socket.SockAddrUnix "localhost")
>        -- (hostname, _) <- Socket.getNameInfo [] True False
> (Socket.SockAddrInet 9000  (127 + 0 * 256 + 0 * 256^2 + 1 * 256^3))
>        ; putStrLn (show hostname)
>        }
>
>
> Running the above code yields the following error
> ghc --make -O2 TestSocket.hs
> [1 of 1] Compiling Main             ( TestSocket.hs, TestSocket.o )
> Linking TestSocket ...
> $ ./TestSocket
> TestSocket: getNameInfo: does not exist (ai_family not supported)
>
> If I switch to SockAddrInet instead, the error is gone.
>
> I am using GHC 6.10.3 and Network 2.2.1

Is SockAddrUnix supposed to work on Mac OS X? Could you test it by
e.g. writing a small C program that uses it?

-- Johan


More information about the Haskell-Cafe mailing list