[Haskell-beginners] Word8, Word32, ByteString, Int, etc. conversions.

Daniel Fischer daniel.is.fischer at web.de
Tue Oct 12 14:18:53 EDT 2010


On Tuesday 12 October 2010 18:38:31, David McBride wrote:
> I'm writing a pcap sniffer, and I have IP addresses from two different
> libraries that are equivalent, but typed differently.
>
> Data.IP.IPv4 Data.ByteString.Internal.ByteString
>
> and
>
> Network.Info.IPv4 = Network.Info.IPv4 !GHC.Word.Word32
>
> Both are probably identical, but I cannot for the life of me figure out
> how to get from one to the other.  Bytestring has the ability to take
> arrays of Word8, how do I split Word32 into Word8's?

If you have the binary package and know the endianness of the IP addresses, 
the simplest way to convert between those is

conv1 :: Network.Info.IPv4 -> Data.IP.IPv4
conv1 (Network.Info.IPv4 w32) =
    Data.IP.IPv4 (runPut $ putWord32be w32)

-- or putWord32le

conv2 :: Data.IP.IPv4 -> Network.Info.IPv4
conv2 (Data.IP.IPv4 bs) = Network.Ifo.IPv4 (runGet $ getWord32be)

-- or getWord32le

Alternatively, you can convert a Word32 to [Word8] per

import Data.Word
import Data.Bits

octets :: Word32 -> [Word8]
octets w = 
    [ fromIntegral (w `shiftR` 24)
    , fromIntegral (w `shiftR` 16)
    , fromIntegral (w `shiftR` 8)
    , fromIntegral w
    ]

for big-endian conversion (for little-endian, reverse the list ;)
And a list of Word8 to a Word32 per

fromOctets :: [Word8] -> Word32
fromOctets = foldl' accum 0
  where
    accum a o = (a `shiftL` 8) .|. fromIntegral o

(reverse or use foldr for little-endian conversion).

>
> I have also had this problem in the past with Word8's, Octets and Chars.
> Beyond this specific problem, what is a good strategy for figuring out
> how to do these conversions in the future?  Sometimes I find a function
> somewhere, but I have never found a general way to deal with it.



More information about the Beginners mailing list