Re: [Haskell-cafe] Parsing binary data question

2011-09-28 Thread Eric Rasmussen
Hi Michael,

I recommend Attoparsec when parsing raw data into custom data types.
There aren't as many examples and tutorials as there are for Parsec,
but the API is very similar, and some of the important differences are
listed on Attoparsec's Hackage entry. There are also helpful examples
of its usage here:
https://bitbucket.org/bos/attoparsec/src/286c3d520c52/examples/

Take care,
Eric


On Tue, Sep 27, 2011 at 2:14 AM, Michael Oswald muell...@gmx.net wrote:
 Hello all,

 I am currently working on parser for some packets received via the network.
 The data structure currently is like that:


 data Value = ValUInt8 Int8
           | ValUInt16 Int16
           | ValUInt32 Int32
        -- more datatypes

 data Parameter = Parameter {
  paramName :: String,
  paramValue :: Value
  }
  | ParameterN {
  paramName :: String,
  paramValue :: Value
  }deriving (Show)

 data TCPacket = TCPacket {
  tcAPID :: Word16,
  tcType :: Word8,
  tcSubType :: Word8,
  tcParameters :: [Parameter]
  }

 The output should a parsed packet (I am using cereal for this). The packet
 structure can vary depending on the type and the configuration, so I have a
 function which takes a TCPacket as input template which has already the
 correct list of parameters which are then parsed:

 parseTCPacket :: Word16 - Word8 - Word8 - ByteString - TCPacket -
 TCPacket
 parseTCPacket apid t st pktData tmplate =
    TCPacket apid t st params
    where
        tmplParams = (tcParameters tmplate)
        params = zipWith (\p v - p {paramValue = v} ) tmplParams values'
        values = map paramValue tmplParams
        values' = binValues values (pktData pusPkt)

 getBinGet :: Value - Get Value
 getBinGet (ValInt8 _) = getWord8 = \x - return $ ValInt8 $ fromIntegral x
 getBinGet (ValInt16 _) = getWord16be = \x - return $ ValInt16 $
 fromIntegral x
 -- many more datatypes

 getBinValues :: [Value] - Get [Value]
 getBinValues inp = mapM getBinGet inp


 binValues :: [Value] - ByteString - ([Value], B.ByteString)
 binValues inp bytes = case runGet (getBinValues inp) bytes of
                        Left err - throw $ DecodeError (binValues:  ++
 err)
                        Right x - x


 This works quite well and does what I want. Now I have the problem that
 there are some parameters, which could be so-called group repeaters (the
 ParameterN constructor above). This means, that if such a parameter N is
 encountered during parsing (it has to be an int type), all following
 parameters are repeated N times with possible nesting.

 So for example if the template (where the values are all 0) is like this:
 [Parameter Param1 (ValUInt32 0), ParameterN N1 (ValUInt8 0), Parameter
 Param2 (ValUint16 0), ParameterN N2 (ValUint8 0),
 Parameter Param3 (ValUint8 0)]

 Which means there is a group for the last 3 parameters which is repeated N1
 times which contains another group which is repeated N2 times.
 If binary data based on the template above would be like this (datatypes
 omitted):

 10, 2, 439, 2, 12, 13, 65535, 2, 22, 23

 then a valid packet after parsing would be:

 [Parameter Param1 (ValUint32 10), ParameterN N1 (ValUint8 2), Parameter
 Param2 (ValUint16 439), ParameterN N2 (ValUint8 2),
 Parameter Param3 (ValUint8 12), Parameter Param3 (ValUint8 13),
 Parameter Param2 (ValUint16 65535), ParameterN N2 (ValUint8 2),
 Parameter Param3 (ValUint8 22), Parameter Param3 (ValUint8 23)]

 Now I am a bit lost on how to implement such a parser. It would be much
 easier if the structure would be already encoded in the binary data, but I
 have to stick to this template approach. I have some C++ parser which does
 this but of course it's very imperative and a little bit quirky implemented,
 so if anybody has an idea on how to proceed (cereal, attoparsec whatever),
 please tell me.


 lg,
 Michael




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


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


Re: [Haskell-cafe] Parsing binary data.

2007-08-22 Thread Lutz Donnerhacke
* Tony Finch wrote:
 http://erlang.org/doc/programming_examples/bit_syntax.html#4
 The IP header example in the latter is a brilliant real-world example.

Unfortunly this example does not handle bit and byte order.
Take a look at Ada's representation clauses for such topics.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsing binary data.

2007-08-22 Thread Tony Finch
On Wed, 22 Aug 2007, Lutz Donnerhacke wrote:
 * Tony Finch wrote:
  http://erlang.org/doc/programming_examples/bit_syntax.html#4
  The IP header example in the latter is a brilliant real-world example.

 Unfortunly this example does not handle bit and byte order.
 Take a look at Ada's representation clauses for such topics.

Erlang has support for byte endianness but not (it seems) bit endianness.
I'm currently kicking up a fuss about this on the erlang-questions list,
since while Erlang's bitwise big-endian layout works OK for network
protocols, it fails for typical little-endian C structures with bit
fields.

Thanks for the pointer to Ada.

Tony.
-- 
f.a.n.finch  [EMAIL PROTECTED]  http://dotat.at/
IRISH SEA: SOUTHERLY, BACKING NORTHEASTERLY FOR A TIME, 3 OR 4. SLIGHT OR
MODERATE. SHOWERS. MODERATE OR GOOD, OCCASIONALLY POOR.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsing binary data.

2007-08-21 Thread Tony Finch
On Sun, 19 Aug 2007, Peter Cai wrote:

 My duty is writing a network server which talks to another server through a
 binary based private protocol.

Haskell needs something like Erlang's bit syntax.

http://erlang.org/doc/reference_manual/expressions.html#6.16
http://erlang.org/doc/programming_examples/bit_syntax.html#4
The IP header example in the latter is a brilliant real-world example.

It has recently been upgraded to support arbitrary bit streams.
See http://www.it.uu.se/research/group/hipe/papers/padl07.pdf

Tony.
-- 
f.a.n.finch  [EMAIL PROTECTED]  http://dotat.at/
IRISH SEA: SOUTHERLY, BACKING NORTHEASTERLY FOR A TIME, 3 OR 4. SLIGHT OR
MODERATE. SHOWERS. MODERATE OR GOOD, OCCASIONALLY POOR.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsing binary data.

2007-08-21 Thread Donald Bruce Stewart
dot:
 On Sun, 19 Aug 2007, Peter Cai wrote:
 
  My duty is writing a network server which talks to another server through a
  binary based private protocol.
 
 Haskell needs something like Erlang's bit syntax.
 
 http://erlang.org/doc/reference_manual/expressions.html#6.16
 http://erlang.org/doc/programming_examples/bit_syntax.html#4
 The IP header example in the latter is a brilliant real-world example.
 
 It has recently been upgraded to support arbitrary bit streams.
 See http://www.it.uu.se/research/group/hipe/papers/padl07.pdf
 

Yes, we've looked at this in the context of Data.Binary. Rather than
extending the core syntax, on option is to use Template Haskell,

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/BitSyntax-0.3

Another is to just use monad and pattern guards, which give quite
reasonable syntax.

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


Re: [Haskell-cafe] Parsing binary data.

2007-08-20 Thread Adam Langley
On 8/19/07, Matthew Sackman [EMAIL PROTECTED] wrote:
 But it's vastly harder to do that for floats / non-integers. Now I know
 that the number classes in the Prelude are basically broken anyway and
 all really need rewriting, but it does seem completely arbitrary that
 Words somehow are only allowed to contain whole numbers!

Well, see the attached patch to Data.Binary to add
putFloat[32|64][be|le]. I got bored, so adding the Get functions is an
exercise for the reader :)

(And so because I think it needs unsafeSomethingIO and I'm a little
unsure about that).

If these functions would be useful for you, you should bug the binary
team to add something similar.


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641


data-binary-float.darcs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsing binary data.

2007-08-19 Thread Adam Langley
On 8/18/07, Matthew Sackman [EMAIL PROTECTED] wrote:
 Also, one thing to watch out for is the fact the existing Get and Put
 instances may not do anything like what you expect. For example, for
 some reason I expected that the instances of Get and Put for Float and
 Double would send across the wire Floats and Doubles in IEEE floating
 point standard. How wrong I was...

Ah, those aren't instances of Get and Put, but of Binary[1]. You use
the Binary instances via the functions 'get' and 'put' (case is
important).

Get and Put provide actions like putWord32be, for which the
resulting bits are pretty much universally accepted. Binary has
default instances which uses Get and Put to serialise Haskell types
like [Int], or (Float, Float). Here the resulting bits aren't
documented, but you can read the code and I have some C code for
dealing with them somewhere if anyone is interrested. The
serialisation of Float is, indeed, nothing like IEEE in either
endianness.

(* and, although Get isn't currently a class, I have sent patches to
dons to make it so, with a default instance which matches current
behaviour and speed, and an alternative which returns a Maybe,
removing a little bit of lazyness in cases where you want to handle
parse failures in pure code. Hopefully something will happen with this
at the next sprint ;) )

[1] http://www.cse.unsw.edu.au/~dons/binary/Data-Binary.html#1

-- 
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] Parsing binary data.

2007-08-18 Thread Marc Weber
As I am a newbie to Haskell, I am not sure how to handle this problem
with less work.  Do you have any ideas about this problem?
Thanks in advance!

Have a look at 
http://haskell.org/haskellwiki/Applications_and_libraries/Data_structures
section 3 (IO) - http://haskell.org/haskellwiki/Binary_IO

Of course you can just use most different parser libraries as well, because most
are not tight to one token type.. So you shouldn't have any trouble
parsing a ByeSttring which is a char (8bit word) buffer.

I'd recommend having a look at ParseP or happy/ alex .. if the binary
libraries aren't suited for your task..

But to get the fastest/ whatsoever solution you should wait for
different replies as I haven't used all those yet to parse binary data..

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