bencoding-0.2.1.0: A library for encoding and decoding of BEncode data.

Portabilityportable
Stabilitystable
Maintainerpxqr.sta@gmail.com
Safe HaskellTrustworthy

Data.BEncode

Contents

Description

This module provides convinient and fast way to serialize, deserealize and construct/destructure Bencoded values with optional fields.

It supports four different types of values:

  • byte strings — represented as ByteString;
  • integers — represented as Integer;
  • lists - represented as ordinary lists;
  • dictionaries — represented as Map;

To serialize any other types we need to make conversion. To make conversion more convenient there is type class for it: BEncodable. Any textual strings are considered as UTF8 encoded Text.

The complete Augmented BNF syntax for bencoding format is:

 <BE>    ::= <DICT> | <LIST> | <INT> | <STR>

 <DICT>  ::= "d" 1 * (<STR> <BE>) "e"
 <LIST>  ::= "l" 1 * <BE>         "e"
 <INT>   ::= "i"     <SNUM>       "e"
 <STR>   ::= <NUM> ":" n * <CHAR>; where n equals the <NUM>

 <SNUM>  ::= "-" <NUM> / <NUM>
 <NUM>   ::= 1 * <DIGIT>
 <CHAR>  ::= %
 <DIGIT> ::= "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" | "8" | "9"

This module is considered to be imported qualified.

Synopsis

Datatype

data BEncode Source

BEncode is straightforward ADT for b-encoded values. Please note that since dictionaries are sorted, in most cases we can compare BEncoded values without serialization and vice versa. Lists is not required to be sorted through.

Constructors

BInteger !BInteger

bencode integers;

BString !BString

bencode strings;

BList BList

list of bencode values;

BDict BDict

bencode key-value dictionary.

ppBEncode :: BEncode -> DocSource

Convert to easily readable JSON-like document. Typically used for debugging purposes.

Conversion

class BEncodable a whereSource

This class is used to define new datatypes that could be easily serialized using bencode format.

By default BEncodable have a generic implementation; suppose the following datatype:

 data List a = Cons { _head  :: a
                    , __tail :: (List a) }
             | Nil
               deriving Generic

If we don't need to obey any particular specification or standard, the default instance could be derived automatically from the Generic instance:

 instance BEncodable a => BEncodable (List a)

Example of derived toBEncode result:

 > toBEncode (Cons 123 $ Cons 1 Nil)
 BDict (fromList [("head",BInteger 123),("tail",BList [])])

Note that '_' prefixes are omitted.

Methods

toBEncode :: a -> BEncodeSource

See an example of implementation here Assoc

fromBEncode :: BEncode -> Result aSource

See an example of implementation here reqKey.

type Result = Either StringSource

Result used in decoding operations.

Serialization

encode :: BEncode -> ByteStringSource

Convert bencoded value to raw bytestring according to the specification.

decode :: ByteString -> Result BEncodeSource

Try to convert raw bytestring to bencoded value according to specification.

encoded :: BEncodable a => a -> ByteStringSource

The same as encode but takes any bencodable value.

decoded :: BEncodable a => ByteString -> Result aSource

The same as decode but returns any bencodable value.

Dictionaries

Building

data Assoc Source

Assoc used to easily build dictionaries with required and optional keys. Suppose we have we following datatype we want to serialize:

 data FileInfo = FileInfo
   { fileLength :: Integer
   , fileMD5sum :: Maybe ByteString
   , filePath   :: [ByteString]
   , fileTags   :: Maybe [Text]
   } deriving (Show, Read, Eq)

We need to make instance BEncodable FileInfo, though we don't want to check the both maybes manually. The more declarative and convenient way to define the toBEncode method is to use dictionary builders:

 instance BEncodable FileInfo where
   toBEncode FileInfo {..} = fromAssocs
     [ "length" -->  fileLength
     , "md5sum" -->? fileMD5sum
     , "path"   -->  filePath
     , "tags"   -->? fileTags
     ]
     ...

(-->) :: BEncodable a => ByteString -> a -> AssocSource

Make required key value pair.

(-->?) :: BEncodable a => ByteString -> Maybe a -> AssocSource

Like (-->) but if the value is not present then the key do not appear in resulting bencoded dictionary.

fromAssocs :: [Assoc] -> BEncodeSource

Build BEncode dictionary using key -> value description.

fromAscAssocs :: [Assoc] -> BEncodeSource

A faster version of fromAssocs. Should be used only when keys in builder list are sorted by ascending.

Extraction

decodingError :: String -> Result aSource

Typically used to throw an decoding error in fromBEncode; when BEncode value to match expected value.

reqKey :: BEncodable a => BDict -> BKey -> Result aSource

Dictionary extractor are similar to dictionary builders, but play the opposite role: they are used to define fromBEncode method in declarative style. Using the same FileInfo datatype fromBEncode looks like:

 instance BEncodable FileInfo where
   ...
   fromBEncode (BDict d) =
     FileInfo <$> d >--  "length"
              <*> d >--? "md5sum"
              <*> d >--  "path"
              <*> d >--? "tags"
   fromBEncode _ = decodingError "FileInfo"

The reqKey is used to extract required key — if lookup is failed then whole destructuring fail.

optKey :: BEncodable a => BDict -> BKey -> Result (Maybe a)Source

Used to extract optional key — if lookup is failed returns Nothing.

(>--) :: BEncodable a => BDict -> BKey -> Result aSource

Infix version of the reqKey.

(>--?) :: BEncodable a => BDict -> BKey -> Result (Maybe a)Source

Infix version of the optKey.

Predicates

isInteger :: BEncode -> BoolSource

Test if bencoded value is an integer.

isString :: BEncode -> BoolSource

Test if bencoded value is a string, both raw and utf8 encoded.

isList :: BEncode -> BoolSource

Test if bencoded value is a list.

isDict :: BEncode -> BoolSource

Test if bencoded value is a dictionary.

Extra

builder :: BEncode -> BuilderSource

BEncode format encoder according to specification.

parser :: Parser BEncodeSource

BEncode format parser according to specification.