Steve Roggenkamp writes:
> I can't get getHostByAddr to work on a Linux 2.0.18, RedHat 4.0. The
> following is a small test program illustrating the problem:
>
> ---------------cut here------------------------------
> module Main where
> import BSD
> import SocketPrim
> import System
>
> main =
> getArgs >>= \ [host] ->
> putStr ("Host: " ++ host ++ "\n" ) >>
> getHostByName host >>= \ (HostEntry _ _ _ haddrs) ->
> putStr ("Address: " ++ (inet_ntoa (head haddrs)) ++ "\n" ) >>
> getHostByAddr AF_INET (head haddrs) >>= \ (HostEntry hname _ _ _ ) ->
> putStr ("HostName: " ++ hname ++ "\n" )
>
> -----------------------------------------------------
> Here is the output I get when I run it:
>
> [skr@roggen net008]$ tmp roggen
> Host: roggen
> Address: 192.168.29.1
>
> Fail: I/O error: NoSuchThing: no such host entry
>
Hi,
thanks for a fine report, the invocation of gethostaddr() in the BSD
module is simply wrong, I'm afraid. If you've compiled up 2.08
from source, the patch at the end fixes the problem.
--Sigbjorn
*** fptools/hslibs/ghc/src/BSD.lhs.~1~ Wed Mar 19 03:03:35 1997
--- fptools/hslibs/ghc/src/BSD.lhs Fri Oct 31 19:34:44 1997
***************
*** 210,217 ****
getHostByAddr :: Family -> HostAddress -> IO HostEntry
getHostByAddr family addr =
! _casm_ ``%r = gethostbyaddr (%0, sizeof(struct in_addr), %1);''
! (inet_ntoa addr)
(packFamily family) `thenIO_Prim` \ ptr ->
if ptr == ``NULL'' then
fail (IOError Nothing NoSuchThing "no such host entry")
--- 210,219 ----
getHostByAddr :: Family -> HostAddress -> IO HostEntry
getHostByAddr family addr =
! _casm_ ``struct in_addr addr;
! addr.s_addr = htonl(%0);
! %r = gethostbyaddr ((char*)&addr, sizeof(struct in_addr), %1);''
! addr
(packFamily family) `thenIO_Prim` \ ptr ->
if ptr == ``NULL'' then
fail (IOError Nothing NoSuchThing "no such host entry")