Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-20 Thread Adam Langley
On Jan 15, 2008 7:33 PM, Adam Langley [EMAIL PROTECTED] wrote:
 Ok, no TH ;)

I've just uploaded binary-strict 0.2.2 to Hackage which factors most
of the common code out via CPP. Hopefully I didn't break anything.



AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-17 Thread Dominic Steinitz
Adam Langley agl at imperialviolet.org writes:

 
 BitGet is just an API RFC at the moment, so I'm just describing it
 here - not trying to justify it.
 
 In BitGet there's getAsWord[8|16|32|64] which take a number of bits ($n$) and
 returns the next $n$ bits in the bottom of a Word$x$. Thus, getAsWord8 is what
 you call getBits and, if you had a 48 bit number, you could use getAsWord64 
 and
 the bottom 48-bits of the resulting Word64 would be what you want.
 
 Equally, asking for more than $x$ bits when calling getAsWord$x$ is a mistake,
 however I don't check for it in the interest of speed.
 
 There are also get[Left|Right]ByteString which return the next $n$ bits in a
 ByteString of Word8's. The padding is either at the end of the last byte (left
 aligned) or at the beginning of the first byte (right aligned).
 

Ok so I should be doing something like this. I'm not clear what happens if you
are reading from a socket and not all the input has arrived but I'll think 
about that over the weekend.

Another thought: could e.g. getRightByteString be in the IO monad and then I
don't have to run the Get(?) monad? Or is that a really stupid question?

Dominic.

import qualified Data.ByteString as B
import Data.Word
import IO

import qualified Data.Binary.Strict.BitGet as BG

test =
   do h - openFile foobarbaz ReadMode
  b - B.hGetContents h
  let ebms = test2 b 
  case ebms of
 Left s- return s
 Right bms - return (concat ((map (show . B.unpack) bms)))

test1 =
   do bm1 - BG.getRightByteString 2
  bm2 - BG.getRightByteString 2
  return [bm1,bm2]
  
test2 bs = BG.runBitGet bs test1
  
  





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


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-17 Thread Adam Langley
On Jan 17, 2008 11:05 AM, Dominic Steinitz
[EMAIL PROTECTED] wrote:

 I'm not clear what happens if you
 are reading from a socket and not all the input has arrived but I'll think
 about that over the weekend.

At the moment, BitGet deals with strict ByteStrings only. One could use it
within a standard Get monad by getting a strict ByteString from the lazy input.
I believe that lazy ByteStrings got fixed a while back so that reading from a
socket doesn't block reading a whole block. (i.e. if you trickle data, byte by
byte, to a socket a lazy ByteString should return a spine of 1 byte strict
ByteStrings.)

A fully lazy BitGet would also be possible, of course, I've just not written it
yet ;)

 Adam Langley agl at imperialviolet.org writes:
 Another thought: could e.g. getRightByteString be in the IO monad and then I
 don't have to run the Get(?) monad? Or is that a really stupid question?

If it were in the IO monad, I guess that you're suggesting that it read from a
handle? If that were the case, the remainder of the last byte would have to be
discarded because one can only read whole bytes from a Handle and there's no
mechanism for pushing back into it.

It's certainly possible to do, but I think a quick wrapper around a BitGet
would be the way to do it. If it's particually desirable I can add it, although
I'll admit that it seems a bit odd and I'm wondering what your use case is.

Cheers


AGL

--
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-16 Thread Dominic Steinitz
Adam Langley agl at imperialviolet.org writes:

 
 On Jan 10, 2008 10:45 AM, Don Stewart dons at galois.com wrote:
  That's pretty much what we envisaged as the approach to take.
  Monad transformers adding some bit-buffer state over Get/Put.
 
 For anyone who's still reading this thread...
 
 I've just uploaded[1] binary-strict 0.2.1 which includes
 Data.Binary.Strict.BitGet - a Get like monad which works by the bit.
 I'm afraid that Haddock 2 is choaking on {-# UNPACK #-}, so I don't
 have the HTML documentation to point to. (And I thought that Haddock 2
 was going to fix all those parsing issues :( - hopefully I'm just
 doing something stupid).
 
 [1] 
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-strict-0.2.1
 
 AGL
 

Thanks for taking the time on this.

The old NewBinary had

NewBinary.Binary.getBits ::
  NewBinary.Binary.BinHandle - Int - IO GHC.Word.Word8

which allowed you to do things like

tlv_ bin =
   do tagValueVal - getBits bin 5
  tagConstructionVal - getBits bin 1
  tagTypeVal - getBits bin 2

I'm sure I'm wrong but putting bits into [Bool] doesn't look very efficient. Of
course, NewBinary didn't address what happened for n = 8. Some possibilities
are a) not allowing more than 8 b) returning [Word8] or c) (which I thought was
where we'd go) a ByteString with some sort of padding.

Dominic.

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


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-16 Thread Adam Langley
On Jan 16, 2008 2:41 PM, Dominic Steinitz
[EMAIL PROTECTED] wrote:
 tlv_ bin =
do tagValueVal - getBits bin 5
   tagConstructionVal - getBits bin 1
   tagTypeVal - getBits bin 2

 I'm sure I'm wrong but putting bits into [Bool] doesn't look very efficient. 
 Of
 course, NewBinary didn't address what happened for n = 8. Some possibilities
 are a) not allowing more than 8 b) returning [Word8] or c) (which I thought 
 was
 where we'd go) a ByteString with some sort of padding.

BitGet is just an API RFC at the moment, so I'm just describing it
here - not trying to justify it.

In BitGet there's getAsWord[8|16|32|64] which take a number of bits ($n$) and
returns the next $n$ bits in the bottom of a Word$x$. Thus, getAsWord8 is what
you call getBits and, if you had a 48 bit number, you could use getAsWord64 and
the bottom 48-bits of the resulting Word64 would be what you want.

Equally, asking for more than $x$ bits when calling getAsWord$x$ is a mistake,
however I don't check for it in the interest of speed.

There are also get[Left|Right]ByteString which return the next $n$ bits in a
ByteString of Word8's. The padding is either at the end of the last byte (left
aligned) or at the beginning of the first byte (right aligned).

If you did want a [Bool], you could use:
  bits - sequence $ take n $ repeat getBit


AGL

--
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-15 Thread Adam Langley
On Jan 10, 2008 10:45 AM, Don Stewart [EMAIL PROTECTED] wrote:
 That's pretty much what we envisaged as the approach to take.
 Monad transformers adding some bit-buffer state over Get/Put.

For anyone who's still reading this thread...

I've just uploaded[1] binary-strict 0.2.1 which includes
Data.Binary.Strict.BitGet - a Get like monad which works by the bit.
I'm afraid that Haddock 2 is choaking on {-# UNPACK #-}, so I don't
have the HTML documentation to point to. (And I thought that Haddock 2
was going to fix all those parsing issues :( - hopefully I'm just
doing something stupid).

[1] 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-strict-0.2.1

AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-15 Thread Don Stewart
agl:
 On Jan 10, 2008 10:45 AM, Don Stewart [EMAIL PROTECTED] wrote:
  That's pretty much what we envisaged as the approach to take.
  Monad transformers adding some bit-buffer state over Get/Put.
 
 For anyone who's still reading this thread...
 
 I've just uploaded[1] binary-strict 0.2.1 which includes
 Data.Binary.Strict.BitGet - a Get like monad which works by the bit.
 I'm afraid that Haddock 2 is choaking on {-# UNPACK #-}, so I don't
 have the HTML documentation to point to. (And I thought that Haddock 2
 was going to fix all those parsing issues :( - hopefully I'm just
 doing something stupid).
 
 [1] 
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-strict-0.2.1

Ok. That's awesome. I guess if you do all the TODOs for Binary like
this, we should merge the code back in :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-15 Thread Adam Langley
On Jan 15, 2008 3:26 PM, Don Stewart [EMAIL PROTECTED] wrote:
 Ok. That's awesome. I guess if you do all the TODOs for Binary like
 this, we should merge the code back in :)

Well, at the moment I'm pretty unhappy with the amount of code
duplication required both within binary-strict and between binary and
binary-strict. I think this code needs a whole lot of restructuring
(maybe a bit of TH for generating the common bits). I'll get to that
when it appears that the API seems reasonable.

AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-15 Thread Neil Mitchell
Hi

 (maybe a bit of TH for generating the common bits)

That would be bad. Then you'll have gone from Data.Binary being
portable code, to being GHC specific code, and I will cry :'-(

CPP is a good way to common stuff up in a portable way - I've used it
in FilePath. There is nearly no end to the amount of crazy CPP hackery
you can use to refactor stuff.

Thanks

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


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-15 Thread Adam Langley
On Jan 15, 2008 5:01 PM, Neil Mitchell [EMAIL PROTECTED] wrote:
 That would be bad. Then you'll have gone from Data.Binary being
 portable code, to being GHC specific code, and I will cry :'-(

Ok, no TH ;)


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-10 Thread Don Stewart
agl:
 On Jan 9, 2008 5:01 PM, David Roundy [EMAIL PROTECTED] wrote:
  But I can't imagine an implementation in which this change wouldn't slow
  down getBytes for the normal case.  Perhaps the slowdown would be small,
  but it seems unwise to enforce that slowness at the API level, when we've
  already got a perfectly good API for fast binary IO.  Maybe there's some
  type hackery you could do to avoid a speed penalty, but that's a lot to add
  for a somewhat dubious benefit.
 
 I believe that it would be an additional if statement in the fast path at 
 least.
 
 How about a BitGet monad which get be run in the Get monad?
 
  test :: Get ()
  test = do
   runBitGet 2 (do
 getBitField 2)
 
 So the first argument to runBitGet is the number of bytes to parse for
 bit fields and then functions in BitGet can extract bit-length ints
 etc.
 
 Anyone like that idea?

That's pretty much what we envisaged as the approach to take.
Monad transformers adding some bit-buffer state over Get/Put.

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


[Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-09 Thread Dominic Steinitz
Duncan Coutts duncan.coutts at worc.ox.ac.uk writes:

 
 
 On Wed, 2008-01-09 at 09:26 +, Dominic Steinitz wrote:
  Adam Langley agl at imperialviolet.org writes:
  
   But if this is useful to you, make any requests. I'll (hopefully) do
   them, clean it up and push a new release of binary-strict.
   
  How difficult would it be to have a getBits functions as well as a getBytes?
  That would allow me drop the dependency on NewBinary in the ASN.1 package.
 
 The difficulty is in deciding what the api should be. Does it give you a
 real bitstream or only a byte aligned one? If I ask for 3 bits then 15
 bytes what does it do? Does it assume I meant 3 bits, then pad to the
 next byte boundary and get 15 bytes, or does it mean get 15 bytes but at
 this 3 bit shift offset?
 
 Duncan
 

I'd suggest an aligned and unaligned api. 

So the aligned api would get 3 bits and the 15 bytes would start from the next
byte boundary.

The unaligned api would get 3 bits and the 15 bytes (=15 x 8 bits) would finish
still with an offset of 3.

Dominic.


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


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-09 Thread David Roundy
On Jan 9, 2008 10:10 AM, Dominic Steinitz
[EMAIL PROTECTED] wrote:
 Duncan Coutts duncan.coutts at worc.ox.ac.uk writes:
  The difficulty is in deciding what the api should be. Does it give you a
  real bitstream or only a byte aligned one? If I ask for 3 bits then 15
  bytes what does it do? Does it assume I meant 3 bits, then pad to the
  next byte boundary and get 15 bytes, or does it mean get 15 bytes but at
  this 3 bit shift offset?

 I'd suggest an aligned and unaligned api.

 So the aligned api would get 3 bits and the 15 bytes would start from the next
 byte boundary.

 The unaligned api would get 3 bits and the 15 bytes (=15 x 8 bits) would 
 finish
 still with an offset of 3.

Do you mean we'd have an unalignedGetBytes as well as getBytes (which
would remain aligned)? That would make sense, but it would seem a bit
heavy to duplicate all of the binary API.

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


[Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-09 Thread Achim Schneider
David Roundy [EMAIL PROTECTED] wrote:

 On Jan 9, 2008 10:10 AM, Dominic Steinitz
 [EMAIL PROTECTED] wrote:
  Duncan Coutts duncan.coutts at worc.ox.ac.uk writes:
   The difficulty is in deciding what the api should be. Does it
   give you a real bitstream or only a byte aligned one? If I ask
   for 3 bits then 15 bytes what does it do? Does it assume I meant
   3 bits, then pad to the next byte boundary and get 15 bytes, or
   does it mean get 15 bytes but at this 3 bit shift offset?
 
  I'd suggest an aligned and unaligned api.
 
  So the aligned api would get 3 bits and the 15 bytes would start
  from the next byte boundary.
 
  The unaligned api would get 3 bits and the 15 bytes (=15 x 8 bits)
  would finish still with an offset of 3.
 
 Do you mean we'd have an unalignedGetBytes as well as getBytes (which
 would remain aligned)? That would make sense, but it would seem a bit
 heavy to duplicate all of the binary API.
 
getBytes per default unaligned and additionally snapToNextByte?


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-09 Thread David Roundy
On Wed, Jan 09, 2008 at 11:43:52PM +0100, Achim Schneider wrote:
 David Roundy [EMAIL PROTECTED] wrote:
 
  On Jan 9, 2008 10:10 AM, Dominic Steinitz
  [EMAIL PROTECTED] wrote:
   Duncan Coutts duncan.coutts at worc.ox.ac.uk writes:
The difficulty is in deciding what the api should be. Does it
give you a real bitstream or only a byte aligned one? If I ask
for 3 bits then 15 bytes what does it do? Does it assume I meant
3 bits, then pad to the next byte boundary and get 15 bytes, or
does it mean get 15 bytes but at this 3 bit shift offset?
  
   I'd suggest an aligned and unaligned api.
  
   So the aligned api would get 3 bits and the 15 bytes would start
   from the next byte boundary.
  
   The unaligned api would get 3 bits and the 15 bytes (=15 x 8 bits)
   would finish still with an offset of 3.
  
  Do you mean we'd have an unalignedGetBytes as well as getBytes (which
  would remain aligned)? That would make sense, but it would seem a bit
  heavy to duplicate all of the binary API.
  
 getBytes per default unaligned and additionally snapToNextByte?

But I can't imagine an implementation in which this change wouldn't slow
down getBytes for the normal case.  Perhaps the slowdown would be small,
but it seems unwise to enforce that slowness at the API level, when we've
already got a perfectly good API for fast binary IO.  Maybe there's some
type hackery you could do to avoid a speed penalty, but that's a lot to add
for a somewhat dubious benefit.

Note that you could get a similar effect with getBytes always aligned, and
an additional function shiftToByte which takes the remainder of the input
and bitshifts everything so that the current read pointer is on a byte
boundary.  Obviously this would be an O(N) operation (where N is the
remainder of the input), which could certainly be a problem.

Another option, I suppose, would be to introduce a type class for
bytewise-reading monads.  That'd be a type hack, but not such a bad one.
Then you could have the efficient implementation, and one that allows
bitwise reading, and there could also be a function that allows bitwise
parsing of a chunk of a byte-aligned data.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-09 Thread Adam Langley
On Jan 9, 2008 5:01 PM, David Roundy [EMAIL PROTECTED] wrote:
 But I can't imagine an implementation in which this change wouldn't slow
 down getBytes for the normal case.  Perhaps the slowdown would be small,
 but it seems unwise to enforce that slowness at the API level, when we've
 already got a perfectly good API for fast binary IO.  Maybe there's some
 type hackery you could do to avoid a speed penalty, but that's a lot to add
 for a somewhat dubious benefit.

I believe that it would be an additional if statement in the fast path at least.

How about a BitGet monad which get be run in the Get monad?

 test :: Get ()
 test = do
  runBitGet 2 (do
getBitField 2)

So the first argument to runBitGet is the number of bytes to parse for
bit fields and then functions in BitGet can extract bit-length ints
etc.

Anyone like that idea?

AGL


-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-09 Thread Achim Schneider
David Roundy [EMAIL PROTECTED] wrote:

 [ something that every C programmer dreams of ]

I'm not going to answer, I'd be just vapour-waring around.

But, yes, any-alignment any-granularity reads can be done in O(1), with
1 ranging from case to case from one instruction to a few shifts and
's, plus some constant cost to choose the appropriate function based
on current alignment, which could be set by things like snapToByte,
snapToWord, snapToInt128, getBit, getBits num_bytes, getByte,
GetWhatever and one state var to change the advance mode from
request-sized to constant-sized.

As I said, I'm vapour-waring.

But then it's a swiss army knife. With many general- and
special-purpose functions.

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

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