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

Data.Bencode.Decode

Description

Conversions from Bencoded ByteStrings to Haskell values.

Synopsis

Quick start

Decoding is done using parsers. This module defines parsers that can be composed to build 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 the 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.

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. The message is a short human-readable error description and should not be relied on programmatically.

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

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

String parsers

string :: Parser ByteString Source #

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

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.

Integer parsers

integer :: Parser Integer Source #

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

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.

int64 :: Parser Int64 Source #

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

Since: 0.1.1.0

int32 :: Parser Int32 Source #

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

Since: 0.1.1.0

int16 :: Parser Int16 Source #

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

Since: 0.1.1.0

int8 :: Parser Int8 Source #

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

Since: 0.1.1.0

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.

word64 :: Parser Word64 Source #

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

Since: 0.1.1.0

word32 :: Parser Word32 Source #

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

Since: 0.1.1.0

word16 :: Parser Word16 Source #

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

Since: 0.1.1.0

word8 :: Parser Word8 Source #

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

Since: 0.1.1.0

List parsers

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.

index :: Int -> Parser a -> Parser a Source #

Decode a list element with the given parser at the given (0-based) index. Fails on a non-list, if the index is out of bounds, or if the element parser fails.

Also see elem and list'.

Examples

Expand
data File = File { name :: Text, size :: Int }

fileParser :: D.Parser File
fileParser =
  File <$> D.index 0 D.text
       <*> D.index 1 D.int

Since: 0.1.1.0

elem :: Parser a -> Elems a Source #

Decode the next list element with the given parser. Convert to a Parser with list'.

Since: 0.1.1.0

list' :: Elems a -> Parser a Source #

Create a Parser from an Elems. Fails on a non-list, if the number of elements does not match the Elems exactly, or if any element parser fails.

Examples

Expand
data File = File { name :: Text, size :: Int }

fileParser :: D.Parser File
fileParser = D.list' $
  File <$> D.elem D.text
       <*> D.elem D.int

Since: 0.1.1.0

data Elems a Source #

List elements parser. See elem and list'.

Instances

Instances details
Alternative Elems Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

empty :: Elems a #

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

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

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

Applicative Elems Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

pure :: a -> Elems a #

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

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

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

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

Functor Elems Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

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

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

Monad Elems Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

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

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

return :: a -> Elems a #

Dictionary parsers

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.

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.

If keys should not be left over in the dict, use field' and dict' instead.

Examples

Expand
data File = File { name :: Text, size :: Int }

fileParser :: D.Parser File
fileParser =
  File <$> D.field "name" D.text
       <*> D.field "size" D.int

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

Decode a value with the given parser for the given key. Convert to a Parser with dict'.

Since: 0.1.1.0

dict' :: Fields a -> Parser a Source #

Create a Parser from a Fields. Fails on a non-dict, if a key is absent, or if any value fails to parse. Also fails if there are leftover unparsed keys in the dict.

If leftover keys should be ignored, use field instead.

Examples

Expand
data File = File { name :: Text, size :: Int }

fileParser :: D.Parser File
fileParser = D.dict' $
  File <$> D.field' "name" D.text
       <*> D.field' "size" D.int

Since: 0.1.1.0

data Fields a Source #

Key-value parsers. See dict' and field'.

Instances

Instances details
Alternative Fields Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

empty :: Fields a #

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

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

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

Applicative Fields Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

pure :: a -> Fields a #

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

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

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

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

Functor Fields Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

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

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

Monad Fields Source # 
Instance details

Defined in Data.Bencode.Decode

Methods

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

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

return :: a -> Fields a #

Miscellaneous

value :: Parser Value Source #

Decode a Value. Always succeeds for valid Bencode.

fail :: String -> Parser a Source #

Always fails with the given message.

mapMaybe :: (a -> Maybe b) -> Parser a -> Parser b Source #

Run the function on the parsed value, fail with empty if the result is Nothing.

Since: 0.1.1.0

mapOrFail :: (a -> Either String b) -> Parser a -> Parser b Source #

Run the function on the parsed value, fail with fail if the result is a Left.

Since: 0.1.1.0

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 a dict, failing on leftover keys

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

fileParser :: D.Parser File
fileParser = D.dict' $
  File
    <$> D.field' "name" D.text
    <*> D.field' "size" D.int
>>> D.decode fileParser "d4:name9:hello.txt4:sizei32ee"
Right (File {name = "hello.txt", size = 32})
>>> D.decode fileParser "d6:hiddeni1e4:name9:hello.txt4:sizei32ee"
Left "UnrecognizedKey \"hidden\""

Decode differently based on dict contents

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

responseParser :: D.Parser Response
responseParser = do
  id_ <- D.field "id" D.int
  status <- D.field "status" D.string
  case status of
    "failure" -> do
      reason <- D.field "reason" D.text
      pure $ Response id_ (Left reason)
    "success" -> do
      data_ <- D.field "data" D.string
      pure $ Response id_ (Right data_)
    _ -> D.fail "unknown status"
>>> 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})

Decode a heterogeneous list

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

fileParser :: D.Parser File
fileParser = D.list' $
  File
    <$> D.elem D.text
    <*> D.elem D.int
>>> D.decode fileParser "l9:hello.txti32ee"
Right (File {name = "hello.txt", size = 32})