benc-0.1.0.0: Bencode encoding and decoding library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Bencode.Decode

Description

Conversions from Bencoded ByteStrings to Haskell values.

Introduction

Decoding is done using parsers. There are parsers for the four Bencode types:

These can be used to build more complex parsers for arbitrary types.

data File = File
  { hash :: ByteString
  , size :: Integer
  , tags :: Vector Text
  } deriving Show

Assuming a File is encoded as a Bencode dictionary with the field names as keys and appropriate value types, a parser for File can be defined as

{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Bencode.Decode as D

fileParser :: D.Parser File
fileParser =
  File <$> D.field "hash" D.string
       <*> D.field "size" D.integer
       <*> D.field "tags" (D.list D.text)

The parser can then be run on a ByteString with decode.

>>> D.decode fileParser "d4:hash4:xxxx4:sizei1024e4:tagsl4:work6:backupee"
Right (File {hash = "xxxx", size = 1024, tags = ["work","backup"]})

Of course, invalid Bencode or Bencode that does not satisfy our File parser will fail to decode.

>>> D.decode fileParser "d4:hash4:xxxx4:tagsl4:work6:backupee"
Left "KeyNotFound \"size\""

For more examples, see the "Recipes" section at the end of this page.

Synopsis

Parser

data Parser a Source #

A parser from a Bencode value to a Haskell value.

Instances

Instances details
Alternative Parser Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

Applicative Parser Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Functor Parser Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Monad Parser Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

decode :: Parser a -> ByteString -> Either String a Source #

Decode a value from the given ByteString. If decoding fails, returns Left with a failure message.

decodeMaybe :: Parser a -> ByteString -> Maybe a Source #

Decode a value from the given ByteString. If decoding fails, returns Nothing.

Primary parsers

string :: Parser ByteString Source #

Decode a Bencode string as a ByteString. Fails on a non-string.

integer :: Parser Integer Source #

Decode a Bencode integer as an Integer. Fails on a non-integer.

list :: Parser a -> Parser (Vector a) Source #

Decode a Bencode list with the given parser for elements. Fails on a non-list or if any element in the list fails to parse.

dict :: Parser a -> Parser (Map ByteString a) Source #

Decode a Bencode dict with the given parser for values. Fails on a non-dict or if any value in the dict fails to parse.

More parsers

stringEq :: ByteString -> Parser () Source #

Succeeds only on a Bencode string that equals the given string.

text :: Parser Text Source #

Decode a bencode string as UTF-8 text. Fails on a non-string or if the string is not valid UTF-8.

textEq :: Text -> Parser () Source #

Succeeds only on a Bencode string that equals the given text.

int :: Parser Int Source #

Decode a Bencode integer as an Int. Fails on a non-integer or if the integer is out of bounds for an Int.

intEq :: Int -> Parser () Source #

Succeeds only on a Bencode integer that equals the given value.

word :: Parser Word Source #

Decode a Bencode integer as a Word. Fails on a non-integer or if the integer is out of bounds for a Word.

field :: ByteString -> Parser a -> Parser a Source #

Decode a value with the given parser for the given key. Fails on a non-dict, if the key is absent, or if the value parser fails.

value :: Parser Value Source #

Decode a Value. Always succeeds for valid Bencode.

fail :: String -> Parser a Source #

Always fails with the given message.

Recipes

Recipes for some common and uncommon usages.

The following preface is assumed.

{-# LANGUAGE OverloadedStrings #-}
import Data.ByteString (ByteString)
import Data.Text (Text)
import qualified Data.Bencode.Decode as D

Decode an optional field

import Control.Applicative (optional)

data File = File { name :: Text, size :: Maybe Int } deriving Show

fileParser :: D.Parser File
fileParser =
  File
    <$> D.field "name" D.text
    <*> optional (D.field "size" D.int)
>>> D.decode fileParser "d4:name9:hello.txt4:sizei16ee"
Right (File {name = "hello.txt", size = Just 16})
>>> D.decode fileParser "d4:name9:hello.txte"
Right (File {name = "hello.txt", size = Nothing})

Decode an enum

import Control.Applicative ((<|>))

data Color = Red | Green | Blue deriving Show

colorParser :: D.Parser Color
colorParser =
      Red   <$ D.stringEq "red"
  <|> Green <$ D.stringEq "green"
  <|> Blue  <$ D.stringEq "blue"
  <|> D.fail "unknown color"
>>> D.decode colorParser "5:green"
Right Green
>>> D.decode colorParser "5:black"
Left "Fail: unknown color"

Decode differently based on dict contents

import Control.Applicative ((<|>))

data Response = Response
  { id_    :: Int
  , result :: Either Text ByteString
  } deriving Show

responseParser :: D.Parser Response
responseParser = do
  id_ <- D.field "id" D.int
  success <- D.field "status" $
        False <$ D.stringEq "failure"
    <|> True  <$ D.stringEq "success"
    <|> D.fail "unknown status"
  Response id_
    <$> if success
        then Right <$> D.field "data" D.string
        else Left  <$> D.field "reason" D.text
>>> D.decode responseParser "d2:idi42e6:reason12:unauthorized6:status7:failuree"
Right (Response {id_ = 42, result = Left "unauthorized"})
>>> D.decode responseParser "d4:data4:00002:idi42e6:status7:successe"
Right (Response {id_ = 42, result = Right "0000"})

Decode nested dicts

data File = File { name :: Text, size :: Int } deriving Show

fileParser :: D.Parser File
fileParser =
  File
    <$> D.field "name" D.text
    <*> D.field "metadata" (D.field "info" (D.field "size" D.int))
>>> D.decode fileParser "d8:metadatad4:infod4:sizei32eee4:name9:hello.txte"
Right (File {name = "hello.txt", size = 32})