
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. Thanks, Joel -- http://wagerlabs.com/idealab

On 10/3/05, Joel Reymont
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

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Oct 3, 2005, at 6:51 AM, Marc Ziegert wrote:
data (Integral a) => BigEndian a = BigEndian a deriving (Eq,Ord,Enum,...) be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) :: Bool
Will this always correctly determine if the platform is big-endian? How does it actually work?
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...
So I would need to implement the various functions from storable, right? Also, what's the easiest way to implement LittleEndian on top of this? Just change peekByteOf, etc.? Thanks, Joel -- http://wagerlabs.com/idealab

On Mon, 3 Oct 2005, Joel Reymont wrote:
On Oct 3, 2005, at 6:51 AM, Marc Ziegert wrote:
data (Integral a) => BigEndian a = BigEndian a deriving (Eq,Ord,Enum,...) be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) :: Bool
Will this always correctly determine if the platform is big-endian? How does it actually work?
I don't know, having not used things like peekByteOff, but my suspicion would be that it's rather like, typedef char byte; char cChar = 1; int cInt = 1; int be = cChar != *(((byte*) &cInt) + 0); printf("be = %i\n", be); return 0; in C, so it's looking to see if the first byte of the int representation of 1 isn't 1. -- Mark

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)

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

On Friday 07 October 2005 14:50, Benjamin Franksen wrote:
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}
Note that even this breaks down for more complex types (i.e. records). For instance, with the obvious Storable instance of (Int16,Int16), the elements will get swapped, too. I can't see how to solve this in a generic way. Ben

What I have in mind is composing a packet structure from a list of storables. These would be the packet fields. Alternatively, I guess I could declare my record to be an instance of storable and implement the peek, poker, etc. Would this work? On Oct 7, 2005, at 4:39 PM, Benjamin Franksen wrote:
On Friday 07 October 2005 14:50, Benjamin Franksen wrote:
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}
Note that even this breaks down for more complex types (i.e. records). For instance, with the obvious Storable instance of (Int16,Int16), the elements will get swapped, too. I can't see how to solve this in a generic way.

This code hangs for me for whatever reason when I run it at the ghci prompt. It does not matter whether I load it from a file or type it in. On Oct 7, 2005, at 2:50 PM, Benjamin Franksen wrote:
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}

It seems that (BigEndian x) <- peek ptr_x is the culprit. On Oct 7, 2005, at 4:48 PM, Joel Reymont wrote:
This code hangs for me for whatever reason when I run it at the ghci prompt. It does not matter whether I load it from a file or type it in.
On Oct 7, 2005, at 2:50 PM, Benjamin Franksen wrote:
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}

On Friday 07 October 2005 16:51, Joel Reymont wrote:
It seems that (BigEndian x) <- peek ptr_x is the culprit.
On Oct 7, 2005, at 4:48 PM, Joel Reymont wrote:
This code hangs for me for whatever reason when I run it at the ghci prompt. It does not matter whether I load it from a file or type it in.
This is because I got the peek vs. peekByteOff semantics completely wrong. Sorry for that. (peekByteOff i) does exactly the same as peek, only with a pointer that is advanced (i) bytes forward. That means, the code I sent reads and writes to random memory locations; no wonder the program hangs (I am astonished it doesn't crash). In order to define byte swapping instances of Storable, you have to swap the bytes /in memory/ and afterwards interprete them as whatever value they were originally. This is like C programming in Haskell, which is possible, but no less ugly than the C version. Cheers, Ben

Well, I'm looking for suggestions on how to implement this. I'll basically get a chunk of data from the socket that will have things little-endian and will need to send out a chunk that will have the numbers big-endian. This is a proxy server that does binary protocol conversion. It's a breeze to implement in Erlang but I'm partial to Haskell and trying to apply it to all sorts of problems. Please, let me know if this is not the type of problem to apply Haskell to ;-). Thanks, Joel On Oct 3, 2005, at 8:35 AM, Tomasz Zielonka wrote:
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.

for just making IO and a little bit-conversion, i would use c++ or even c. for such a problem you have to be near the machine, not necessarily near mathematical abstraction. there exist assembler-commands to flip endians of register-values, so i would just search in /usr/include/*/* for a platform independent c-function, and either pipe a proxy through such a little prog, or patch an existing proxy, like "tinyproxy". of course, if you want to make more than just a proxy, or if you want to play with different languages, be welcome to use haskell. but remind, it is not easy to use high-developed-mars-rover-technology to replace a shovel for playing with sand at the beach. - marc Joel Reymont wrote:
Well, I'm looking for suggestions on how to implement this. I'll basically get a chunk of data from the socket that will have things little-endian and will need to send out a chunk that will have the numbers big-endian.
This is a proxy server that does binary protocol conversion. It's a breeze to implement in Erlang but I'm partial to Haskell and trying to apply it to all sorts of problems. Please, let me know if this is not the type of problem to apply Haskell to ;-).
Thanks, Joel
On Oct 3, 2005, at 8:35 AM, Tomasz Zielonka wrote:
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.
-- http://wagerlabs.com/idealab
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Well, I can make the problem a little more complex to give you a better picture of where Haskell fits in... I need to write a simulation environment to be able to run bots against a poker server and reproduce this intermittent memory corruption that happens within it. The poker server is written in C++ on Windows. There's no documentation and all I have is the source code to the communications layer of the server and an older test tool. I'm currently in discovery mode as I need to figure out the protocol, the format of each packet, etc. Haskell should let me write down the bits of info as I discover them, as a specification of sorts. I would describe each packet as I learn its format, etc. Work from the top down. Erlang would be perfect for all the binary parsing but... I intuitively fell that Haskell will let me "document" the hairy C++ poker server and its non-intuitive ways. I'm still now sure if I could write a high-performance server in Haskell, that's the task for another project that I have (the binary protocol converter/proxy) but in this particular case all I'll be doing is launching bots in separate threads and have them follow some scenarious or maybe just decide what to do using their internal logic. Thus I'm not too concerned with performance. I'm putting an onus here on clarity and endowing my bots with some complex brains to be able to explore the hidden crannies of the target poker server to make it crash. It seems to me that Haskell is best for bot logic and documentation so it's more like using mars- rover-technology to explore Mars and getting stuck on a wee bit of sand shoveling. Joel On Oct 3, 2005, at 11:54 AM, Marc Ziegert wrote:
for just making IO and a little bit-conversion, i would use c++ or even c. for such a problem you have to be near the machine, not necessarily near mathematical abstraction. there exist assembler-commands to flip endians of register-values, so i would just search in /usr/include/*/* for a platform independent c-function, and either pipe a proxy through such a little prog, or patch an existing proxy, like "tinyproxy". of course, if you want to make more than just a proxy, or if you want to play with different languages, be welcome to use haskell. but remind, it is not easy to use high-developed-mars-rover- technology to replace a shovel for playing with sand at the beach.

Joel Reymont wrote:
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.
Why don't you pull out 4 bytes and assemble them manually? Three shifts, logical ors and fromIntegrals aren't that much of a burden after all. Udo. -- The Second Law of Thermodynamics: If you think things are in a mess now, just wait! -- Jim Warner

Well, I liked that bit of Template Haskell code that Marc sent. I'm now stuck trying to adapt it to read Storables :-). It seems, on a second glance, that there's not that much to adapt. If I read Marc's code correctly it "derives" Storable and uses the peek, etc. methods to swap bytes around. Which means to me that so long as the byte swapping methods are implemented and I try to store a BigEndian or LittleEndian it would be stored correctly for me. Is this so? To recap, I'm trying to read binary packets from a socket and the first thing I do is read the packet length. I then need to read the packet body where the numbers are little or big endian. After processing the packet I need to write it out and the numbers again could be little or big endian. I could read a FastString from a socket since it has IO methods but I don't know how to convert the FS into a pointer suitable for Storable. So much to learn :-). Thanks, Joel On Oct 3, 2005, at 9:33 PM, Udo Stenzel wrote:
Why don't you pull out 4 bytes and assemble them manually? Three shifts, logical ors and fromIntegrals aren't that much of a burden after all.

Why don't you pull out 4 bytes and assemble them manually?
To that I'd like to add a snippet from NewBinary itself: | instance Binary Word32 where | put_ h w = do | putByte h (fromIntegral (w `shiftR` 24)) | putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff)) | putByte h (fromIntegral ((w `shiftR` 8) .&. 0xff)) | putByte h (fromIntegral (w .&. 0xff)) | get h = do | w1 <- getWord8 h | w2 <- getWord8 h | w3 <- getWord8 h | w4 <- getWord8 h | return $! ((fromIntegral w1 `shiftL` 24) .|. | (fromIntegral w2 `shiftL` 16) .|. | (fromIntegral w3 `shiftL` 8) .|. | (fromIntegral w4)) This obviously writes a Word32 in big endian format, also known as "network byte order", and doesn't care how the host platform stores integers. No need for `hton' and `ntoh'. To convert it to write little endian, just copy it and reorder some lines. (But I think, writing LE integers with no good reason and without an enclosing protocol that explicitly declares them (like IIOP) is a bad idea.) [Which reminds me, has anyone ever tried implementing a Corba ORB in Haskell? There's a binding to MICO, but that just adds to the uglyness of MICO and does Haskell a bit of injustice...]
Well, I liked that bit of Template Haskell code that Marc sent. I'm now stuck trying to adapt it to read Storables :-).
I don't. It's complex machinery, it's ugly, it solves a problem that doesn't even exist and it solves it incompletely. It will determine the byte order of the host system, not of the target, which fails when cross-compiling, and it doesn't work on machines with little endian words and big endian long words (yes, this has been seen in the wild, though might be extinct these days). Use it only if You Know What You Are Doing, have a performance problem and also know that writing integers en bloc would help with it.
I could read a FastString from a socket since it has IO methods but I don't know how to convert the FS into a pointer suitable for Storable. So much to learn :-).
useAsCString might be your friend. But so might be (fold (:) []). Udo. -- "The greatest dangers to liberty lurk in insidious encroachment by men of zeal, well-meaning but without understanding." -- Brandeis

you are right, that pice of code is ugly. i would write sth simmilar (Int32->[Word8]) like you did, iff it should be able to cross-compile or do not need to be fast or should not need TH. well, i think, in the case of joel's project the last sentence means "..., iff true or true or undefined". is there any architecture with sth like 0xaabbccdd->bb aa dd cc, ghc (or any other haskell-compiler) runs on? (i did know, that such architectures exist.) - marc Udo Stenzel wrote:
Why don't you pull out 4 bytes and assemble them manually?
To that I'd like to add a snippet from NewBinary itself:
| instance Binary Word32 where | put_ h w = do | putByte h (fromIntegral (w `shiftR` 24)) | putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff)) | putByte h (fromIntegral ((w `shiftR` 8) .&. 0xff)) | putByte h (fromIntegral (w .&. 0xff)) | get h = do | w1 <- getWord8 h | w2 <- getWord8 h | w3 <- getWord8 h | w4 <- getWord8 h | return $! ((fromIntegral w1 `shiftL` 24) .|. | (fromIntegral w2 `shiftL` 16) .|. | (fromIntegral w3 `shiftL` 8) .|. | (fromIntegral w4))
This obviously writes a Word32 in big endian format, also known as "network byte order", and doesn't care how the host platform stores integers. No need for `hton' and `ntoh'. To convert it to write little endian, just copy it and reorder some lines. (But I think, writing LE integers with no good reason and without an enclosing protocol that explicitly declares them (like IIOP) is a bad idea.)
[Which reminds me, has anyone ever tried implementing a Corba ORB in Haskell? There's a binding to MICO, but that just adds to the uglyness of MICO and does Haskell a bit of injustice...]
Well, I liked that bit of Template Haskell code that Marc sent. I'm now stuck trying to adapt it to read Storables :-).
I don't. It's complex machinery, it's ugly, it solves a problem that doesn't even exist and it solves it incompletely. It will determine the byte order of the host system, not of the target, which fails when cross-compiling, and it doesn't work on machines with little endian words and big endian long words (yes, this has been seen in the wild, though might be extinct these days). Use it only if You Know What You Are Doing, have a performance problem and also know that writing integers en bloc would help with it.
I could read a FastString from a socket since it has IO methods but I don't know how to convert the FS into a pointer suitable for Storable. So much to learn :-).
useAsCString might be your friend. But so might be (fold (:) []).
Udo. -- "The greatest dangers to liberty lurk in insidious encroachment by men of zeal, well-meaning but without understanding." -- Brandeis
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Regarding NewBinary... I think my challenge is how to add endian- conversion without duplicating all the put and get methods from NewBinary. I would still use that bit of TH code to figure out whether my platform is big or little endian. I don't care about cross- compilation and what that code does is analogous to #ifdef ... #define LITTLE_ENDIAN ... #endif, etc. I'm looking for architectural suggestions, though. Should I define LittleEndian Word32, BigEndian Word16, etc. or should I have Endian Word32 Big, Endian Word16 Little, etc. Thanks, Joel On Oct 5, 2005, at 11:42 AM, Udo Stenzel wrote:
Why don't you pull out 4 bytes and assemble them manually?
To that I'd like to add a snippet from NewBinary itself:
| instance Binary Word32 where | put_ h w = do | putByte h (fromIntegral (w `shiftR` 24)) | putByte h (fromIntegral ((w `shiftR` 16) .&. 0xff)) | putByte h (fromIntegral ((w `shiftR` 8) .&. 0xff)) | putByte h (fromIntegral (w .&. 0xff)) | get h = do | w1 <- getWord8 h | w2 <- getWord8 h | w3 <- getWord8 h | w4 <- getWord8 h | return $! ((fromIntegral w1 `shiftL` 24) .|. | (fromIntegral w2 `shiftL` 16) .|. | (fromIntegral w3 `shiftL` 8) .|. | (fromIntegral w4))
This obviously writes a Word32 in big endian format, also known as "network byte order", and doesn't care how the host platform stores integers. No need for `hton' and `ntoh'. To convert it to write little endian, just copy it and reorder some lines. (But I think, writing LE integers with no good reason and without an enclosing protocol that explicitly declares them (like IIOP) is a bad idea.)

I don't want to replicate all the code in NewBinary for Little/Big endian. I'm looking for an elegant solution (Haskell, the elegant language, you know). I don't care about cross-compiling stuff and the server that I need to work with runs on Wintel whereas I can be either on Windows or Mac or Linux. Last but not least, I also need to read floats. These would be IEEE 754 (standard) but I still need to swap the bytes around. I still don't know how to do this without rewriting all the get/put functions in NewBinary. Marc Ziegert's code is very hepful but still incomplete. I think Marc's TH bit be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) :: Bool is the way to determine if you are BE or LE but how do I use it to read a Float and a 32-bit Int for example? If anyone would be kind enough to give me a complete example I would appreciate it. Thanks, Joel On Oct 5, 2005, at 11:42 AM, Udo Stenzel wrote:
This obviously writes a Word32 in big endian format, also known as "network byte order", and doesn't care how the host platform stores integers. No need for `hton' and `ntoh'. To convert it to write little endian, just copy it and reorder some lines. (But I think, writing LE integers with no good reason and without an enclosing protocol that explicitly declares them (like IIOP) is a bad idea.)

On Thu, 6 Oct 2005, Joel Reymont wrote:
I don't want to replicate all the code in NewBinary for Little/Big endian. I'm looking for an elegant solution (Haskell, the elegant language, you know).
Maybe that's why I haven't seen anyone propose a foreign interface,
but it's sure how I would do it. This standard network library stuff
is all sorted out for C programmers, it's just a matter of getting to it.
Code for htonl follows, htons should obvious. For floats, I suppose
you'd deliver them across the interface as whatever the floating point
equivalent of CInt, then make sure they're 32 bit floats on the C
side before swapping them with htonl.
Donn Cave, donn@drizzle.com
--- Netword.hsc ---
-# OPTIONS -fffi #-}
module Netword (htonl,ntohl) where
import Foreign
import Foreign.C
#include "netw.h"
foreign import ccall unsafe "c_htonl" htonl :: CInt -> CInt
foreign import ccall unsafe "c_ntohl" ntohl :: CInt -> CInt
--- netw.c ---
#include

Why doesn't this compile? be = $( (1::CChar) /= (unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) :: Bool Endian.hs:10:8: Couldn't match `Language.Haskell.TH.Lib.ExpQ' against `Bool' Expected type: Language.Haskell.TH.Lib.ExpQ Inferred type: Bool In the expression: (1 :: CChar) /= (unsafePerformIO $ ((with (1 :: CInt)) $ (peekByteOff `flip` 0))) In the expression: $[splice]((1 :: CChar) /= (unsafePerformIO $ ((with (1 :: CInt)) $ (peekByteOff `flip` 0)))) :: Bool Thanks, Joel

Solution by TheHunter on #haskell: be = $(lift $ (1::CChar) /= (unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) :: Bool Thanks, Joel On Oct 6, 2005, at 9:13 PM, Joel Reymont wrote:
Why doesn't this compile?
be = $( (1::CChar) /= (unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) :: Bool
Endian.hs:10:8: Couldn't match `Language.Haskell.TH.Lib.ExpQ' against `Bool' Expected type: Language.Haskell.TH.Lib.ExpQ Inferred type: Bool In the expression: (1 :: CChar) /= (unsafePerformIO $ ((with (1 :: CInt)) $ (peekByteOff `flip` 0))) In the expression: $[splice]((1 :: CChar) /= (unsafePerformIO $ ((with (1 :: CInt)) $ (peekByteOff `flip` 0)))) :: Bool

On 10/3/05, Udo Stenzel
Joel Reymont wrote:
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.
Why don't you pull out 4 bytes and assemble them manually? Three shifts, logical ors and fromIntegrals aren't that much of a burden after all.
Exactly! Network encodings for integers are precisely, mathematically defined. Surprisingly, it is very difficult to see (it was a revelation for me too). Perhaps the reason is that people get used to the mess in C networking code. Best regards Tomasz

On Mon, Oct 03, 2005 at 09:33:11PM +0200, Udo Stenzel wrote:
Joel Reymont wrote:
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.
Why don't you pull out 4 bytes and assemble them manually? Three shifts, logical ors and fromIntegrals aren't that much of a burden after all.
Yeah, this is exactly the right approach, just pull out the bytes with a shift and bitwise and, and then send them in one order or the other. there is no need to know the endianess of the architecture the program is running on. John -- John Meacham - ⑆repetae.net⑆john⑈
participants (8)
-
Benjamin Franksen
-
Donn Cave
-
Joel Reymont
-
John Meacham
-
Marc Ziegert
-
Mark Carroll
-
Tomasz Zielonka
-
Udo Stenzel