Below is the relevant source code.

David


foreign import ccall unsafe "my_inet_ntoa"
  c_inet_ntoa :: HostAddress -> IO (Ptr CChar)

foreign import CALLCONV unsafe "inet_addr"
  c_inet_addr :: Ptr CChar -> IO HostAddress

-- -----------------------------------------------------------------------------
-- Internet address manipulation routines:

inet_addr :: String -> IO HostAddress
inet_addr ipstr = do
   withCString ipstr $ \str -> do
   had <- c_inet_addr str
   if had == -1
    then ioError (userError ("inet_addr: Malformed address: " ++ ipstr))
    else return had  -- network byte order

inet_ntoa :: HostAddress -> IO String
inet_ntoa haddr = do
  pstr <- c_inet_ntoa haddr
  peekCString pstr


On 5/7/05, Dominic Steinitz <[EMAIL PROTECTED]> wrote:
> Does anyone know why these are in the IO monad? Aren't they pure functions
> converting between dotted-decimal strings and a 32-bit network byte ordered
> binary value?
> 
> Dominic.
> 
> http://www.haskell.org/ghc/docs/latest/html/libraries/network/Network.Socket.html#v%3Ainet_addr
> http://www.haskell.org/ghc/docs/latest/html/libraries/network/Network.Socket.html#v%3Ainet_ntoa
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to