[Haskell-cafe] Endian conversion

Joel Reymont joelr1 at gmail.com
Fri Oct 7 06:50:24 EDT 2005


Folks,

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.

     Thanks, Joel

{-# OPTIONS_GHC -fglasgow-exts -fth #-}

module Endian
(
Endian,
ByteOrder,
getHostByteOrder
)
where

import Foreign
import CTypes
import Language.Haskell.TH.Syntax

data ByteOrder = BigEndian | LittleEndian deriving (Show, Eq, Ord)
data Endian a = Endian a ByteOrder deriving (Show, Eq, Ord)

castAway :: Ptr (Endian a b) -> Ptr a
castAway = castPtr

isBigEndian = $(lift $ (1::CChar) /= (unsafePerformIO
                                      $ with (1::CInt)
                                      $ peekByteOff `flip` 0) ) :: Bool

getByteOrder :: Endian a -> ByteOrder
getByteOrder (Endian a e) = e

getHostByteOrder :: ByteOrder
getHostByteOrder
     | isBigEndian = BigEndian
     | otherwise = LittleEndian

instance (Storable a) => Storable (Endian a b) where
     sizeOf (Endian a _) = sizeOf a
     alignment (Endian a _) = alignment a
     peek a =
         if getHostByteOrder == b
            then peek0
            else peekR
         where
             peek0 a = peekByteOff `flip` 0
             peekR a = peekByteOff a 0
     peekByteOff (Endian a b) i = if getHostByteOrder == b
                   then peekByteOff0
                   else peekByteOffR
         where
             peekByteOff0 (Endian a) = peekByteOff a
             peekByteOffR (Endian a) i = peekByteOff a (sizeOf a - 1  
- i)




More information about the Haskell-Cafe mailing list