[Haskell-cafe] Endian conversion

Benjamin Franksen benjamin.franksen at bessy.de
Fri Oct 7 08:50:12 EDT 2005


On Friday 07 October 2005 12:50, Joel Reymont wrote:
> I tried to generalize the endian-related code and came up with
> something like the following which does not compile. What am I doing
> wrong? I would like Endian to be a wrapper around Storable with the
> endian flag. I want to be able to read/write little-endian on a big-
> endian platform and vise versa.

The way you started out, this will work only for the poke family of 
functions, but not for peek.

First a version that should work (at least it compiles) for poke:

\begin{code}
instance (Storable a) => Storable (Endian a) where
    sizeOf (Endian a _) = sizeOf a
    alignment (Endian a _) = alignment a
    pokeByteOff p i (Endian a b) =
        if getHostByteOrder == b
            then pokeByteOff p i a
            else pokeByteOff p (sizeOf a - 1  - i) a
\end{code}

Now, in contrast to poke, peek does /not/ get a value as argument, but 
only a pointer to the value. But the pointer has no information about 
endianness -- because you encoded the endianness into the value. 
Haskell overloading (class) system can infer such information only if 
it is encoded in the types. It can differentiate between different 
instances of Storable, because they all work on different types, 
whereas in your approach big-endian and little-endian values have 
the /same/ type, that is (Endian a).

One way to solve the problem is to encode endianness into the type of 
the value:

\begin{code}
-- note: newtype has no runtime overhead
newtype BigEndian a = BigEndian a
newtype LittleEndian a = LittleEndian a

isLittleEndian = not isBigEndian

instance (Storable a) => Storable (BigEndian a) where
    sizeOf (BigEndian a) = sizeOf a
    alignment (BigEndian a) = alignment a
    -- note: for the other peek and poke functions
    -- the default implementation can be used
    pokeByteOff p i (BigEndian a) = 
        if isBigEndian
            then pokeByteOff p i a
            else pokeByteOff p (sizeOf a - 1  - i) a
    peekByteOff p i =
        if isBigEndian
            then peekByteOff p i
            else peekByteOff p (sizeOf (undefined::a) - 1  - i)

instance (Storable a) => Storable (LittleEndian a) where
    sizeOf (LittleEndian a) = sizeOf a
    alignment (LittleEndian a) = alignment a
    -- note: for the other peek and poke functions
    -- the default implementation can be used
    pokeByteOff p i (LittleEndian a) = 
        if isLittleEndian
            then pokeByteOff p i a
            else pokeByteOff p (sizeOf a - 1  - i) a
    peekByteOff p i =
        if isLittleEndian
            then peekByteOff p i
            else peekByteOff p (sizeOf (undefined::a) - 1  - i)
\end{code}

You would probably want to wrap/unwrap values (using 
BigEndian/LittleEndian) just before/after calling poke/peek, like this:

\begin{code}
main = do
    ptr_x <- new (BigEndian(1::Int))
    (BigEndian x) <- peek ptr_x
    poke ptr_x (BigEndian 2)
    -- poke ptr_x (LittleEndian 3)
\end{code}

Note, with such an encoding, you cannot accidentally mix little and 
big-endian access. If the last line above is uncommented, the compiler 
complains.

HTH,
Ben


More information about the Haskell-Cafe mailing list