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

-----------------------------------------------------

Here is a Perl program which indicates that the gethostbyaddr call
works:

-----------------------------------------------------
#!/usr/bin/perl
#
($host) = @ARGV;
$AF_INET = 2;

($name,$aliases,$type,$len,$addr)   = gethostbyname($host);
($hname,$aliases,$type,$len,@addrs) = gethostbyaddr($addr,$AF_INET);
($a,$b,$c,$d) = unpack('C4',$addr );
printf( "Host: %s ($name)\n", $host );
printf( "Address: %d.%d.%d.%d\n", $a,$b,$c,$d );
printf( "HostName: %s\n", $hname );

-----------------------------------------------------

And here is the output from the Perl program:

[skr@roggen net008]$ tmp.pl roggen
Host: roggen (roggen.infinet.com)
Address: 192.168.29.1
HostName: roggen.infinet.com
-----------------------------------------------------

Thanks,

Steve 
-----
Steve Roggenkamp
InterNet:    [EMAIL PROTECTED]
Address:     9159 Eversole Run Road
             Powell, OH  43065  USA
Phone:       614.873.6573
WWW:         http://www.infinet.com/~sroggen/home.html

Reply via email to