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.
- type BInteger = Integer
- type BString = ByteString
- type BList = [BEncode]
- type BDict = Map BKey BEncode
- type BKey = ByteString
- data BEncode
- ppBEncode :: BEncode -> Doc
- class BEncodable a where
- toBEncode :: a -> BEncode
- fromBEncode :: BEncode -> Result a
- type Result = Either String
- encode :: BEncode -> ByteString
- decode :: ByteString -> Result BEncode
- encoded :: BEncodable a => a -> ByteString
- decoded :: BEncodable a => ByteString -> Result a
- data Assoc
- (-->) :: BEncodable a => ByteString -> a -> Assoc
- (-->?) :: BEncodable a => ByteString -> Maybe a -> Assoc
- fromAssocs :: [Assoc] -> BEncode
- fromAscAssocs :: [Assoc] -> BEncode
- decodingError :: String -> Result a
- reqKey :: BEncodable a => BDict -> BKey -> Result a
- optKey :: BEncodable a => BDict -> BKey -> Result (Maybe a)
- (>--) :: BEncodable a => BDict -> BKey -> Result a
- (>--?) :: BEncodable a => BDict -> BKey -> Result (Maybe a)
- isInteger :: BEncode -> Bool
- isString :: BEncode -> Bool
- isList :: BEncode -> Bool
- isDict :: BEncode -> Bool
- builder :: BEncode -> Builder
- parser :: Parser BEncode
Datatype
type BString = ByteStringSource
type BKey = ByteStringSource
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.
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.
toBEncode :: a -> BEncodeSource
See an example of implementation here Assoc
fromBEncode :: BEncode -> Result aSource
See an example of implementation here reqKey
.
BEncodable Bool | |
BEncodable Int | |
BEncodable Int8 | |
BEncodable Int16 | |
BEncodable Int32 | |
BEncodable Int64 | |
BEncodable Word | |
BEncodable Word8 | |
BEncodable Word16 | |
BEncodable Word32 | |
BEncodable Word64 | |
BEncodable () | |
BEncodable Text | |
BEncodable Version | |
BEncodable BEncode | |
BEncodable BString | |
BEncodable BInteger | |
BEncodable a => BEncodable [a] | |
(Eq a, BEncodable a) => BEncodable (Set a) | |
(BEncodable a, BEncodable b) => BEncodable (a, b) | |
BEncodable a => BEncodable (Map ByteString a) | |
(BEncodable a, BEncodable b, BEncodable c) => BEncodable (a, b, c) | |
(BEncodable a, BEncodable b, BEncodable c, BEncodable d) => BEncodable (a, b, c, d) | |
(BEncodable a, BEncodable b, BEncodable c, BEncodable d, BEncodable e) => BEncodable (a, b, c, d, e) |
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
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
.