darcs patch: Implementation of aton and ntoa outside ... (and 1 more)

Mon Sep 25 16:55:55 JST 2006 Robert Marlow

Warning: This is my first use of FFI so it's probably buggy. In particular I don't know how to use structs from haskell so I think aton is probably incorrect in how it uses the Ptr HostAddress. Sorry for the email flood. On Mon, 2006-09-25 at 17:15 +0900, Robert Marlow wrote:
Mon Sep 25 16:55:55 JST 2006 Robert Marlow
* Implementation of aton and ntoa outside the IO monad This is a second attempt at the earlier patch
inet_ntoa and inet_aton can be implemented purely to avoid the need for the IO monad. Additionally, inet_addr is currently incorrect due to using the inet_addr C function which is considered obsolete due to incorrectly failing while converting 255.255.255.255 as an address.
Mon Sep 25 17:12:52 JST 2006 Robert Marlow
* Fixed bugs in names of aton and ntoa _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries -- Robert Marlow

Robert Marlow wrote:
Mon Sep 25 16:55:55 JST 2006 Robert Marlow
* Implementation of aton and ntoa outside the IO monad This is a second attempt at the earlier patch
inet_ntoa and inet_aton can be implemented purely to avoid the need for the IO monad. Additionally, inet_addr is currently incorrect due to using the inet_addr C function which is considered obsolete due to incorrectly failing while converting 255.255.255.255 as an address.
Mon Sep 25 17:12:52 JST 2006 Robert Marlow
* Fixed bugs in names of aton and ntoa ------------------------------------------------------------------------
New patches:
[Implementation of aton and ntoa outside the IO monad Robert Marlow
**20060925075555 This is a second attempt at the earlier patch
inet_ntoa and inet_aton can be implemented purely to avoid the need for the IO monad. Additionally, inet_addr is currently incorrect due to using the inet_addr C function which is considered obsolete due to incorrectly failing while converting 255.255.255.255 as an address.
] { hunk ./Network/Socket.hsc 93 + aton, -- :: String -> HostAddress + ntoa, -- :: HostAddress -> String hunk ./Network/Socket.hsc 1886 +-- Implementations outside the IO Monad + +inet_aton :: String -> HostAddress +inet_aton ipstr = unsafePerformIO $ do + withCString ipstr $ \str -> do + allocaBytes 4 $ \buf -> do + success <- c_inet_aton str buf + if success == -1 + then throw $ ErrorCall $ "inet_addr: Malformed address: " ++ ipstr + else peek buf + +inet_ntoa :: HostAddress -> String +inet_ntoa haddr = unsafePerformIO $ do + pstr <- c_inet_ntoa haddr + peekCString pstr
inet_ntoa() uses a static buffer, so it isn't threadsafe. So while the current IO version is already broken, putting unsafePerformIO around it makes the problem more likely to manifest, and harder to avoid. We really need to do this in Haskell code, I think. Cheers, Simon

On Fri, Sep 29, 2006 at 01:19:40PM +0100, Simon Marlow wrote:
inet_ntoa() uses a static buffer, so it isn't threadsafe. So while the current IO version is already broken, putting unsafePerformIO around it makes the problem more likely to manifest, and harder to avoid. We really need to do this in Haskell code, I think.
If it is portable enough then inet_ntop might be another solution. Thanks Ian

On Fri, 2006-09-29 at 13:19 +0100, Simon Marlow wrote:
inet_ntoa() uses a static buffer, so it isn't threadsafe. So while the current IO version is already broken, putting unsafePerformIO around it makes the problem more likely to manifest, and harder to avoid. We really need to do this in Haskell code, I think.
I've attached a new revision of the earlier Data.Byte module I sent to
this list.
I've taken Bulat's suggestion on making flipEndian more efficient and
extended it so it should work with all word sizes as well as signed
types such as Ints.
The file also includes purely functional versions of aton and ntoa,
though a module named Data.Byte is the wrong place for them.
One problem is that aton and ntoa currently only work with ipv4
addresses. There should probably be versions for ipv6 and any others.
This doesn't seem to be a problem the current inet_addr and inet_ntoa
don't suffer from though.
A lot of the functions don't work with Integers due to a use of bitSize.
--
Robert Marlow

Hello Robert, Monday, October 2, 2006, 5:06:57 AM, you wrote:
The file also includes purely functional versions of aton and ntoa, though a module named Data.Byte is the wrong place for them.
i think that the whole module is better to name ByteOrder or like and put it somewhere in Codec.* hierarchy also, i propose to not use regexs for such simple task, (split '.') does what you need: split :: (Eq a) => a -> [a] -> [[a]] split c s = let (chunk, rest) = break (==c) s in case rest of [] -> [chunk] _:rest -> chunk : split c rest -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Robert: would you like to resubmit this suggestion using the new submission guidelines for library additions? http://www.haskell.org/haskellwiki/Library_submissions Cheers, Simon Robert Marlow wrote:
On Fri, 2006-09-29 at 13:19 +0100, Simon Marlow wrote:
inet_ntoa() uses a static buffer, so it isn't threadsafe. So while the current IO version is already broken, putting unsafePerformIO around it makes the problem more likely to manifest, and harder to avoid. We really need to do this in Haskell code, I think.
I've attached a new revision of the earlier Data.Byte module I sent to this list.
I've taken Bulat's suggestion on making flipEndian more efficient and extended it so it should work with all word sizes as well as signed types such as Ints.
The file also includes purely functional versions of aton and ntoa, though a module named Data.Byte is the wrong place for them.
One problem is that aton and ntoa currently only work with ipv4 addresses. There should probably be versions for ipv6 and any others. This doesn't seem to be a problem the current inet_addr and inet_ntoa don't suffer from though.
A lot of the functions don't work with Integers due to a use of bitSize.
------------------------------------------------------------------------
module Data.Byte ( ByteOrder (..) , hostByteOrder , networkByteOrder , changeByteOrder , hton , ntoh
, byteShow , byteRead , word8ToChar , charToWord8 , showBits
, logShift , logShiftL , logShiftR
, flipEndian
, word8Split , word8Concat
, aton , ntoa ) where
import Control.Exception
import Data.Bits import Data.Char import Data.List import Data.Word
import Network.Socket
import System.Info import System.IO.Unsafe
import Foreign.Marshal.Utils ( with ) import Foreign.Storable ( peekByteOff )
import Text.Regex
data ByteOrder = BigEndian | LittleEndian deriving ( Eq, Show, Read )
hostByteOrder :: ByteOrder hostByteOrder = let test = (word8Concat [1,2]) :: Word16 answer = (unsafePerformIO $ with test firstByte) :: Word8 in case answer of 1 -> LittleEndian 2 -> BigEndian otherwise -> throw $ ErrorCall $ "Unexpected result when checking byte order" where firstByte = (flip peekByteOff) 0
networkByteOrder :: ByteOrder networkByteOrder = BigEndian
changeByteOrder :: (Bits a, Integral a) => ByteOrder -> ByteOrder -> a -> a changeByteOrder bo1 bo2 x = if bo1 == bo2 then x else flipEndian x
-- |Host to Network byteorder hton :: (Bits a, Integral a) => a -> a hton = changeByteOrder hostByteOrder networkByteOrder
-- |Network to Host byteorder ntoh :: (Bits a, Integral a) => a -> a ntoh = hton
-- |Converts the argument to a string representing the bytes in the -- argument byteShow :: (Integral a, Bits a) => a -> String byteShow = (map word8ToChar) . word8Split
-- |Reads a string of bytes. Reads only as many bytes as are needed -- to represent the resulting type. Does not work with Integers byteRead :: (Bits a, Integral a) => String -> a byteRead = word8Concat . (map charToWord8)
word8ToChar :: Word8 -> Char word8ToChar = chr . fromEnum
charToWord8 :: Char -> Word8 charToWord8 = toEnum . ord
-- |Returns a string representing the bits of the argument. -- Does not work with Integers showBits :: Bits a => a -> String showBits x = showBits' ((bitSize x) -1) x where showBits' i x | i < 0 = "" | testBit x i = '1' : showBits' (i-1) x | otherwise = '0' : showBits' (i-1) x
-- |Reverses the endianness of the argument. Does not work -- with Integers flipEndian :: Bits a => a -> a flipEndian x = bwOr $ zipWith logShift bytes shiftLengths where bytes = map (x .&.) $ map (shift 255) [0,8..sz-8] shiftLengths = [sz-8,sz-24..(negate sz)+8] sz = bitSize x
-- flipEndian = word8Concat . reverse . word8Split
bwOr :: Bits a => [a] -> a bwOr = foldr (.|.) 0
-- |Logical shift version of the shift operator. Does not work with -- Integers logShift :: Bits a => a -> Int -> a logShift x i | i >= 0 = logShiftL x i | otherwise = logShiftR x i
-- |Logical shift version of the shiftR operator. Does not work with -- Integers logShiftR :: Bits a => a -> Int -> a logShiftR x i | isSigned x = clearBits (shiftR x i) (sz+i) sz | otherwise = shiftR x i where sz = bitSize x
-- |Identical to the shiftL operator. logShiftL :: Bits a => a -> Int -> a logShiftL = shiftL
clearBits :: Bits a => a -> Int -> Int -> a clearBits x min max | min >= max = x | otherwise = clearBits (clearBit x min) (min+1) max
-- |Returns a list of Word8s in little-endian byte order. Does not -- work with Integers word8Split :: (Integral a, Bits a) => a -> [Word8] word8Split x = map (fromIntegral . (shiftR x)) [0,8..sz-8] where sz = bitSize x
-- |Concats a list of Word8s in little-endian byte order. -- For big-endian byte order reverse the Word8s first. -- Does not work with Integers word8Concat :: (Bits a, Integral a) => [Word8] -> a word8Concat w8s = bwOr $ zipWith shiftL xs [0,8..sz-8] where xs = map fromIntegral w8s sz = bitSize $ head xs
-- |Implementation of inet_addr outside the IO monad aton :: String -> HostAddress aton ipstr = word8Concat $ toBytes ipstr where toBytes = (map readByte) . checkLength . dotSplit dotSplit = splitRegex $ mkRegex "\\." checkLength x = if length x == 4 then x else malformed readByte b = case reads b of ((x,""):_) -> if x >= 0 && x <= 255 then fromInteger x else malformed otherwise -> malformed malformed = throw $ ErrorCall $ "Malformed Address: " ++ ipstr
-- |Implementation of inet_ntoa outside the IO monad ntoa :: HostAddress -> String ntoa = concat . (intersperse ".") . (map show) . word8Split
------------------------------------------------------------------------
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Whew! I finally got a patch done: http://hackage.haskell.org/trac/ghc/ticket/1005 At this stage, I've just added the logical shift operators since I'll need them to do the aton/ntoa stuff in haskell code. The first patch is obsolete since it puts the quickcheck properties in a non-standard location. The second two patches fix that. Ignore the stuff about quickcheck properties in the trac details. On Tue, 2006-11-14 at 10:52 +0000, Simon Marlow wrote:
Robert: would you like to resubmit this suggestion using the new submission guidelines for library additions?
http://www.haskell.org/haskellwiki/Library_submissions
Cheers, Simon
--
Robert Marlow
participants (5)
-
Bulat Ziganshin
-
Ian Lynagh
-
Robert Marlow
-
Robert Marlow
-
Simon Marlow