[Haskell-cafe] Bencoding in Haskell
Sebastian Sylvan
sebastian.sylvan at gmail.com
Wed Apr 20 13:04:44 EDT 2005
Yeah, you probably want the main parser to be "many beParser" and not
just beParser:
-- main parser function
parseBencoded :: String -> Maybe [Bencode]
parseBencode str = case parse (many beParse) "" str of
Left err -> Nothing
Right val -> Just val
On 4/20/05, Sebastian Sylvan <sebastian.sylvan at gmail.com> wrote:
> On 4/20/05, Tommi Airikka <haskell-cafe at airikka.net> wrote:
> > Hi!
> >
> > I was just wondering if there are any good ways to represent a bencoded
> > (http://en.wikipedia.org/wiki/Bencoding) message in Haskell? Any
> > suggestions?
> >
>
> Not that I know of, but it should be very easy to write a parser using
> the parser library Parsec.
>
> You'll need a datatype, something like this:
>
> data Bencode = BEInteger Integer |
> BEString String |
> BEList [Bencode] |
> BEDictionary (Data.Map String Bencode)
> deriving (Show, Eq)
>
> Which should be sufficient to represent any Bencoded message (if I
> didn't make a misstake).
> Then you could probably use the standard char-parser in parsec to
> parse it quite easily. Read the docs, they're quite straightforward.
>
> I'm a bit rusty but something like this:
>
> -- just parse an integer, parsec might have one of these already
> number :: Parser Integer
> number =
> do n_str <- many1 digit -- parse a number
> let n = read n_str -- convert to an Int
> return n -- return the number
>
> beString :: Parser Bencode
> beString =
> do n <- number -- the length prefix
> char ':' -- now a ':'
> str <- count n anyChar -- and now n number of letters
> return (BEString str) -- return the string wrapped up as a
> BEString
>
> beInt :: Parser Bencode
> beInt =
> do char 'i'
> n <- number
> char 'e'
> return n
>
> -- parse any Bencoded value
> beParse :: Parser Bencode
> beParse =
> do beInt <|> beString <|> beDictionary <|> beList
>
> beList :: Parser Bencode
> beList =
> do char 'l'
> xs <- many beParse -- parse many bencoded values
> char 'e'
> return (BEList xs)
>
> beDictionary :: Parser Bencode
> beDictionary =
> do char 'd'
> key <- beString
> val <- beParse
> m <- beDictionary <|> char 'e' >> return Data.Map.empty
> return (Data.Map.insert key val m)
>
> -- main parser function
> parseBencoded :: String -> Maybe Bencode
> parseBencode str = case parse beParse "" str of
> Left err -> Nothing
> Right val -> Just val
>
> Note: This is all untested code that I just scribbled down real quick.
> There's probably tons of misstakes, but you should get the picture.
> Read the Parsec docs and then write your own.
>
> /S
> --
> Sebastian Sylvan
> +46(0)736-818655
> UIN: 44640862
>
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
More information about the Haskell-Cafe
mailing list