Skip to content

Instantly share code, notes, and snippets.

@rgrinberg
Created October 3, 2013 22:09
Show Gist options
  • Save rgrinberg/6817900 to your computer and use it in GitHub Desktop.
Save rgrinberg/6817900 to your computer and use it in GitHub Desktop.
bencode parser in attoparsec
module Bencode where
import Data.Maybe (fromJust)
import Control.Monad (liftM)
import Control.Applicative
import Data.ByteString.Char8 as BS
import Data.Attoparsec.ByteString.Char8 as A hiding (string)
import qualified Text.Show.Pretty as Pr
data Bencode = String ByteString
| Int Int
| List [Bencode]
| Dict [(ByteString, Bencode)] deriving (Show, Eq)
digits :: Parser Int
digits = do
digits' <- takeWhile1 isDigit
(return . fst . fromJust . readInt) digits'
string :: Parser ByteString
string = do
length' <- digits
char ':'
A.take length'
integer :: Parser Int
integer = do -- no float support
char 'i'
i <- digits
char 'e'
return i
list :: Parser [Bencode]
list = do
char 'l'
elements <- many' bencode
char 'e'
return elements
pair :: Parser (ByteString, Bencode)
pair = do
key <- string
val <- bencode
return (key, val)
dict :: Parser [(ByteString, Bencode)]
dict = do
char 'd'
dict' <- many' pair
char 'e'
return dict'
bencode :: Parser Bencode
bencode = String `liftM` string
<|> Int `liftM` integer
<|> List `liftM` list
<|> Dict `liftM` dict
prettyPrint :: Bencode -> ByteString
prettyPrint = BS.pack .Pr.ppShow
main :: IO ()
main = BS.interact (prettyPrint . fromRight . (parseOnly bencode))
where fromRight (Right x) = x
fromRight (Left _) = undefined
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment