doubts about runGetState in the binary package

Hi. I have some doubts about the runGetState function in the binary package. The signature is: runGetState :: Get a -> LBS -> Int64 -> (a, LBS, Int64) however the Int64 "input parameter" is not documented. What value should I pass? How will be used? Thanks Manlio Perillo

Manlio Perillo wrote:
Hi.
I have some doubts about the runGetState function in the binary package. The signature is: runGetState :: Get a -> LBS -> Int64 -> (a, LBS, Int64)
however the Int64 "input parameter" is not documented. What value should I pass? How will be used?
Thanks Manlio Perillo
hackage has the code at http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/src/Data... And I have pieced together an answer at the bottom...
-- | The parse state data S = S {-# UNPACK #-} !B.ByteString -- current chunk L.ByteString -- the rest of the input {-# UNPACK #-} !Int64 -- bytes read
-- | The Get monad is just a State monad carrying around the input ByteString -- We treat it as a strict state monad. newtype Get a = Get { unGet :: S -> (a, S) }
mkState :: L.ByteString -> Int64 -> S mkState l = case l of L.Empty -> S B.empty L.empty L.Chunk x xs -> S x xs
-- | Run the Get monad applies a 'get'-based parser on the input -- ByteString. Additional to the result of get it returns the number of -- consumed bytes and the rest of the input. runGetState :: Get a -> L.ByteString -> Int64 -> (a, L.ByteString, Int64) runGetState m str off = case unGet m (mkState str off) of (a, ~(S s ss newOff)) -> (a, s `join` ss, newOff)
getBytes :: Int -> Get B.ByteString getBytes n = do S s ss bytes <- get if n <= B.length s then do let (consume,rest) = B.splitAt n s put $! S rest ss (bytes + fromIntegral n) return $! consume else ...
The Int64 passed to runGetState just initializes the running total of consumed bytes. The updated total is returned by runGetState. The absolute value of the Int64 is never used; it is only increased by "getBytes". Cheers, Chris

ChrisK ha scritto:
Manlio Perillo wrote:
Hi.
I have some doubts about the runGetState function in the binary package. The signature is: runGetState :: Get a -> LBS -> Int64 -> (a, LBS, Int64)
however the Int64 "input parameter" is not documented. What value should I pass? How will be used?
[...]
hackage has the code at http://hackage.haskell.org/packages/archive/binary/0.5.0.1/doc/html/src/Data...
Yes, and I have read the code, as the first thing. And (after some testing) I figured out how it works. However I wanted to be sure I understand it, since, as I have written, IMHO it is not clearly documented; and I can't see how it can be useful, there are no usage examples.
[...]
Thanks Manlio Perillo
participants (2)
-
ChrisK
-
Manlio Perillo