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

Copyright(c) Sam Truzjan 2013
LicenseBSD3
Maintainerpxqr.sta@gmail.com
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

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 BDictMap;

To serialize any other types we need to make conversion. To make conversion more convenient there is type class for it: BEncode. 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, for example:

import Data.BEncode as BE
Synopsis

Documentation

data BValue Source #

BValue 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.

Instances
Eq BValue Source # 
Instance details

Defined in Data.BEncode.Types

Methods

(==) :: BValue -> BValue -> Bool #

(/=) :: BValue -> BValue -> Bool #

Ord BValue Source # 
Instance details

Defined in Data.BEncode.Types

Read BValue Source # 
Instance details

Defined in Data.BEncode.Types

Show BValue Source # 
Instance details

Defined in Data.BEncode.Types

Generic BValue Source # 
Instance details

Defined in Data.BEncode.Types

Associated Types

type Rep BValue :: Type -> Type #

Methods

from :: BValue -> Rep BValue x #

to :: Rep BValue x -> BValue #

NFData BValue Source # 
Instance details

Defined in Data.BEncode.Types

Methods

rnf :: BValue -> () #

BEncode BValue Source # 
Instance details

Defined in Data.BEncode

BEncode BDict Source # 
Instance details

Defined in Data.BEncode

type Rep BValue Source # 
Instance details

Defined in Data.BEncode.Types

class BEncode a where Source #

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

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

data List a = C { _head  :: a
                , __tail :: List a }
            | N
              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 BEncode a => BEncode (List a)

Example of derived toBEncode result:

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

Note that prefixed underscore characters are omitted since they are usually used for lens.

Minimal complete definition

Nothing

Methods

toBEncode :: a -> BValue Source #

See an example of implementation here Assoc

toBEncode :: Generic a => GBEncodable (Rep a) BValue => a -> BValue Source #

See an example of implementation here Assoc

fromBEncode :: BValue -> Result a Source #

See an example of implementation here Get.

fromBEncode :: Generic a => GBEncodable (Rep a) BValue => BValue -> Result a Source #

See an example of implementation here Get.

Instances
BEncode Bool Source # 
Instance details

Defined in Data.BEncode

BEncode Int Source # 
Instance details

Defined in Data.BEncode

BEncode Int8 Source # 
Instance details

Defined in Data.BEncode

BEncode Int16 Source # 
Instance details

Defined in Data.BEncode

BEncode Int32 Source # 
Instance details

Defined in Data.BEncode

BEncode Int64 Source # 
Instance details

Defined in Data.BEncode

BEncode Word Source # 
Instance details

Defined in Data.BEncode

BEncode Word8 Source # 
Instance details

Defined in Data.BEncode

BEncode Word16 Source # 
Instance details

Defined in Data.BEncode

BEncode Word32 Source # 
Instance details

Defined in Data.BEncode

BEncode Word64 Source # 
Instance details

Defined in Data.BEncode

BEncode () Source # 
Instance details

Defined in Data.BEncode

BEncode Text Source # 
Instance details

Defined in Data.BEncode

BEncode Version Source # 
Instance details

Defined in Data.BEncode

BEncode BValue Source # 
Instance details

Defined in Data.BEncode

BEncode BDict Source # 
Instance details

Defined in Data.BEncode

BEncode BString Source # 
Instance details

Defined in Data.BEncode

BEncode BInteger Source # 
Instance details

Defined in Data.BEncode

BEncode a => BEncode [a] Source # 
Instance details

Defined in Data.BEncode

(BEncode a, BEncode b) => BEncode (a, b) Source # 
Instance details

Defined in Data.BEncode

Methods

toBEncode :: (a, b) -> BValue Source #

fromBEncode :: BValue -> Result (a, b) Source #

(BEncode a, BEncode b, BEncode c) => BEncode (a, b, c) Source # 
Instance details

Defined in Data.BEncode

Methods

toBEncode :: (a, b, c) -> BValue Source #

fromBEncode :: BValue -> Result (a, b, c) Source #

(BEncode a, BEncode b, BEncode c, BEncode d) => BEncode (a, b, c, d) Source # 
Instance details

Defined in Data.BEncode

Methods

toBEncode :: (a, b, c, d) -> BValue Source #

fromBEncode :: BValue -> Result (a, b, c, d) Source #

(BEncode a, BEncode b, BEncode c, BEncode d, BEncode e) => BEncode (a, b, c, d, e) Source # 
Instance details

Defined in Data.BEncode

Methods

toBEncode :: (a, b, c, d, e) -> BValue Source #

fromBEncode :: BValue -> Result (a, b, c, d, e) Source #

encode :: BEncode a => a -> ByteString Source #

Encode a value using bencode format to a lazy ByteString.

decode :: BEncode a => ByteString -> Result a Source #

Decode a value from a strict ByteString using bencode format.

Helpers

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 BEncode 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 BEncode FileInfo where
    toBEncode FileInfo {..} = toDict $
         "length" .=! fileLength
      .: "md5sum" .=? fileMD5sum
      .: "path"   .=! filePath
      .: "tags"   .=? fileTags
      .: endDict
 

NOTE: the list of pairs MUST be sorted lexicographically by keys, like so:

"length" < "md5sum" < "path" < "tags"

(.=!) :: BEncode a => BKey -> a -> Assoc infix 6 Source #

Make required key value pair.

(.=?) :: BEncode a => BKey -> Maybe a -> Assoc infix 6 Source #

Like the (.=!) operator but if the value is not present then the key do not appear in resulting bencode dictionary.

(.:) :: Assoc -> BDict -> BDict infixr 5 Source #

Cons a key/value pair.

endDict :: BDict Source #

Used to specify end of dictionary. See Assoc.

toDict :: BDict -> BValue Source #

Make a bencode value from dictionary description.

Extraction

data Get a Source #

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 the fromBEncode function instance looks like:

  instance BEncode FileInfo where
    fromBEncode = fromDict $ do
      FileInfo <$>! "length"
               <*>? "md5sum"
               <*>! "path"
               <*>? "tags"
 

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

NOTE: the actions MUST be sorted lexicographically by keys, like so:

"length" < "md5sum" < "path" < "tags"

Instances
Monad Get Source #

fail is catchable from pure code.

Instance details

Defined in Data.BEncode

Methods

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

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

return :: a -> Get a #

fail :: String -> Get a #

Functor Get Source # 
Instance details

Defined in Data.BEncode

Methods

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

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

Applicative Get Source # 
Instance details

Defined in Data.BEncode

Methods

pure :: a -> Get a #

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

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

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

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

Alternative Get Source # 
Instance details

Defined in Data.BEncode

Methods

empty :: Get a #

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

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

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

type Result = Either String Source #

Result used in decoding operations.

decodingError :: String -> Result a Source #

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

fromDict :: forall a. Typeable a => Get a -> BValue -> Result a Source #

Run a Get monad. See Get for usage.

lookAhead :: Get a -> Get a Source #

Run action, but return without consuming and key/value pair. Fails if the action fails.

next :: Get BValue Source #

Get lexicographical successor of the current key/value pair.

req :: BKey -> Get BValue Source #

Extract required value from the given key.

opt :: BKey -> Get (Maybe BValue) Source #

Extract optional value from the given key.

field :: BEncode a => Get BValue -> Get a Source #

Reconstruct a bencodable value from bencode value.

match :: BKey -> BValue -> Get () Source #

Match key with value.

(<$>!) :: BEncode a => (a -> b) -> BKey -> Get b infixl 4 Source #

Shorthand for: f <$> field (req k).

(<$>?) :: BEncode a => (Maybe a -> b) -> BKey -> Get b infixl 4 Source #

Shorthand for: f <$> optional (field (req k)).

(<*>!) :: BEncode a => Get (a -> b) -> BKey -> Get b infixl 4 Source #

Shorthand for: f <*> field (req k).

(<*>?) :: BEncode a => Get (Maybe a -> b) -> BKey -> Get b infixl 4 Source #

Shorthand for: f <*> optional (field (req k)).