[Haskell-cafe] Endian conversion

Marc Ziegert coeus at gmx.de
Mon Oct 3 00:51:17 EDT 2005


well, fastest conversion to compute could be an assembler-command, but if we don't use that, it could be converted via Foreign.Storable and sth like the following: (i did not test it, and i hope, TH works like this...)

data (Integral a) => BigEndian a = BigEndian a deriving (Eq,Ord,Enum,...)
be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) :: Bool
instance (Storable a) => Storable (BigEndian a) where
 sizeOf (BigEndian a) = sizeOf a
 alignment (BigEndian a) = alignment a
 peek = if be then peek0 else peekR
  where
   peek0 (BigEndian a) = peek a
   peekR = peekByteOff `flip` 0
 peekByteOff = if be then peekByteOff0 else peekByteOffR
  where
   peekByteOff0 (BigEndian a) = peekByteOff a
   peekByteOffR (BigEndian a) i = peekByteOff a (sizeOf a - 1 - i)
...poke...

- marc


Tomasz Zielonka wrote:
> On 10/3/05, Joel Reymont <joelr1 at gmail.com> wrote:
> >
> > Folks,
> >
> > Are there any endian conversion routines for Haskell? I'm looking to
> > build binary packets on top of NewBinary.Binary but my data is coming
> > in little-endian whereas I'll need to send it out big endian.
> 
> 
> >From your question I assume you want functions like htonl / ntohl.
> I think the cleanest approach is to always have yours Ints, etc in host
> order, and place
> the endianness stuff in serialization / deserialization code, ie. on the
> Number <-> Byte
> sequence boundary.
> 
> Having htonl/ntohl as pure functions in Haskell would be a bit ugly, because
> they would be defined differently on different platforms, and putting them
> in the
> IO monad would make them barely usable.
> 
> Best regards
> Tomasz
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 



More information about the Haskell-Cafe mailing list