beDictionary is wrong, though. It will only find dictionaries with a single entry.
This next parser should do the trick (again, untested!). It basically reads a "d" and then a list of (key,value) pairs (which is now a separate parser) and then an "e", and then it returns a "Map String Bencode". Should be something like this -- parses an association list of the contents -- of a dictionary beDicContents :: Parser (String, Bencode) beDicContents = do (BEString key) <- beString val <- beParse return (String, Bencode) beDictionary :: Parser Bencode beDictionary = do char 'd' xs <- many beDicContents char 'e' return (BEDictionary (Map.fromAscList xs)) On 4/20/05, Tommi Airikka <[EMAIL PROTECTED]> wrote: > Thank you very much! I really appreciate your help! > I have to read a little bit more about Parsec to fully understand what > your code does, but it seems to be what I was looking for. > > Regards, > Tommi > > On Wed, Apr 20, 2005 at 08:58:41PM +0200, Sebastian Sylvan wrote: > > I was bored so I ran it through ghci and fixed the small errors I > > found, here's the "working" version, I don't really have much of test > > data to play with, but it seems to be working with the small examples > > I copy-n-pasted from the wiki and the bittorrent website: > > > > import qualified Data.Map as Map > > import Data.Map(Map) > > import Text.ParserCombinators.Parsec > > > > data Bencode = BEInteger Integer > > | BEString String > > | BEList [Bencode] > > | BEDictionary (Map String Bencode) > > deriving (Show, Eq) > > > > number :: Parser Integer > > number = > > do n_str <- many1 digit > > let n = read n_str > > return n > > > > beString :: Parser Bencode > > beString = > > do n <- number > > char ':' > > str <- count (fromInteger n) anyChar > > return (BEString str) > > > > > > beInt :: Parser Bencode > > beInt = > > do char 'i' > > n <- number > > char 'e' > > return (BEInteger n) > > > > -- parse any Bencoded value > > beParse :: Parser Bencode > > beParse = 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' > > (BEString key) <- beString > > val <- beParse > > (BEDictionary m) <- beDictionary > > <|> do char 'e' > > return (BEDictionary Map.empty) > > > > return (BEDictionary (Map.insert key val m)) > > > > -- main parser function > > parseBencoded :: String -> Maybe [Bencode] > > parseBencoded str = case parse (many beParse) "" str of > > Left err -> Nothing > > Right val -> Just val > > > > > > > > /S > > > > On 4/20/05, Sebastian Sylvan <[EMAIL PROTECTED]> wrote: > > > 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 <[EMAIL PROTECTED]> wrote: > > > > On 4/20/05, Tommi Airikka <[EMAIL PROTECTED]> 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 > > > > > > > > > -- > > Sebastian Sylvan > > +46(0)736-818655 > > UIN: 44640862 > > > -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe