[Haskell-cafe] Success and one last issue with Data.Binary

David Leimbach leimy2k at gmail.com
Tue Jun 2 17:00:12 EDT 2009


0.5.0.1
On Tue, Jun 2, 2009 at 1:56 PM, John Van Enk <vanenkj at gmail.com> wrote:

> Just so we know that it's not the issue, what version of binary are
> you using? The most current one is 0.5.0.1.
>
> On Tue, Jun 2, 2009 at 4:46 PM, David Leimbach <leimy2k at gmail.com> wrote:
> >
> >
> > On Tue, Jun 2, 2009 at 1:36 PM, John Van Enk <vanenkj at gmail.com> wrote:
> >>
> >> What happens if you use `getRemainingLazyByteString' in your error
> >> branch instead of `getLazyByteString'?
> >
> > I actually am using getRemainingLazyByteString right now, and it still
> > thinks I'm asking for a 20th byte.
> > if I delete the other guarded branch of that function, it still fails
> saying
> > I'm asking for the 20th byte.
> > Dave
> >
> >>
> >> On Tue, Jun 2, 2009 at 4:31 PM, David Leimbach <leimy2k at gmail.com>
> wrote:
> >> >
> >> >
> >> > On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk <vanenkj at gmail.com>
> wrote:
> >> >>
> >> >> I think Thomas' point was that some other branch in `getSpecific' is
> >> >> running. Is there a chance we can see the rest of `getSpecific'?
> >> >
> >> > Sure:  (In the meantime, I'll try the suggested code from before)
> >> >  get = do s <- getWord32le
> >> >              mtype <- getWord8
> >> >              getSpecific s mtype
> >> >         where
> >> >           getSpecific s mt
> >> >                       | mt == mtRversion = do t <- getWord16le
> >> >                                               ms <- getWord32le
> >> >                                               ss <- getWord16le
> >> >                                               v <-
> >> > getRemainingLazyByteString
> >> >                                               return $ MessageClient $
> >> > Rversion {size=s,
> >> >
> >> >     mtype=mt,
> >> >
> >> >     tag=t,
> >> >
> >> >     msize=ms,
> >> >
> >> >     ssize=ss,
> >> >
> >> >     version=v}
> >> >                       | mt == mtRerror = do t <- getWord16le
> >> >                                             ss <- getWord16le
> >> >                                             e <- getLazyByteString $
> >> > fromIntegral ss
> >> >                                             return $ MessageClient $
> >> > Rerror
> >> > {size=s,
> >> >
> >> > mtype=mt,
> >> >
> >> > tag=t,
> >> >
> >> > ssize=ss,
> >> >
> >> > ename=e}
> >> >
> >> >>
> >> >> On Tue, Jun 2, 2009 at 4:20 PM, David Leimbach <leimy2k at gmail.com>
> >> >> wrote:
> >> >> > The thing is I have 19 bytes in the hex string I provided:
> >> >> > 1300000065ffff000400000600395032303030
> >> >> > That's 38 characters or 19 bytes.
> >> >> > The last 4 are 9P2000
> >> >> > 13000000  = 4 bytes for 32bit message payload,  This is little
> endian
> >> >> > for 19
> >> >> > bytes total.
> >> >> > 65 = 1 byte for message type.  65 is "Rversion" or the response
> type
> >> >> > for
> >> >> > a
> >> >> > Tversion request
> >> >> > ffff = 2 bytes for 16bit message "tag".
> >> >> >
> >> >> > 00040000 = 4 bytes for the 32 bit maximum message payload size I'm
> >> >> > negotiating with the 9P server.  This is little endian for 1024
> >> >> > 0600 =  2 bytes for 16 bit value for the length of the "string" I'm
> >> >> > sending.
> >> >> >  The strings are *NOT* null terminated in 9p, and this is little
> >> >> > endian
> >> >> > for
> >> >> > 6 bytes remaining.
> >> >> > 5032303030 = 6 bytes the ASCII or UTF-8 string "9P2000" which is 6
> >> >> > bytes
> >> >> > 4 + 1 + 2 + 4 + 2 + 6 = 19 bytes.
> >> >> > As far as I can see, my "get" code does NOT ask for a 20th byte, so
> >> >> > why
> >> >> > am I
> >> >> > getting that error?
> >> >> > get = do s <- getWord32le  -- 4
> >> >> >              mtype <- getWord8  -- 1
> >> >> >              getSpecific s mtype
> >> >> >         where
> >> >> >           getSpecific s mt
> >> >> >                       | mt == mtRversion = do t <- getWord16le -- 2
> >> >> >                                               ms <- getWord32le  --
> 4
> >> >> >                                               ss <- getWord16le --
> 2
> >> >> >                                               v <-
> >> >> > getRemainingLazyByteString  -- remaining should be 6 bytes.
> >> >> >                                               return $
> MessageClient
> >> >> > $
> >> >> > Rversion {size=s,
> >> >> >
> >> >> >                         mtype=mt,
> >> >> >
> >> >> >                         tag=t,
> >> >> >
> >> >> >                         msize=ms,
> >> >> >
> >> >> >                         ssize=ss,
> >> >> >
> >> >> >                         version=v}
> >> >> > Should I file a bug?  I don't believe I should be seeing an error
> >> >> > message
> >> >> > claiming a failure at the 20th byte when I've never asked for one.
> >> >> > Dave
> >> >> >
> >> >> > On Tue, Jun 2, 2009 at 10:51 AM, John Van Enk <vanenkj at gmail.com>
> >> >> > wrote:
> >> >> >>
> >> >> >> Thomas,
> >> >> >>
> >> >> >> You're correct. For some reason, I based my advice on the thought
> >> >> >> that
> >> >> >> 19 was the minimum size instead of 13.
> >> >> >>
> >> >> >> On Tue, Jun 2, 2009 at 1:24 PM, Thomas DuBuisson
> >> >> >> <thomas.dubuisson at gmail.com> wrote:
> >> >> >> >> I think getRemainingLazyByteString expects at least one byte
> >> >> >> > No, it works with an empty bytestring.  Or, my tests do with
> >> >> >> > binary
> >> >> >> > 0.5.0.1.
> >> >> >> >
> >> >> >> > The specific error means you are requiring more data than
> >> >> >> > providing.
> >> >> >> > First check the length of the bytestring you pass in to the to
> >> >> >> > level
> >> >> >> > decode (or 'get') routine and walk though that to figure out how
> >> >> >> > much
> >> >> >> > it should be consuming.  I notice you have a guard on the
> >> >> >> > 'getSpecific' function, hopefully you're sure the case you gave
> us
> >> >> >> > is
> >> >> >> > the branch being taken.
> >> >> >> >
> >> >> >> > I think the issue isn't with the code provided.  I cleaned up
> the
> >> >> >> > code
> >> >> >> > (which did change behavior due to the guard and data
> declarations
> >> >> >> > that
> >> >> >> > weren't in the mailling) and it works fine all the way down to
> the
> >> >> >> > expected minimum of 13 bytes.
> >> >> >> >
> >> >> >> >
> >> >> >> >> import Data.ByteString.Lazy
> >> >> >> >> import Data.Binary
> >> >> >> >> import Data.Binary.Get
> >> >> >> >>
> >> >> >> >> data RV =
> >> >> >> >> Rversion {     size   :: Word32,
> >> >> >> >>                mtype  :: Word8,
> >> >> >> >>                tag    :: Word16,
> >> >> >> >>                msize  :: Word32,
> >> >> >> >>                ssize  :: Word16,
> >> >> >> >>                version :: ByteString}
> >> >> >> >>       deriving (Eq, Ord, Show)
> >> >> >> >
> >> >> >> >> instance Binary RV where
> >> >> >> >>  get = do s <- getWord32le
> >> >> >> >>          mtype <- getWord8
> >> >> >> >>          getSpecific s mtype
> >> >> >> >>   where
> >> >> >> >>    getSpecific s mt = do t <- getWord16le
> >> >> >> >>                          ms <- getWord32le
> >> >> >> >>                          ss <- getWord16le
> >> >> >> >>                          v <- getRemainingLazyByteString
> >> >> >> >>                          return $ Rversion {size=s,
> >> >> >> >>                                             mtype=mt,
> >> >> >> >>                                             tag=t,
> >> >> >> >>                                             msize=ms,
> >> >> >> >>                                             ssize=ss,
> >> >> >> >>                                             version=v }
> >> >> >> >>  put _ = undefined
> >> >> >> >
> >> >> >>
> >> >> >>
> >> >> >>
> >> >> >> --
> >> >> >> /jve
> >> >> >
> >> >> >
> >> >> > _______________________________________________
> >> >> > Haskell-Cafe mailing list
> >> >> > Haskell-Cafe at haskell.org
> >> >> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >> >> >
> >> >> >
> >> >>
> >> >>
> >> >>
> >> >> --
> >> >> /jve
> >> >
> >> >
> >>
> >>
> >>
> >> --
> >> /jve
> >
> >
>
>
>
> --
> /jve
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090602/9e6b7891/attachment.html


More information about the Haskell-Cafe mailing list