Copyright | (c) Sam Truzjan 2013 |
---|---|
License | BSD3 |
Maintainer | pxqr.sta@gmail.com |
Stability | stable |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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
- data BValue
- class BEncode a where
- toBEncode :: a -> BValue
- fromBEncode :: BValue -> Result a
- encode :: BEncode a => a -> ByteString
- decode :: BEncode a => ByteString -> Result a
- data Assoc
- (.=!) :: BEncode a => BKey -> a -> Assoc
- (.=?) :: BEncode a => BKey -> Maybe a -> Assoc
- (.:) :: Assoc -> BDict -> BDict
- endDict :: BDict
- toDict :: BDict -> BValue
- data Get a
- type Result = Either String
- decodingError :: String -> Result a
- fromDict :: forall a. Typeable a => Get a -> BValue -> Result a
- lookAhead :: Get a -> Get a
- next :: Get BValue
- req :: BKey -> Get BValue
- opt :: BKey -> Get (Maybe BValue)
- field :: BEncode a => Get BValue -> Get a
- match :: BKey -> BValue -> Get ()
- (<$>!) :: BEncode a => (a -> b) -> BKey -> Get b
- (<$>?) :: BEncode a => (Maybe a -> b) -> BKey -> Get b
- (<*>!) :: BEncode a => Get (a -> b) -> BKey -> Get b
- (<*>?) :: BEncode a => Get (Maybe a -> b) -> BKey -> Get b
Documentation
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.
BInteger !BInteger | bencode integers; |
BString !BString | bencode strings; |
BList BList | list of bencode values; |
BDict BDict | bencode key-value dictionary. |
Instances
Eq BValue Source # | |
Ord BValue Source # | |
Read BValue Source # | |
Show BValue Source # | |
Generic BValue Source # | |
NFData BValue Source # | |
Defined in Data.BEncode.Types | |
BEncode BValue Source # | |
BEncode BDict Source # | |
type Rep BValue Source # | |
Defined in Data.BEncode.Types type Rep BValue = D1 ('MetaData "BValue" "Data.BEncode.Types" "bencoding-0.4.5.3-3C5sORAAFvX3pierLOBPg9" 'False) ((C1 ('MetaCons "BInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BInteger)) :+: C1 ('MetaCons "BString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BString))) :+: (C1 ('MetaCons "BList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BList)) :+: C1 ('MetaCons "BDict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BDict)))) |
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.
Nothing
toBEncode :: a -> BValue Source #
See an example of implementation here Assoc
fromBEncode :: BValue -> Result a Source #
See an example of implementation here Get
.
Instances
BEncode Bool Source # | |
BEncode Int Source # | |
BEncode Int8 Source # | |
BEncode Int16 Source # | |
BEncode Int32 Source # | |
BEncode Int64 Source # | |
BEncode Word Source # | |
BEncode Word8 Source # | |
BEncode Word16 Source # | |
BEncode Word32 Source # | |
BEncode Word64 Source # | |
BEncode () Source # | |
Defined in Data.BEncode | |
BEncode Text Source # | |
BEncode Version Source # | |
BEncode BValue Source # | |
BEncode BDict Source # | |
BEncode BString Source # | |
BEncode BInteger Source # | |
BEncode a => BEncode [a] Source # | |
Defined in Data.BEncode | |
(BEncode a, BEncode b) => BEncode (a, b) Source # | |
Defined in Data.BEncode | |
(BEncode a, BEncode b, BEncode c) => BEncode (a, b, c) Source # | |
Defined in Data.BEncode | |
(BEncode a, BEncode b, BEncode c, BEncode d) => BEncode (a, b, c, d) Source # | |
Defined in Data.BEncode | |
(BEncode a, BEncode b, BEncode c, BEncode d, BEncode e) => BEncode (a, b, c, d, e) Source # | |
Defined in Data.BEncode |
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
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
, though we don't want
to check the both BEncode
FileInfoMaybe
s manually. The more declarative and
convenient way to define the toBEncode
method is to use
dictionary builders:
instanceBEncode
FileInfo wheretoBEncode
FileInfo {..} =toDict
$ "length".=!
fileLength.:
"md5sum".=?
fileMD5sum.:
"path".=!
filePath.:
"tags".=?
fileTags.:
endDict
NOTE: the list of pairs MUST be sorted lexicographically by keys, like so:
(.=?) :: 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.
Extraction
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:
instanceBEncode
FileInfo wherefromBEncode
=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:
decodingError :: String -> Result a Source #
Typically used to throw an decoding error in fromBEncode; when BEncode value to match expected value.
lookAhead :: Get a -> Get a Source #
Run action, but return without consuming and key/value pair. Fails if the action fails.
field :: BEncode a => Get BValue -> Get a Source #
Reconstruct a bencodable value from bencode value.