
Hi, I've been trying to implement the RFB (VNC) protocol and I was exploring a neat way of parsing the protocol bytestream. The protocol specifies that the client first sends a byte that identifies the command then a sequence of word8, word16, word32 and paddings. I've tried to capture that logic with the function below. commandFormat :: Word8 -> [Int] -- 0 for padding bytes commandFormat c | c == setPixelFormat = [0,0,0,1,1,1,1,2,2,2,1,1,1,0,0,0] | c == setEncodings = [0,2] | c == framebufferUpdateRequest = [0,2,2,2,2] | c == keyEvent = [1,2,4] | c == pointerEvent = [1,2,2] | c == clientCutText = [0,0,0,4] | otherwise = [] What I am struggling with is a function like this - parseCommand :: Word8 -> ByteStream -> [Int] parseCommand command byteStream = ... I want the function to use the commandFormat above and return me a list of integers -- for example - if the command is keyEvent and the bytestream is "<1> <0> <2> <0> <0> <0> <3>" The output should be -> [1,2,3]!!! -> That way, I can process it easily. I'd appreciate some help on this very much. -- Regards, Kashyap

I'd use a parser combinator library that has word8 word16, word32 combinators. The latter should really have big and little endian versions word16be, word16le, word32be, word32le. Data.Binary should provide this and Attoparsec I think. Usually I roll my own, but only because I had my own libraries before these two existed. The idiom of a tag byte telling you what comes next is very common in binary formats. It means parsers can avoid backtracking altogether.

Thanks Stephen,
On Tue, Nov 9, 2010 at 2:53 PM, Stephen Tetley
I'd use a parser combinator library that has word8 word16, word32 combinators. The latter should really have big and little endian versions word16be, word16le, word32be, word32le.
Data.Binary should provide this and Attoparsec I think. Usually I roll my own, but only because I had my own libraries before these two existed.
The idiom of a tag byte telling you what comes next is very common in binary formats. It means parsers can avoid backtracking altogether.
I'll take a look at attoparsec I was also trying to understand how I could do it myself also - Basically I've been using the Get Monad for getting out the word/8/16 etc out of a ByteStream - but I dont want to write a separate parsing routine for each command. So instead of doing something like this - parseCommand1 byteStream = runGet $ do b1 <- getWord8 b2 <- getWord16be return (b1,b2) parseCommand2 byteStream = runGet $ do b1 <- getWord16be b2 <- getWord16be return (b1,b2) I'd like to do this parse byteStream command = runGet $ do map (commandFormat command) --- or something like this - not exactly sure about this. Regards, Kashyap

2010/11/9 C K Kashyap
Thanks Stephen,
On Tue, Nov 9, 2010 at 2:53 PM, Stephen Tetley
wrote: I'd use a parser combinator library that has word8 word16, word32 combinators. The latter should really have big and little endian versions word16be, word16le, word32be, word32le.
Data.Binary should provide this and Attoparsec I think. Usually I roll my own, but only because I had my own libraries before these two existed.
The idiom of a tag byte telling you what comes next is very common in binary formats. It means parsers can avoid backtracking altogether.
I'll take a look at attoparsec
I was also trying to understand how I could do it myself also -
Basically I've been using the Get Monad for getting out the word/8/16 etc out of a ByteStream - but I dont want to write a separate parsing routine for each command.
So instead of doing something like this -
parseCommand1 byteStream = runGet $ do b1 <- getWord8 b2 <- getWord16be return (b1,b2)
parseCommand2 byteStream = runGet $ do b1 <- getWord16be b2 <- getWord16be return (b1,b2)
I'd like to do this
parse byteStream command = runGet $ do map (commandFormat command) --- or something like this - not exactly sure about this.
Hi, This doesn't seem a good idea to me. In the first case, when you have parsed your data, you end up with very specific data structures that can be processed later as-is. In the second case, you end up with a list for every kind of data, so you're bound to "parse" that list again to know what you're dealing with. In the first case, parsing wrong data is the only way to fail and you produce solid data you can work with. In the second case, you have a very weak representation that will need more work afterward, and that work is very similar to the parsing you do in the first place. Cheers, Thu

I think I can restate my problem like this --- If I have a list of actions as follows - import Data.Word import Data.Binary.Get data MyAction = A1 (Get Word8) | A2 (Get Word16) a = A1 getWord8 b = A2 getWord16be listOfActions = [a,b,a] How can I execute the "listOfActions" inside of a Get Monad and get the output as a list?

2010/11/9 C K Kashyap
I think I can restate my problem like this ---
If I have a list of actions as follows -
import Data.Word import Data.Binary.Get
data MyAction = A1 (Get Word8) | A2 (Get Word16)
a = A1 getWord8 b = A2 getWord16be
listOfActions = [a,b,a]
How can I execute the "listOfActions" inside of a Get Monad and get the output as a list?
Since you want the result as a list, by somehow mapping over a list of action, and since lists are homogeneous in Haskell, you need each action to have the same result type. Something like: performAction :: MyAction -> Get Int performAction A1 = getWord8 >>= return . someHypotheticalWordToIntYouWouldLike Notice that I have rewritten your data MyAction = A1 (Get Word8) as simply data MyAction = A1 because it seems your A1 action will always be getWord8. Now, you don't need specifically a list of MyAction and map performAction on it: you can achieve the same thing with: sequence [getWord8 >>= return . someHypotheticalWordToIntYouWouldLike, ...] Cheers, Thu

On Tue, Nov 9, 2010 at 8:10 AM, C K Kashyap
import Control.Applicative ((<$>))
data MyAction m = A1 (m Word8) | A2 (m Word16)
a = A1 getWord8 b = A2 getWord16be
listOfActions = [a,b,a]
newtype Id a = Id a
getAction :: MyAction Get -> Get (MyAction Id) getAction (A1 act) = A1 . Id <$> act getAction (A2 act) = A2 . Id <$> act
getActions :: [MyAction Get] -> Get [MyAction Id] getActions = mapM getAction
-- Felipe.

Oops .. I made a mistake .. I had gone with Felipe's solution -
getActions :: [MyAction Get] -> Get [MyAction Id] getActions = mapM getAction
-- Felipe.
Felpe, could you please confirm if
bs = BS.pack [1,0,2,4]
toVal (A1 (Id v)) = fromIntegral v :: Int toVal (A2 (Id v)) = fromIntegral v :: Int
abc = map toVal $ runGet (getActions listOfActions) bs
is the right way of getting the values out? -- Regards, Kashyap

Hi Felipe,
On Tue, Nov 9, 2010 at 3:53 PM, Felipe Almeida Lessa
On Tue, Nov 9, 2010 at 8:10 AM, C K Kashyap
wrote: ] I think I can restate my problem like this --- ] ] If I have a list of actions as follows - ] ] import Data.Word ] import Data.Binary.Get ] ] data MyAction = A1 (Get Word8) | A2 (Get Word16) ] ] a = A1 getWord8 ] b = A2 getWord16be ] ] listOfActions = [a,b,a] ] ] How can I execute the "listOfActions" inside of a Get Monad and get ] the output as a list? Do you mean, something like this?
import Control.Applicative ((<$>))
data MyAction m = A1 (m Word8) | A2 (m Word16)
a = A1 getWord8 b = A2 getWord16be
listOfActions = [a,b,a]
newtype Id a = Id a
getAction :: MyAction Get -> Get (MyAction Id) getAction (A1 act) = A1 . Id <$> act getAction (A2 act) = A2 . Id <$> act
getActions :: [MyAction Get] -> Get [MyAction Id] getActions = mapM getAction
-- Felipe.
Could you please give a solution for Put as well ... I need to generate a series of put actions from a list of tuples as follows - [(100,1),(200,2),500,4)] -> [putWord8 100, putWord16be 200, putWord32be 500] -- Regards, Kashyap

If we change the code a bit, data MyAction = A1 Word8 | A2 Word16 a,b :: Get MyAction
a = A1 <$> getWord8
b = A2 <$> getWord16be
listOfActions :: [Get MyAction] listOfActions = [a,b,a] Now, we know how to execute the list of actions, and get the output as list. Using the following guys: sequence :: Monad m => [m a] -> m [a] runGet :: Get a -> ByteString -> a Best, Ozgur

2010/11/9 Ozgur Akgun
If we change the code a bit,
data MyAction = A1 Word8 | A2 Word16
a,b :: Get MyAction
a = A1 <$> getWord8
b = A2 <$> getWord16be
listOfActions :: [Get MyAction] listOfActions = [a,b,a] Now, we know how to execute the list of actions, and get the output as list. Using the following guys: sequence :: Monad m => [m a] -> m [a] runGet :: Get a -> ByteString -> a
The original question was (I believe) how to drive the parsing with a list of Actions, not the result be a list of Actions. Cheers, Thu

The original question was (I believe) how to drive the parsing with a list of Actions, not the result be a list of Actions.
Yes ... the result needs to be a list of plain values - Int's But I did not follow why you have dropped the word16 .... -- Regards, Kashyap

Thanks Ozgur and Felipe, Could you also show how I could actually use it to parse a bytestring please? import qualified Data.ByteString.Lazy as BS import Control.Applicative ((<$>)) import Data.Word import Data.Binary.Get data MyAction = A1 Word8 | A2 Word16 a,b :: Get MyAction a = A1 <$> getWord8 b = A2 <$> getWord16be listOfActions :: [Get MyAction] listOfActions = [a,b,a] --sequence :: Monad m => [m a] -> m [a] --runGet :: Get a -> ByteString -> a bs = BS.pack [1,0,2] How exactly can I get back a list of integers from bs? -- Regards, Kashyap

Okay, I think I got it .. I went with Ozgur's example - data MyAction m = A1 (m Word8) | A2 (m Word16) a = A1 getWord8 b = A2 getWord16be listOfActions = [a,b,a] newtype Id a = Id a getAction :: MyAction Get -> Get (MyAction Id) getAction (A1 act) = A1 . Id <$> act getAction (A2 act) = A2 . Id <$> act getActions :: [MyAction Get] -> Get [MyAction Id] getActions = mapM getAction bs = BS.pack [1,0,2,4] abc = map toVal $ runGet (getActions listOfActions) bs toVal (A1 (Id v)) = fromIntegral v :: Int toVal (A2 (Id v)) = fromIntegral v :: Int Kindly let me know if this is exactly how you intended it to be used? Regards, Kashyap
participants (5)
-
C K Kashyap
-
Felipe Almeida Lessa
-
Ozgur Akgun
-
Stephen Tetley
-
Vo Minh Thu