
I've got the following "printHex" string as a response from a 9P server running on the Inferno Operating System. (thanks to a friendly mailing list contributor who sent a nice example of using Data.Binary) 1300000065ffff000400000600395032303030 This is a little endian encoded ByteString with the following fields in it: Rversion {size :: Word32, mtype :: Word8, tag :: Word16, msize :: Word32, ssize :: Word16, version :: ByteString} But when I try to use the following implementation of "get" to decode this stream, I'm getting the following error: "too few bytes. Failed reading at byte position 20" Unfortunately, I'm only expecting 19 bytes, and in fact never asked for byte 20. (I am just asking for everything up to ssize, and then "getRemainingLazyByteString"). Is this a bug? Is it mine or in Data.Binary? :-) Here's my "get" function: 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} The good news is I'm talking 9P otherwise, correctly, just having some decoding issues. I hope to have a hackage package eventually for this. Dave

I think getRemainingLazyByteString expects at least one byte (this,
perhaps, is not the appropriate behavior). You'll want to wrap your
call to getRemainingLazyByteString with a call to
Data.Binary.Get.remaining[1] like this:
foo = do
r <- remaining
rbs <- case r of
0 -> return empty -- Data.ByteString.Lazy.empty
_ -> getRemainingLazyByteString
Hope this helps. :)
/jve
1: http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Bin...
On Tue, Jun 2, 2009 at 12:20 PM, David Leimbach
I've got the following "printHex" string as a response from a 9P server running on the Inferno Operating System. (thanks to a friendly mailing list contributor who sent a nice example of using Data.Binary) 1300000065ffff000400000600395032303030 This is a little endian encoded ByteString with the following fields in it: Rversion {size :: Word32, mtype :: Word8, tag :: Word16, msize :: Word32, ssize :: Word16, version :: ByteString} But when I try to use the following implementation of "get" to decode this stream, I'm getting the following error: "too few bytes. Failed reading at byte position 20" Unfortunately, I'm only expecting 19 bytes, and in fact never asked for byte 20. (I am just asking for everything up to ssize, and then "getRemainingLazyByteString"). Is this a bug? Is it mine or in Data.Binary? :-) Here's my "get" function: 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}
The good news is I'm talking 9P otherwise, correctly, just having some decoding issues. I hope to have a hackage package eventually for this. Dave _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve

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

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
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

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
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
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

I think Thomas' point was that some other branch in `getSpecific' is
running. Is there a chance we can see the rest of `getSpecific'?
On Tue, Jun 2, 2009 at 4:20 PM, David Leimbach
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve

On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve

What happens if you use `getRemainingLazyByteString' in your error
branch instead of `getLazyByteString'?
On Tue, Jun 2, 2009 at 4:31 PM, David Leimbach
On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve
-- /jve

On Tue, Jun 2, 2009 at 1:36 PM, John Van Enk
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
wrote: On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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 $
{size=s,
mtype=mt,
tag=t,
ssize=ss,
ename=e}
On Tue, Jun 2, 2009 at 4:20 PM, David Leimbach
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
wrote: Thomas,
You're correct. For some reason, I based my advice on the thought
19 was the minimum size instead of 13.
On Tue, Jun 2, 2009 at 1:24 PM, Thomas DuBuisson
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
Rerror that 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve
-- /jve

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
On Tue, Jun 2, 2009 at 1:36 PM, John Van Enk
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
wrote: On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve
-- /jve
-- /jve

0.5.0.1
On Tue, Jun 2, 2009 at 1:56 PM, John Van Enk
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
wrote: On Tue, Jun 2, 2009 at 1:36 PM, John Van Enk
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
I'm asking for the 20th byte. Dave
On Tue, Jun 2, 2009 at 4:31 PM, David Leimbach
wrote:
On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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
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
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 > 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 > > 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
saying the 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve
-- /jve
-- /jve

Again, I can't reproduce your problem. Are you getting data through
some previous Binary instance before calling the routines you show us
here? The code I tested with is below - I've tried it with both
'getSpecific' paths by commenting out one path at a time. Both
methods work, shown below.
Thomas
*Main> decode test :: RV
Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize =
6, version = Chunk "9P2000" Empty}
*Main> :q
Leaving GHCi.
[... edit ...]
[1 of 1] Compiling Main ( p.hs, interpreted )
Ok, modules loaded: Main.
*Main> decode test :: RV
Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename =
Chunk "\NUL\NUL\ACK\NUL9P2000" Empty}
*Main>
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}
| Rerror { size :: Word32,
mtype :: Word8,
tag :: Word16,
ssize :: Word16,
ename :: ByteString}
deriving (Eq, Ord, Show)
instance Binary RV where
put = undefined
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}
-}
= do t <- getWord16le
ss <- getWord16le
e <- getLazyByteString $ fromIntegral ss
return $ Rerror {size=s,
mtype=mt,
tag=t,
ssize=ss,
ename=e}
test = pack
[ 0x13
, 0x00
, 0x00
, 0x00
, 0x65
, 0xff
, 0xff
, 0x00
, 0x04
, 0x00
, 0x00
, 0x06
, 0x00
, 0x39
, 0x50
, 0x32
, 0x30
, 0x30
, 0x30 ]
On Tue, Jun 2, 2009 at 1:31 PM, David Leimbach
On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Jun 2, 2009 at 1:56 PM, Thomas DuBuisson wrote: Again, I can't reproduce your problem. Are you getting data through
some previous Binary instance before calling the routines you show us
here? Ah good question... I'm calling "decode", but it's not clear that it's even
running my instance of Get!!!!
If I have a lazy bytestring, and call "decode", which instance of "Get"
runs? Probably not my 9P message version I'll bet...
geeze... :-( The code I tested with is below - I've tried it with both
'getSpecific' paths by commenting out one path at a time. Both
methods work, shown below. Thomas *Main> decode test :: RV
Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize =
6, version = Chunk "9P2000" Empty}
*Main> :q
Leaving GHCi.
[... edit ...]
[1 of 1] Compiling Main ( p.hs, interpreted )
Ok, modules loaded: Main.
*Main> decode test :: RV
Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename =
Chunk "\NUL\NUL\ACK\NUL9P2000" Empty}
*Main> 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}
| Rerror { size :: Word32,
mtype :: Word8,
tag :: Word16,
ssize :: Word16,
ename :: ByteString}
deriving (Eq, Ord, Show) instance Binary RV where
put = undefined
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}
-}
= do t <- getWord16le
ss <- getWord16le
e <- getLazyByteString $ fromIntegral ss
return $ Rerror {size=s,
mtype=mt,
tag=t,
ssize=ss,
ename=e} test = pack
[ 0x13
, 0x00
, 0x00
, 0x00
, 0x65
, 0xff
, 0xff
, 0x00
, 0x04
, 0x00
, 0x00
, 0x06
, 0x00
, 0x39
, 0x50
, 0x32
, 0x30
, 0x30
, 0x30 ] On Tue, Jun 2, 2009 at 1:31 PM, David Leimbach On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk 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 $ {size=s, mtype=mt, tag=t, ssize=ss, ename=e} On Tue, Jun 2, 2009 at 4:20 PM, David Leimbach 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 Thomas, You're correct. For some reason, I based my advice on the thought 19 was the minimum size instead of 13. On Tue, Jun 2, 2009 at 1:24 PM, Thomas DuBuisson
> 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 Rerror
that
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe --
/jve _______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

It will run the instance of the inferred type (or you can provide a
type signature to force it). I've done this often before with lists -
trying to read in some arbitrary, typically high, number of elements
causes issues :-)
Thomas
On Tue, Jun 2, 2009 at 2:07 PM, David Leimbach
On Tue, Jun 2, 2009 at 1:56 PM, Thomas DuBuisson
wrote: Again, I can't reproduce your problem. Are you getting data through some previous Binary instance before calling the routines you show us here?
Ah good question... I'm calling "decode", but it's not clear that it's even running my instance of Get!!!! If I have a lazy bytestring, and call "decode", which instance of "Get" runs? Probably not my 9P message version I'll bet... geeze... :-(
The code I tested with is below - I've tried it with both 'getSpecific' paths by commenting out one path at a time. Both methods work, shown below.
Thomas
*Main> decode test :: RV Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize = 6, version = Chunk "9P2000" Empty} *Main> :q Leaving GHCi. [... edit ...] [1 of 1] Compiling Main ( p.hs, interpreted ) Ok, modules loaded: Main. *Main> decode test :: RV Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename = Chunk "\NUL\NUL\ACK\NUL9P2000" Empty} *Main>
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} | Rerror { size :: Word32, mtype :: Word8, tag :: Word16, ssize :: Word16, ename :: ByteString} deriving (Eq, Ord, Show)
instance Binary RV where put = undefined 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} -} = do t <- getWord16le ss <- getWord16le e <- getLazyByteString $ fromIntegral ss return $ Rerror {size=s, mtype=mt, tag=t, ssize=ss, ename=e}
test = pack [ 0x13 , 0x00 , 0x00 , 0x00 , 0x65 , 0xff , 0xff , 0x00 , 0x04 , 0x00 , 0x00 , 0x06 , 0x00 , 0x39 , 0x50 , 0x32 , 0x30 , 0x30 , 0x30 ]
On Tue, Jun 2, 2009 at 1:31 PM, David Leimbach
wrote: On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Jun 2, 2009 at 2:07 PM, David Leimbach
On Tue, Jun 2, 2009 at 1:56 PM, Thomas DuBuisson < thomas.dubuisson@gmail.com> wrote:
Again, I can't reproduce your problem. Are you getting data through some previous Binary instance before calling the routines you show us here?
Ah good question... I'm calling "decode", but it's not clear that it's even running my instance of Get!!!!
If I have a lazy bytestring, and call "decode", which instance of "Get" runs? Probably not my 9P message version I'll bet...
geeze... :-(
AAAAANd... that was it. I totally didn't decode with the right decoder. By the expression I had, it appears it was trying to decode a ByteString as a String, and that was causing a big darned mess. Thanks for all the help guys. I'm glad it's not a bug in the library, just my dumb code Dave
The code I tested with is below - I've tried it with both 'getSpecific' paths by commenting out one path at a time. Both methods work, shown below.
Thomas
*Main> decode test :: RV Rversion {size = 19, mtype = 101, tag = 65535, msize = 1024, ssize = 6, version = Chunk "9P2000" Empty} *Main> :q Leaving GHCi. [... edit ...] [1 of 1] Compiling Main ( p.hs, interpreted ) Ok, modules loaded: Main. *Main> decode test :: RV Rerror {size = 19, mtype = 101, tag = 65535, ssize = 1024, ename = Chunk "\NUL\NUL\ACK\NUL9P2000" Empty} *Main>
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} | Rerror { size :: Word32, mtype :: Word8, tag :: Word16, ssize :: Word16, ename :: ByteString} deriving (Eq, Ord, Show)
instance Binary RV where put = undefined 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} -} = do t <- getWord16le ss <- getWord16le e <- getLazyByteString $ fromIntegral ss return $ Rerror {size=s, mtype=mt, tag=t, ssize=ss, ename=e}
test = pack [ 0x13 , 0x00 , 0x00 , 0x00 , 0x65 , 0xff , 0xff , 0x00 , 0x04 , 0x00 , 0x00 , 0x06 , 0x00 , 0x39 , 0x50 , 0x32 , 0x30 , 0x30 , 0x30 ]
On Tue, Jun 2, 2009 at 1:31 PM, David Leimbach
wrote: On Tue, Jun 2, 2009 at 1:28 PM, John Van Enk
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 $
{size=s,
mtype=mt,
tag=t,
ssize=ss,
ename=e}
On Tue, Jun 2, 2009 at 4:20 PM, David Leimbach
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
wrote: Thomas,
You're correct. For some reason, I based my advice on the thought
19 was the minimum size instead of 13.
On Tue, Jun 2, 2009 at 1:24 PM, Thomas DuBuisson
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 Rerror that 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Jun 2, 2009 at 10:24 AM, Thomas DuBuisson < thomas.dubuisson@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.
I've shown that I am not trying to decode more than I'm providing. I've asked, expliciitly, for 13 bytes, and then "remaining", and the library is complaining about the 20th byte.
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.
The other branch is Rerror, which is a shorter message decode stream. Unfortunately, I can't get Debug.Trace to show anything to prove it's taking this fork of the code. I suppose I could unsafePerformIO :-) Perhaps I just need a new version of "binary"?? I'll give it a go and try your version. But I need to decode over a dozen message types, so I will need a case or guard or something. Dave
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

Perhaps there's some place in your code that's forcing the lazy read
to consume more. Perhaps you could replace it with an explict (and
strict) getBytes[1] in combination with remaining[2]?
Is there a reason you want to use lazy byte strings rather than
forcing full consumption? Do the 9P packets generally have a lot of
trailing useless data?
1. http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Bin...
2. http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Bin...
On Tue, Jun 2, 2009 at 4:28 PM, David Leimbach
On Tue, Jun 2, 2009 at 10:24 AM, Thomas DuBuisson
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.
I've shown that I am not trying to decode more than I'm providing. I've asked, expliciitly, for 13 bytes, and then "remaining", and the library is complaining about the 20th byte.
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.
The other branch is Rerror, which is a shorter message decode stream. Unfortunately, I can't get Debug.Trace to show anything to prove it's taking this fork of the code. I suppose I could unsafePerformIO :-) Perhaps I just need a new version of "binary"?? I'll give it a go and try your version. But I need to decode over a dozen message types, so I will need a case or guard or something. Dave
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

On Tue, Jun 2, 2009 at 1:32 PM, John Van Enk
Perhaps there's some place in your code that's forcing the lazy read to consume more. Perhaps you could replace it with an explict (and strict) getBytes[1] in combination with remaining[2]?
Unfortunately, I'm using a Lazy ByteString network IO lib. So I don't think going to a strict ByteString is going to be possible.
Is there a reason you want to use lazy byte strings rather than forcing full consumption? Do the 9P packets generally have a lot of trailing useless data?
Nope. Just I noticed that there was a Network ByteString package that utilized lazy bytestrings :-). Even if that's why it's going for a 20th byte, shouldn't that be a bug? :-)
1. http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Bin... 2. http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/Data-Bin...
On Tue, Jun 2, 2009 at 4:28 PM, David Leimbach
wrote: On Tue, Jun 2, 2009 at 10:24 AM, Thomas DuBuisson
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.
I've shown that I am not trying to decode more than I'm providing. I've asked, expliciitly, for 13 bytes, and then "remaining", and the library
complaining about the 20th byte.
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.
The other branch is Rerror, which is a shorter message decode stream. Unfortunately, I can't get Debug.Trace to show anything to prove it's taking this fork of the code. I suppose I could unsafePerformIO :-) Perhaps I just need a new version of "binary"?? I'll give it a go and
is try
your version. But I need to decode over a dozen message types, so I will need a case or guard or something. Dave
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
participants (3)
-
David Leimbach
-
John Van Enk
-
Thomas DuBuisson