| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.Bencode.Encode
Description
Conversions from Haskell values to Bencoded ByteStrings.
Introduction
Encoding is done using encoders. An encoder is simply a function from a
Haskell type to Encoding. There are encoders for the four Bencode types:
stringencodesByteStrings as Bencode stringsintegerencodesIntegers as Bencode integerslistencodesVectors as Bencode listsdictencodesMaps withByteStringkeys as Bencode dictionaries
These can used to build more complex encoders for arbitrary types.
data File = File
{ hash :: ByteString
, size :: Integer
, tags :: Vector Text
} deriving Show
It is reasonable to encode a File as a Bencode dictionary with the field
names as keys, and appropriate types for the values.
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Bencode.Encode as E
encodeFile :: File -> E.Encoding
encodeFile (File hash size tags) = E.dict' $
E.field "hash" E.string hash
<> E.field "size" E.integer size
<> E.field "tags" (E.list E.text) tags
Applying toBuilder to an Encoding gives a ByteString
Builder, which can then be converted to a lazy
ByteString, written to a file, or used otherwise.
import qualified Data.ByteString.Builder (toLazyByteString) import qualified Data.Vector as V
>>>toLazyByteString $ encodeFile $ File "xxxx" 1024 (V.fromList ["work", "backup"])"d4:hash4:xxxx4:sizei1024e4:tagsl4:work6:backupee"
In this module, encodings are total conversions from Haskell values to
ByteStrings. If some data should fail to encode, it should be handled
separately.
For more examples, see the "Recipes" section at the end of this page.
Synopsis
- data Encoding
- toBuilder :: Encoding -> Builder
- string :: ByteString -> Encoding
- integer :: Integer -> Encoding
- list :: (a -> Encoding) -> Vector a -> Encoding
- dict :: (a -> Encoding) -> Map ByteString a -> Encoding
- text :: Text -> Encoding
- int :: Int -> Encoding
- word :: Word -> Encoding
- field :: ByteString -> (a -> Encoding) -> a -> FieldEncodings
- dict' :: FieldEncodings -> Encoding
- data FieldEncodings
- value :: Value -> Encoding
Encoding
toBuilder :: Encoding -> Builder Source #
Get a ByteString Builder representation for an encoded Bencode value.
Primary encoders
string :: ByteString -> Encoding Source #
Encode a bytestring as a Bencode string.
list :: (a -> Encoding) -> Vector a -> Encoding Source #
Encode a Vector as a Bencode list, using the given encoder for elements.
dict :: (a -> Encoding) -> Map ByteString a -> Encoding Source #
Encode a Map as a Bencode dictionary, using the given encoder for values.
More encoders
text :: Text -> Encoding Source #
Encode Text as a Bencode string. As per the Bencode specification, all
text must be encoded as UTF-8 strings.
field :: ByteString -> (a -> Encoding) -> a -> FieldEncodings Source #
A key-value encoding for a Bencode dictionary.
dict' :: FieldEncodings -> Encoding Source #
Encode Bencode key-value pairs as a Bencode dictionary.
WARNING: If there are duplicate keys in the FieldEncodings, an
arbitrary key-value pair among them will be encoded and the rest discarded.
data FieldEncodings Source #
Key-value encodings for a Bencode dictionary.
Instances
| Monoid FieldEncodings Source # | |
Defined in Data.Bencode.Encode Methods mappend :: FieldEncodings -> FieldEncodings -> FieldEncodings # mconcat :: [FieldEncodings] -> FieldEncodings # | |
| Semigroup FieldEncodings Source # | |
Defined in Data.Bencode.Encode Methods (<>) :: FieldEncodings -> FieldEncodings -> FieldEncodings # sconcat :: NonEmpty FieldEncodings -> FieldEncodings # stimes :: Integral b => b -> FieldEncodings -> FieldEncodings # | |
Recipes
Recipies for some common and uncommon usages.
The following preface is assumed.
{-# LANGUAGE OverloadedStrings #-}
import Data.ByteString.Builder (toLazyByteString)
import Data.Text (Text)
import qualified Data.Bencode.Encode as E
toLBS = toLazyByteString . E.toBuilder
Encode an optional field
data File = File { name :: Text, size :: Maybe Int }
encodeFile :: File -> E.Encoding
encodeFile (File name size) = E.dict' $
E.field "name" E.text name
<> foldMap (E.field "size" E.int) size
>>>toLBS $ encodeFile $ File "hello.txt" (Just 16)"d4:name9:hello.txt4:sizei16ee">>>toLBS $ encodeFile $ File "hello.txt" Nothing"d4:name9:hello.txte"
Encode an enum
data Color = Red | Green | Blue encodeColor :: Color -> E.EncodingencodeColor = E.text. toText where toText Red = "red" toText Green = "green" toText Blue = "blue"
>>>toLBS $ encodeColor Green"5:green"
Encode fields differently based on the value
data Response = Response { id_ :: Int, result :: Either Text ByteString }
encodeResponse :: Response -> E.Encoding
encodeResponse (Response id_ result) = E.dict' $
E.field "id" E.int id_
<> either err ok result
where
err reason =
E.field "status" E.text "failure"
<> E.field "reason" E.text reason
ok data_ =
E.field "status" E.text "success"
<> E.field "data" E.string data_
>>>toLBS $ encodeResponse $ Response 42 (Left "unauthorized")"d2:idi42e6:reason12:unauthorized6:status7:failuree">>>toLBS $ encodeResponse $ Response 42 (Right "0000")"d4:data4:00002:idi42e6:status7:successe"
Encode as nested dicts
data File = File { name :: Text, size :: Int }
encodeFile :: File -> E.Encoding
encodeFile (File name size) = E.dict' $
E.field "name" E.text name
<> E.field "metadata" id (E.dict' $
E.field "info" id (E.dict' $
E.field "size" E.int size))
>>>toLBS $ encodeFile $ File "hello.txt" 32"d8:metadatad4:infod4:sizei32eee4:name9:hello.txte"