Portability | portable |
---|---|
Stability | stable |
Maintainer | pxqr.sta@gmail.com |
Safe Haskell | Trustworthy |
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.
- 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
- next :: Get BValue
- req :: BKey -> Get BValue
- opt :: BKey -> Get (Maybe BValue)
- field :: BEncode a => Get BValue -> Get a
- (<$>!) :: 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.
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 '_' prefixes are omitted since they are used for lens.
toBEncode :: a -> BValueSource
See an example of implementation here Assoc
fromBEncode :: BValue -> Result aSource
See an example of implementation here Get
.
BEncode Bool | |
BEncode Int | |
BEncode Int8 | |
BEncode Int16 | |
BEncode Int32 | |
BEncode Int64 | |
BEncode Word | |
BEncode Word8 | |
BEncode Word16 | |
BEncode Word32 | |
BEncode Word64 | |
BEncode () | |
BEncode Text | |
BEncode Version | |
BEncode BValue | |
BEncode BDict | |
BEncode BString | |
BEncode BInteger | |
BEncode a => BEncode [a] | |
(BEncode a, BEncode b) => BEncode (a, b) | |
(BEncode a, BEncode b, BEncode c) => BEncode (a, b, c) | |
(BEncode a, BEncode b, BEncode c, BEncode d) => BEncode (a, b, c, d) | |
(BEncode a, BEncode b, BEncode c, BEncode d, BEncode e) => BEncode (a, b, c, d, e) |
encode :: BEncode a => a -> ByteStringSource
Encode a value using bencode format to a lazy ByteString
.
decode :: BEncode a => ByteString -> Result aSource
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 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 SHOULD be sorted lexicographically by keys, so: length < md5sum < path < tags.
(.=?) :: BEncode a => BKey -> Maybe a -> AssocSource
Like (.=!) 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:
instance BEncodable 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 SHOULD be sorted lexicographically by keys, so: length < md5sum < path < tags.
decodingError :: String -> Result aSource
Typically used to throw an decoding error in fromBEncode; when BEncode value to match expected value.