Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-29 Thread Ketil Malde
Duncan Coutts duncan.cou...@worc.ox.ac.uk writes:

 FWIW, I've used Data.Binary extensively and have found it a joy to
 work with. I've used it to serialize/deserialize ethernet packets in
 real time for a VPN implementation and have never had a problem. It's
 quite fast and robust.

 Is that code available? We could do with something serious for
 benchmarking the binary package, especially if we go for any major
 re-engineering.

I'm using Data.Binary in the bioinformatics library to encode/decode
SFF files.  These contain gene sequences produced with the new
pyrosequencing technology from Roche/454, have sizes (with the latest
incarnation of the sequencing) of about 1-2GB.  Plenty of test data at

 http://www.ncbi.nlm.nih.gov/sites/entrez?db=sra

A program using the library is described here:

 http://blog.malde.org/index.php/flower/

All available with (L)GPL licenses.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-28 Thread Khudyakov Alexey
On Thursday 28 of May 2009 07:52:56 David Leimbach wrote:
 Sorry took so long to get back... Thank you for the response.  Been really
 busy lately :-)

 There are also a lot of 9P implementations in many languages that you can
 interoperate with:

 http://9p.cat-v.org/implementations

Thank you for that link. I didn't find it earlier. But actually I asked what 
are you trying to write? 

--
  Khudyakov Alexey 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-28 Thread David Leimbach
On Thu, May 28, 2009 at 5:42 AM, Khudyakov Alexey alexey.sklad...@gmail.com
 wrote:

 On Thursday 28 of May 2009 07:52:56 David Leimbach wrote:
  Sorry took so long to get back... Thank you for the response.  Been
 really
  busy lately :-)
 
  There are also a lot of 9P implementations in many languages that you can
  interoperate with:
 
  http://9p.cat-v.org/implementations
 
 Thank you for that link. I didn't find it earlier. But actually I asked
 what
 are you trying to write?


I'm trying to implement the protocol, so that I can implement other things
on top of that.

I'm also trying to figure out how bad/good Haskell Binary IO really is that
it's been addressed a few times differently :-)



 --
   Khudyakov Alexey
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-28 Thread Don Stewart
leimy2k:
 I'm also trying to figure out how bad/good Haskell Binary IO really is that
 it's been addressed a few times differently :-)

FWIW Binary IO as implemented in Data.Binary is widely used in our
production systems at Galois. I'd be fairly confident in it.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-28 Thread John Van Enk


 I'm trying to implement the protocol, so that I can implement other things
 on top of that.

 I'm also trying to figure out how bad/good Haskell Binary IO really is that
 it's been addressed a few times differently :-)



FWIW, I've used Data.Binary extensively and have found it a joy to work
with. I've used it to serialize/deserialize ethernet packets in real time
for a VPN implementation and have never had a problem. It's quite fast and
robust.

/jve
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-28 Thread Duncan Coutts
On Thu, 2009-05-28 at 12:08 -0400, John Van Enk wrote:
  
 I'm trying to implement the protocol, so that I can implement
 other things on top of that.  
  
 I'm also trying to figure out how bad/good Haskell Binary IO
 really is that it's been addressed a few times differently :-)
  
  
 FWIW, I've used Data.Binary extensively and have found it a joy to
 work with. I've used it to serialize/deserialize ethernet packets in
 real time for a VPN implementation and have never had a problem. It's
 quite fast and robust.

Is that code available? We could do with something serious for
benchmarking the binary package, especially if we go for any major
re-engineering.

If it's not available publicly perhaps you might share it privately. Don
and I have discussed a few times writing a paper on the design and
implementation of a binary library.

Duncan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-28 Thread Johan Tibell
On Thu, May 28, 2009 at 6:34 PM, Duncan Coutts
duncan.cou...@worc.ox.ac.ukwrote:

 If it's not available publicly perhaps you might share it privately. Don
 and I have discussed a few times writing a paper on the design and
 implementation of a binary library.


I would definitely like to read such a paper. Except for Don's blog entries
there's precious little written on the design of high performance Haskell
libraries.

-- Johan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-27 Thread David Leimbach
Sorry took so long to get back... Thank you for the response.  Been really
busy lately :-)

On Sat, May 16, 2009 at 3:46 AM, Khudyakov Alexey alexey.sklad...@gmail.com
 wrote:

 On Friday 15 May 2009 06:52:29 David Leimbach wrote:
  I actually need little endian encoding... wondering if anyone else hit
 this
  with Data.Binary. (because I'm working with Bell Lab's 9P protocol which
  does encode things on the network in little-endian order).
  Anyone got some tricks for this?
 
  Dave

 You could just define data type and Binary instance for 9P messages.
 Something
 like this:

 P9Message = Tversion { tag :: Word16, msize :: Word32, version :: String }
| ...

 instance Binary P9Message where
  put (Tverstion  t m v) =  putWord16le t   putWord32le m  put v
  -- and so on...

  get = do
length - getWord32le
id - getWord16le
case is of
  p9TMessage - do ...

 There are a lot of boilerplate code thought...


Thank you, this still looks like a useful way to proceed, combined with the
BinaryLE approach perhaps, to avoid a lot of boilerplate.




 BTW could you say what do you want to do with 9P? I tried to play with it
 using libixp library but without any success. It was mainly to understand
 how
 does it works and how can it be used.


From a services point of view, 9P gives you a way to host them, and even
devices, on a network share that can be mounted into the filesystem's
namespace.  The net result is you've plugged into the standard unix
utilities that do open, read, write etc, and can do a lot of interesting
things with mere shell scripts.

Operating systems that can be clients of a 9P service include Linux,
Inferno, Plan 9, and anything else that runs FUSE 9P (several BSDs).

From a client perspective, having a 9P implementation gives you a more
fine-grained programatic interface to accessing other 9P services.

There are also a lot of 9P implementations in many languages that you can
interoperate with:

http://9p.cat-v.org/implementations






 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-18 Thread Sven Panne
Am Sonntag, 17. Mai 2009 15:08:29 schrieb Don Stewart:
 Sven.Panne:
  [...]
  I think most problems can be fixed in a rather pragmatic way by adding a
  few functions to the binary package:
 [...]
 Patches are welcome.

Attached. A few remarks:

 * This is only a quick and mildly tested implementation of the IEEE 
functions, especially NaNs, infinities and denormalized numbers are untested. 
These problems could totally be avoided if we can coerce representations 
directly, changing only their interpretation.

 * The *host functions assume an IEEE platform, but this can easily be changed 
(see comments).

 * Perhaps one can use unsafeCoerce for word32ToFloat and friends, but I 
haven't checked this.

 * I've seen a few {- INLINE -} comments. Is this really wanted or only a 
typo?

 * A comment about using peek/poke for the *le/*be functions is wrong, because 
this would introduce alignment constraints on some platforms.

I think the main point is to provide a nice and efficient API, hiding all the 
dirty stuff in the implementation.

  One final remarks: I think the low level functions of the binary package
  should really keep the notions of endianess and alignment constraints
  separate, something which isn't done currently: The *host functions have
  alignment restrictions, the *be/*le functions don't. There is no good
  reason for this non-orthogonality.

 That seems reasonable.

There are various ways to achieve this, but the most obvious way leads to a 
combinatorial explosion of functions:

   no. of types * 3 (LE/BE/host) * 2 (aligned/unaligned)

Furthermore, it would be good to split the binary package into the 2 layers 
already discussed first, then it is perhaps a bit clearer what a nice API 
would look like. I think it would be best to shift this API design discussion 
to the libraries list.

Cheers,
   S.

Only in binary-0.5.0.1: dist
diff -r -u binary-0.5.0.1.orig/src/Data/Binary/Builder.hs binary-0.5.0.1/src/Data/Binary/Builder.hs
--- binary-0.5.0.1.orig/src/Data/Binary/Builder.hs	Sat Mar  7 23:59:44 2009
+++ binary-0.5.0.1/src/Data/Binary/Builder.hs	Mon May 18 17:36:22 2009
@@ -41,20 +41,27 @@
 , putWord16be   -- :: Word16 - Builder
 , putWord32be   -- :: Word32 - Builder
 , putWord64be   -- :: Word64 - Builder
+, putFloatIEEEbe-- :: Float - Builder
+, putDoubleIEEEbe   -- :: Double - Builder
 
 -- ** Little-endian writes
 , putWord16le   -- :: Word16 - Builder
 , putWord32le   -- :: Word32 - Builder
 , putWord64le   -- :: Word64 - Builder
+, putFloatIEEEle-- :: Float - Builder
+, putDoubleIEEEle   -- :: Double - Builder
 
 -- ** Host-endian, unaligned writes
 , putWordhost   -- :: Word - Builder
 , putWord16host -- :: Word16 - Builder
 , putWord32host -- :: Word32 - Builder
 , putWord64host -- :: Word64 - Builder
+, putFloatIEEEhost  -- :: Float - Builder
+, putDoubleIEEEhost -- :: Double - Builder
 
   ) where
 
+import Prelude hiding (significand, exponent)
 import Foreign
 import Data.Monoid
 import Data.Word
@@ -360,6 +367,60 @@
 -- on a little endian machine:
 -- putWord64le w64 = writeN 8 (\p - poke (castPtr p) w64)
 
+-- | Write a Float in IEEE big endian format
+putFloatIEEEbe :: Float - Builder
+putFloatIEEEbe = putWord32be . floatToWord32
+{-# INLINE putFloatIEEEbe #-}
+
+-- | Write a Double in IEEE big endian format
+putDoubleIEEEbe :: Double - Builder
+putDoubleIEEEbe = putWord64be . doubleToWord64
+{-# INLINE putDoubleIEEEbe #-}
+
+-- | Write a Float in IEEE little endian format
+putFloatIEEEle :: Float - Builder
+putFloatIEEEle = putWord32le . floatToWord32
+{-# INLINE putFloatIEEEle #-}
+
+-- | Write a Double in IEEE little endian format
+putDoubleIEEEle :: Double - Builder
+putDoubleIEEEle = putWord64le . doubleToWord64
+{-# INLINE putDoubleIEEEle #-}
+
+floatToWord32 :: Float - Word32
+-- floatToWord32 = unsafeReinterpret
+floatToWord32 = encodeIEEE 8 23
+
+doubleToWord64 :: Double - Word64
+-- doubleToWord64 = unsafeReinterpret
+doubleToWord64 = encodeIEEE 11 52
+
+-- TODO: Check if this works for denormalized numbers, NaNs and infinities.
+encodeIEEE :: (RealFloat a, Bits b, Integral b) = Int - Int - a - b
+encodeIEEE exponentBits significandBits f =
+  (signBit `shiftL` (exponentBits + significandBits)) .|.
+  (exponentField `shiftL` significandBits) .|.
+  significandField
+   where (significand, exponent) = decodeFloat f
+
+ signBit | significand  0 = 1
+ | otherwise = 0
+ exponentField | significand == 0  exponent == 0 = 0
+   | otherwise = fromIntegral exponent + exponentBias + fromIntegral significandBits
+ significandField = fromIntegral (abs significand) .. significandMask
+
+ exponentBias = bit (exponentBits - 1) - 1
+ significandMask = bit significandBits - 1
+
+{-
+-- Evil! Poor man's version 

Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-17 Thread Sven Panne
Am Freitag, 15. Mai 2009 06:37:22 schrieb Don Stewart:
 timd:
  On a related matter, I am using Data.Binary to serialise data from
  haskell for use from other languages. [...]
 [...]
 Yep, it's possible, just not portably so. Google for Data.Binary IEEE
 discussions.

I think this topic pops up over and over again, and the proposed solutions 
are no solutions at all, neither from a performance point of view, nor from an 
ease of use point of view. Proposing insane bit fiddling by hand when all one 
technically needs is often a peek or poke amounts to simply ignoring an 
API problem. ;-)

I think most problems can be fixed in a rather pragmatic way by adding a few 
functions to the binary package:

Add to Data.Binary.Builder:

   putFloatIEEEbe :: Float - Builder
   putDoubleIEEEbe :: Double - Builder
   putFloatIEEEle :: Float - Builder
   putDoubleIEEEle :: Double - Builder
   putFloatIEEEhost :: Float - Builder
   putDoubleIEEEhost :: Double - Builder

Add to Data.Binary.Get:

   getFloatIEEEbe :: Get Float
   getDoubleIEEEbe :: Get Double
   getFloatIEEEle :: Get Float
   getDoubleIEEEle :: Get Double
   getFloatIEEEhost :: Get Float
   getDoubleIEEEhost :: Get Double

Add to Data.Binary.Put:

   putFloatIEEEbe ::  Float - Put
   putDoubleIEEEbe ::  Double - Put
   putFloatIEEEle ::  Float - Put
   putDoubleIEEEle ::  Double - Put
   putFloatIEEEhost ::  Float - Put
   putDoubleIEEEhost ::  Double - Put

The *host functions are basically peek/poke for most platforms. The *le/*be 
functions can use peek/poke if the endianess matches (compile time decision) 
*and* the alignment is OK for the given platform (runtime decision). Non-IEEE 
platforms always have to do the bit fiddling internally, but all this is 
hidden behind the above API.

IIRC I have proposed something similar 1-2 years ago, but I can't remember any 
reason why this hasn't been implemented. Any comments on the above functions?

One final remarks: I think the low level functions of the binary package 
should really keep the notions of endianess and alignment constraints 
separate, something which isn't done currently: The *host functions have 
alignment restrictions, the *be/*le functions don't. There is no good reason 
for this non-orthogonality.

Cheers,
   S.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-17 Thread Don Stewart
Sven.Panne:
 Am Freitag, 15. Mai 2009 06:37:22 schrieb Don Stewart:
  timd:
   On a related matter, I am using Data.Binary to serialise data from
   haskell for use from other languages. [...]
  [...]
  Yep, it's possible, just not portably so. Google for Data.Binary IEEE
  discussions.
 
 I think this topic pops up over and over again, and the proposed solutions 
 are no solutions at all, neither from a performance point of view, nor from 
 an 
 ease of use point of view. Proposing insane bit fiddling by hand when all one 
 technically needs is often a peek or poke amounts to simply ignoring an 
 API problem. ;-)
 
 I think most problems can be fixed in a rather pragmatic way by adding a few 
 functions to the binary package:
 
 Add to Data.Binary.Builder:
 
putFloatIEEEbe :: Float - Builder
putDoubleIEEEbe :: Double - Builder
putFloatIEEEle :: Float - Builder
putDoubleIEEEle :: Double - Builder
putFloatIEEEhost :: Float - Builder
putDoubleIEEEhost :: Double - Builder
 
 Add to Data.Binary.Get:
 
getFloatIEEEbe :: Get Float
getDoubleIEEEbe :: Get Double
getFloatIEEEle :: Get Float
getDoubleIEEEle :: Get Double
getFloatIEEEhost :: Get Float
getDoubleIEEEhost :: Get Double
 
 Add to Data.Binary.Put:
 
putFloatIEEEbe ::  Float - Put
putDoubleIEEEbe ::  Double - Put
putFloatIEEEle ::  Float - Put
putDoubleIEEEle ::  Double - Put
putFloatIEEEhost ::  Float - Put
putDoubleIEEEhost ::  Double - Put
 
 The *host functions are basically peek/poke for most platforms. The *le/*be 
 functions can use peek/poke if the endianess matches (compile time decision) 
 *and* the alignment is OK for the given platform (runtime decision). Non-IEEE 
 platforms always have to do the bit fiddling internally, but all this is 
 hidden behind the above API.
 
 IIRC I have proposed something similar 1-2 years ago, but I can't remember 
 any 
 reason why this hasn't been implemented. Any comments on the above functions?


Patches are welcome.
  
 One final remarks: I think the low level functions of the binary package 
 should really keep the notions of endianess and alignment constraints 
 separate, something which isn't done currently: The *host functions have 
 alignment restrictions, the *be/*le functions don't. There is no good reason 
 for this non-orthogonality.

That seems reasonable.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-16 Thread Khudyakov Alexey
On Friday 15 May 2009 06:52:29 David Leimbach wrote:
 I actually need little endian encoding... wondering if anyone else hit this
 with Data.Binary. (because I'm working with Bell Lab's 9P protocol which
 does encode things on the network in little-endian order).
 Anyone got some tricks for this?

 Dave

You could just define data type and Binary instance for 9P messages. Something 
like this:

P9Message = Tversion { tag :: Word16, msize :: Word32, version :: String } 
| ... 

instance Binary P9Message where
  put (Tverstion  t m v) =  putWord16le t   putWord32le m  put v
  -- and so on...

  get = do 
length - getWord32le
id - getWord16le
case is of
  p9TMessage - do ... 
  
There are a lot of boilerplate code thought...


BTW could you say what do you want to do with 9P? I tried to play with it  
using libixp library but without any success. It was mainly to understand how 
does it works and how can it be used. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-15 Thread Duncan Coutts
On Thu, 2009-05-14 at 20:46 -0700, David Leimbach wrote:
 
 
 On Thu, May 14, 2009 at 8:40 PM, Don Stewart d...@galois.com wrote:
 leimy2k:
 
  I actually need little endian encoding... wondering if
 anyone else hit this
  with Data.Binary. (because I'm working with Bell Lab's 9P
 protocol which does
  encode things on the network in little-endian order).
 
  Anyone got some tricks for this?
 
 
 Yes!
 There are big, little and host-endian primitives in the
 Get/Put monads.
 
 
  
 http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Put.html#v%3AputWord16le
 
 You can use these to build encoders directly.
 
 
 Cool... I just have to write my own encoder and decoder now.
 
 
 As a request could we get encodeLe decodeLe for a later version of
 this library?  :-)  That'd be totally awesome.

The thing you're missing (and which admittedly is not clear) is that the
binary package has two parts. One is a layer where you get full control
over the binary representation. The other is a portable serialisation
layer for pickling and unpickling Haskell values. That pickling layer
(ie the Binary class) is not for working with externally-defined binary
formats.

It might seem like we could co-opt the Binary class for this purpose eg
by parametrising by a dozen things like endian, padding, etc etc but I
don't think it scales or is sufficiently flexible (and it'd be slow).

What is missing in the binary package is a nice set of combinators for
using the low level layer to easily construct parsers for
externally-defined formats. That's what you'd want for your P9 protocol.

To reduce confusion we should also split the Haskell picking layer from
the lower layer.

This has been on our TODO list for some time. It needs to be done pretty
carefully however and we've not really had the time.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread Don Stewart
leimy2k:
 I actually need little endian encoding... wondering if anyone else hit this
 with Data.Binary. (because I'm working with Bell Lab's 9P protocol which does
 encode things on the network in little-endian order).
 
 Anyone got some tricks for this?

Yes!
There are big, little and host-endian primitives in the Get/Put monads.


http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Put.html#v%3AputWord16le

You can use these to build encoders directly.

Cheers,
  Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread David Leimbach
On Thu, May 14, 2009 at 8:40 PM, Don Stewart d...@galois.com wrote:

 leimy2k:
  I actually need little endian encoding... wondering if anyone else hit
 this
  with Data.Binary. (because I'm working with Bell Lab's 9P protocol which
 does
  encode things on the network in little-endian order).
 
  Anyone got some tricks for this?

 Yes!
 There are big, little and host-endian primitives in the Get/Put monads.


 http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Binary-Put.html#v%3AputWord16le

 You can use these to build encoders directly.


Cool... I just have to write my own encoder and decoder now.

As a request could we get encodeLe decodeLe for a later version of this
library?  :-)  That'd be totally awesome.




 Cheers,
   Don

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread Don Stewart
leimy2k:
 
 
 On Thu, May 14, 2009 at 8:40 PM, Don Stewart d...@galois.com wrote:
 
 leimy2k:
  I actually need little endian encoding... wondering if anyone else hit
 this
  with Data.Binary. (because I'm working with Bell Lab's 9P protocol which
 does
  encode things on the network in little-endian order).
 
  Anyone got some tricks for this?
 
 Yes!
 There are big, little and host-endian primitives in the Get/Put monads.
 
http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/
 Data-Binary-Put.html#v%3AputWord16le
 
 You can use these to build encoders directly.
 
 
 Cool... I just have to write my own encoder and decoder now.
 
 As a request could we get encodeLe decodeLe for a later version of this
 library?  :-)  That'd be totally awesome.

Oh, you mean entirely different instances for all the current ones, that
use LE encodings? 

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread David Leimbach
On Thu, May 14, 2009 at 8:46 PM, Don Stewart d...@galois.com wrote:

 leimy2k:
 
 
  On Thu, May 14, 2009 at 8:40 PM, Don Stewart d...@galois.com wrote:
 
  leimy2k:
   I actually need little endian encoding... wondering if anyone else
 hit
  this
   with Data.Binary. (because I'm working with Bell Lab's 9P protocol
 which
  does
   encode things on the network in little-endian order).
  
   Anyone got some tricks for this?
 
  Yes!
  There are big, little and host-endian primitives in the Get/Put
 monads.
 
 
 http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/
  Data-Binary-Put.html#v%3AputWord16le
 
  You can use these to build encoders directly.
 
 
  Cool... I just have to write my own encoder and decoder now.
 
  As a request could we get encodeLe decodeLe for a later version of this
  library?  :-)  That'd be totally awesome.

 Oh, you mean entirely different instances for all the current ones, that
 use LE encodings?


Well the library is leaning towards Network Byte Order in that it has
encode/decode that only encode/decode for Big Endian.

Us folks who have to do little endian all now have to write our own
encoding/decoding :-)

I'm speaking specifically of the encode/decode functions.  I have no idea
how they're implemented.

Are you saying that encode is doing something really simple and the default
encodings for things just happen to be big endian?  If so, then I understand
the pain but it still means I have to roll my own :-)  I guess if one
must choose, big endian kind of makes sense, except that the whole world is
little endian now, except for networks :-)  (No one *really* cares about
anything but x86 anyway these days right?)

I'm only half-kidding.



 -- Don

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread Don Stewart
 I'm speaking specifically of the encode/decode functions.  I have no idea how
 they're implemented.
 
 Are you saying that encode is doing something really simple and the default
 encodings for things just happen to be big endian?  If so, then I understand
 the pain but it still means I have to roll my own :-)  I guess if one must
 choose, big endian kind of makes sense, except that the whole world is little
 endian now, except for networks :-)  (No one *really* cares about anything but
 x86 anyway these days right?)

Oh, 'encode' has type:

encode :: Binary a = a - ByteString

it just encodes with the default instances, which are all network order:

http://en.wikipedia.org/wiki/Endianness#Endianness_in_networking

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread David Leimbach
On Thu, May 14, 2009 at 8:54 PM, Don Stewart d...@galois.com wrote:

  I'm speaking specifically of the encode/decode functions.  I have no idea
 how
  they're implemented.
 
  Are you saying that encode is doing something really simple and the
 default
  encodings for things just happen to be big endian?  If so, then I
 understand
  the pain but it still means I have to roll my own :-)  I guess if one
 must
  choose, big endian kind of makes sense, except that the whole world is
 little
  endian now, except for networks :-)  (No one *really* cares about
 anything but
  x86 anyway these days right?)

 Oh, 'encode' has type:

encode :: Binary a = a - ByteString

 it just encodes with the default instances, which are all network order:

http://en.wikipedia.org/wiki/Endianness#Endianness_in_networking


Yeah I understand that Big Endian == Network Byte Order... which would be
true, if I wasn't talking about Plan 9's 9P protocol which specifies little
endian bytes on the wire (as far as I can tell anyway from the man page).

Dave



 -- Don

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread David Leimbach
On Thu, May 14, 2009 at 8:57 PM, David Leimbach leim...@gmail.com wrote:



 On Thu, May 14, 2009 at 8:54 PM, Don Stewart d...@galois.com wrote:

  I'm speaking specifically of the encode/decode functions.  I have no
 idea how
  they're implemented.
 
  Are you saying that encode is doing something really simple and the
 default
  encodings for things just happen to be big endian?  If so, then I
 understand
  the pain but it still means I have to roll my own :-)  I guess if
 one must
  choose, big endian kind of makes sense, except that the whole world is
 little
  endian now, except for networks :-)  (No one *really* cares about
 anything but
  x86 anyway these days right?)

 Oh, 'encode' has type:

encode :: Binary a = a - ByteString

 it just encodes with the default instances, which are all network order:

http://en.wikipedia.org/wiki/Endianness#Endianness_in_networking


 Yeah I understand that Big Endian == Network Byte Order... which would be
 true, if I wasn't talking about Plan 9's 9P protocol which specifies little
 endian bytes on the wire (as far as I can tell anyway from the man page).

 Dave


FYI here's what I've ended up trying to write to negotiate the version of
a 9p server:

main = withSocketsDo $
   do
  ainfo - getAddrInfo Nothing (Just 127.0.0.1) (Just 6872)  --
hardcoded for now, it's an IRC filesystem server
  let a = head ainfo
  sock - socket AF_INET Stream defaultProtocol
  connect sock (addrAddress a)
  sendAll sock $ (toLazyByteString (putWord32le (fromIntegral (16
::Int32
  sendAll sock $ (encode (100 ::Int8))
  sendAll sock $ (toLazyByteString (putWord32le (fromIntegral (1024
::Int32
  sendAll sock $ (encode (C.pack 9P2000))


I feel like I should use wireshark or something to watch the bytes :-)  I'm
not feeling very sure about this.




 -- Don



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread David Leimbach
On Thu, May 14, 2009 at 9:10 PM, David Leimbach leim...@gmail.com wrote:



 On Thu, May 14, 2009 at 8:57 PM, David Leimbach leim...@gmail.com wrote:



 On Thu, May 14, 2009 at 8:54 PM, Don Stewart d...@galois.com wrote:

  I'm speaking specifically of the encode/decode functions.  I have no
 idea how
  they're implemented.
 
  Are you saying that encode is doing something really simple and the
 default
  encodings for things just happen to be big endian?  If so, then I
 understand
  the pain but it still means I have to roll my own :-)  I guess if
 one must
  choose, big endian kind of makes sense, except that the whole world is
 little
  endian now, except for networks :-)  (No one *really* cares about
 anything but
  x86 anyway these days right?)

 Oh, 'encode' has type:

encode :: Binary a = a - ByteString

 it just encodes with the default instances, which are all network order:

http://en.wikipedia.org/wiki/Endianness#Endianness_in_networking


 Yeah I understand that Big Endian == Network Byte Order... which would be
 true, if I wasn't talking about Plan 9's 9P protocol which specifies little
 endian bytes on the wire (as far as I can tell anyway from the man page).

 Dave


 FYI here's what I've ended up trying to write to negotiate the version of
 a 9p server:

 main = withSocketsDo $
do
   ainfo - getAddrInfo Nothing (Just 127.0.0.1) (Just 6872)  --
 hardcoded for now, it's an IRC filesystem server
   let a = head ainfo
   sock - socket AF_INET Stream defaultProtocol
   connect sock (addrAddress a)
   sendAll sock $ (toLazyByteString (putWord32le (fromIntegral (16
 ::Int32
   sendAll sock $ (encode (100 ::Int8))
   sendAll sock $ (toLazyByteString (putWord32le (fromIntegral (1024
 ::Int32
   sendAll sock $ (encode (C.pack 9P2000))



I totally forgot the tag part of 9p ugh.  I think I should probably just
go to bed now.



 I feel like I should use wireshark or something to watch the bytes :-)  I'm
 not feeling very sure about this.




 -- Don




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread Tim Docker
On a related matter, I am using Data.Binary to serialise data from
haskell
for use from other languages. The Data.Binary encoding of a Double is a
long
integer for the mantissa, and an int for the exponent.  This doesn't
work too well for interacting with other languages as I'd need to have
an arbitrary precision int type there to decode/encode. The CORBA CDR
standard encodes doubles in a big ended fashion like this (excuse my
possibly incorrect ascii art):


| byte | msb   lsb |
|--+---|
|0 | S   E6 E0 |
|1 | E10 E9 E8 E7 F3 F2 F1  F0 |
|2 | F11F4 |
|3 | F19   F12 |
|4 | F27   F20 |
|5 | F35   F28 |
|6 | F43   F36 |
|7 | F51   F44 |

Up until now, my code is pure haskell.  Is it possible to get at the
internal bits of a Double/CDouble in ghc? Or Should I use the FFI and
write C to encode something like the above?

Tim



From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of David Leimbach
Sent: Friday, 15 May 2009 1:58 PM
To: Don Stewart
Cc: Haskell Cafe
Subject: Re: [Haskell-cafe] Data.Binary and little endian encoding




On Thu, May 14, 2009 at 8:54 PM, Don Stewart d...@galois.com wrote:


 I'm speaking specifically of the encode/decode functions.  I
have no idea how
 they're implemented.

 Are you saying that encode is doing something really simple
and the default
 encodings for things just happen to be big endian?  If so,
then I understand
 the pain but it still means I have to roll my own :-)  I
guess if one must
 choose, big endian kind of makes sense, except that the whole
world is little
 endian now, except for networks :-)  (No one *really* cares
about anything but
 x86 anyway these days right?)


Oh, 'encode' has type:

   encode :: Binary a = a - ByteString

it just encodes with the default instances, which are all
network order:


http://en.wikipedia.org/wiki/Endianness#Endianness_in_networking



Yeah I understand that Big Endian == Network Byte Order... which would
be true, if I wasn't talking about Plan 9's 9P protocol which specifies
little endian bytes on the wire (as far as I can tell anyway from the
man page).

Dave
 


-- Don



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary and little endian encoding

2009-05-14 Thread Don Stewart
timd:
 On a related matter, I am using Data.Binary to serialise data from
 haskell
 for use from other languages. The Data.Binary encoding of a Double is a
 long
 integer for the mantissa, and an int for the exponent.  This doesn't
 work too well for interacting with other languages as I'd need to have
 an arbitrary precision int type there to decode/encode. The CORBA CDR
 standard encodes doubles in a big ended fashion like this (excuse my
 possibly incorrect ascii art):
 
 
 | byte | msb   lsb |
 |--+---|
 |0 | S   E6 E0 |
 |1 | E10 E9 E8 E7 F3 F2 F1  F0 |
 |2 | F11F4 |
 |3 | F19   F12 |
 |4 | F27   F20 |
 |5 | F35   F28 |
 |6 | F43   F36 |
 |7 | F51   F44 |
 
 Up until now, my code is pure haskell.  Is it possible to get at the
 internal bits of a Double/CDouble in ghc? Or Should I use the FFI and
 write C to encode something like the above?

Yep, it's possible, just not portably so. Google for Data.Binary IEEE
discussions.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe