Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Conversions from Bencoded ByteString
s to Haskell values.
Synopsis
- data Parser a
- decode :: Parser a -> ByteString -> Either String a
- decodeMaybe :: Parser a -> ByteString -> Maybe a
- string :: Parser ByteString
- stringEq :: ByteString -> Parser ()
- text :: Parser Text
- textEq :: Text -> Parser ()
- integer :: Parser Integer
- int :: Parser Int
- intEq :: Int -> Parser ()
- int64 :: Parser Int64
- int32 :: Parser Int32
- int16 :: Parser Int16
- int8 :: Parser Int8
- word :: Parser Word
- word64 :: Parser Word64
- word32 :: Parser Word32
- word16 :: Parser Word16
- word8 :: Parser Word8
- list :: Parser a -> Parser (Vector a)
- index :: Int -> Parser a -> Parser a
- elem :: Parser a -> Elems a
- list' :: Elems a -> Parser a
- data Elems a
- dict :: Parser a -> Parser (Map ByteString a)
- field :: ByteString -> Parser a -> Parser a
- field' :: ByteString -> Parser a -> Fields a
- dict' :: Fields a -> Parser a
- data Fields a
- value :: Parser Value
- fail :: String -> Parser a
- mapMaybe :: (a -> Maybe b) -> Parser a -> Parser b
- mapOrFail :: (a -> Either String b) -> Parser a -> Parser b
Quick start
Decoding is done using parsers. This module defines parsers that can be composed to build parsers for arbitrary types.
data File = File { hash :: ByteString , size :: Integer , tags :: Vector Text } deriving Show
Assuming a File
is encoded as a Bencode dictionary with the field names as
keys and appropriate value types, a parser for File
can be defined as
{-# LANGUAGE OverloadedStrings #-} import qualified Data.Bencode.Decode as D fileParser :: D.Parser
File fileParser = File <$> D.field
"hash" D.string
<*> D.field
"size" D.integer
<*> D.field
"tags" (D.list
D.text
)
The parser can then be run on a ByteString
with decode
.
>>>
D.decode fileParser "d4:hash4:xxxx4:sizei1024e4:tagsl4:work6:backupee"
Right (File {hash = "xxxx", size = 1024, tags = ["work","backup"]})
Of course, invalid Bencode or Bencode that does not satisfy the File
parser
will fail to decode.
>>>
D.decode fileParser "d4:hash4:xxxx4:tagsl4:work6:backupee"
Left "KeyNotFound \"size\""
For more examples, see the Recipes section at the end of this page.
Parser
A parser from a Bencode value to a Haskell value.
decode :: Parser a -> ByteString -> Either String a Source #
Decode a value from the given ByteString
. If decoding fails, returns
Left
with a failure message. The message is a short human-readable error
description and should not be relied on programmatically.
decodeMaybe :: Parser a -> ByteString -> Maybe a Source #
Decode a value from the given ByteString
. If decoding fails, returns
Nothing
.
String parsers
string :: Parser ByteString Source #
Decode a Bencode string as a ByteString. Fails on a non-string.
stringEq :: ByteString -> Parser () Source #
Succeeds only on a Bencode string that equals the given string.
Decode a bencode string as UTF-8 text. Fails on a non-string or if the string is not valid UTF-8.
Integer parsers
Decode a Bencode integer as an Int
. Fails on a non-integer or if the
integer is out of bounds for an Int
.
int64 :: Parser Int64 Source #
Decode a Bencode integer as an Int64
. Fails on a non-integer or if the
integer is out of bounds for an Int64
.
Since: 0.1.1.0
int32 :: Parser Int32 Source #
Decode a Bencode integer as an Int32
. Fails on a non-integer or if the
integer is out of bounds for an Int32
.
Since: 0.1.1.0
int16 :: Parser Int16 Source #
Decode a Bencode integer as an Int16
. Fails on a non-integer or if the
integer is out of bounds for an Int16
.
Since: 0.1.1.0
Decode a Bencode integer as an Int8
. Fails on a non-integer or if the
integer is out of bounds for an Int8
.
Since: 0.1.1.0
Decode a Bencode integer as a Word
. Fails on a non-integer or if the
integer is out of bounds for a Word
.
word64 :: Parser Word64 Source #
Decode a Bencode integer as a Word64
. Fails on a non-integer or if the
integer is out of bounds for a Word64
.
Since: 0.1.1.0
word32 :: Parser Word32 Source #
Decode a Bencode integer as a Word32
. Fails on a non-integer or if the
integer is out of bounds for a Word32
.
Since: 0.1.1.0
word16 :: Parser Word16 Source #
Decode a Bencode integer as a Word16
. Fails on a non-integer or if the
integer is out of bounds for a Word16
.
Since: 0.1.1.0
word8 :: Parser Word8 Source #
Decode a Bencode integer as a Word8
. Fails on a non-integer or if the
integer is out of bounds for a Word8
.
Since: 0.1.1.0
List parsers
list :: Parser a -> Parser (Vector a) Source #
Decode a Bencode list with the given parser for elements. Fails on a non-list or if any element in the list fails to parse.
index :: Int -> Parser a -> Parser a Source #
Decode a list element with the given parser at the given (0-based) index. Fails on a non-list, if the index is out of bounds, or if the element parser fails.
Examples
data File = File { name :: Text, size :: Int } fileParser :: D.Parser
File fileParser = File <$> D.index 0 D.text
<*> D.index 1 D.int
Since: 0.1.1.0
elem :: Parser a -> Elems a Source #
Decode the next list element with the given parser. Convert to a Parser
with list'
.
Since: 0.1.1.0
list' :: Elems a -> Parser a Source #
Create a Parser
from an Elems
. Fails on a non-list, if the number of
elements does not match the Elems
exactly, or if any element parser fails.
Examples
data File = File { name :: Text, size :: Int } fileParser :: D.Parser
File fileParser = D.list' $ File <$> D.elem
D.text
<*> D.elem
D.int
Since: 0.1.1.0
Dictionary parsers
dict :: Parser a -> Parser (Map ByteString a) Source #
Decode a Bencode dict with the given parser for values. Fails on a non-dict or if any value in the dict fails to parse.
field' :: ByteString -> Parser a -> Fields a Source #
Decode a value with the given parser for the given key. Convert to a
Parser
with dict'
.
Since: 0.1.1.0
dict' :: Fields a -> Parser a Source #
Create a Parser
from a Fields
. Fails on a non-dict, if a key is
absent, or if any value fails to parse. Also fails if there are leftover
unparsed keys in the dict.
If leftover keys should be ignored, use field
instead.
Examples
data File = File { name :: Text, size :: Int } fileParser :: D.Parser
File fileParser = D.dict' $ File <$> D.field'
"name" D.text
<*> D.field'
"size" D.int
Since: 0.1.1.0
Miscellaneous
mapMaybe :: (a -> Maybe b) -> Parser a -> Parser b Source #
Run the function on the parsed value, fail with empty
if the result is
Nothing
.
Since: 0.1.1.0
mapOrFail :: (a -> Either String b) -> Parser a -> Parser b Source #
Run the function on the parsed value, fail with fail
if the result is a
Left
.
Since: 0.1.1.0
Recipes
Recipes for some common and uncommon usages.
The following preface is assumed.
{-# LANGUAGE OverloadedStrings #-} import Data.ByteString (ByteString) import Data.Text (Text) import qualified Data.Bencode.Decode as D
Decode an optional field
import Control.Applicative (optional
) data File = File { name :: Text, size :: Maybe Int } deriving Show fileParser :: D.Parser
File fileParser = File <$> D.field
"name" D.text
<*> optional (D.field
"size" D.int
)
>>>
D.decode fileParser "d4:name9:hello.txt4:sizei16ee"
Right (File {name = "hello.txt", size = Just 16})>>>
D.decode fileParser "d4:name9:hello.txte"
Right (File {name = "hello.txt", size = Nothing})
Decode an enum
import Control.Applicative ((<|>)
) data Color = Red | Green | Blue deriving Show colorParser :: D.Parser
Color colorParser = Red <$ D.stringEq
"red" <|> Green <$ D.stringEq
"green" <|> Blue <$ D.stringEq
"blue" <|> D.fail
"unknown color"
>>>
D.decode colorParser "5:green"
Right Green>>>
D.decode colorParser "5:black"
Left "Fail: unknown color"
Decode a dict, failing on leftover keys
data File = File { name :: Text, size :: Int } deriving Show fileParser :: D.Parser
File fileParser = D.dict'
$ File <$> D.field'
"name" D.text
<*> D.field'
"size" D.int
>>>
D.decode fileParser "d4:name9:hello.txt4:sizei32ee"
Right (File {name = "hello.txt", size = 32})>>>
D.decode fileParser "d6:hiddeni1e4:name9:hello.txt4:sizei32ee"
Left "UnrecognizedKey \"hidden\""
Decode differently based on dict contents
data Response = Response { id_ :: Int , result :: Either Text ByteString } deriving Show responseParser :: D.Parser
Response responseParser = do id_ <- D.field
"id" D.int
status <- D.field
"status" D.string
case status of "failure" -> do reason <- D.field
"reason" D.text
pure $ Response id_ (Left reason) "success" -> do data_ <- D.field
"data" D.string
pure $ Response id_ (Right data_) _ -> D.fail
"unknown status"
>>>
D.decode responseParser "d2:idi42e6:reason12:unauthorized6:status7:failuree"
Right (Response {id_ = 42, result = Left "unauthorized"})>>>
D.decode responseParser "d4:data4:00002:idi42e6:status7:successe"
Right (Response {id_ = 42, result = Right "0000"})
Decode nested dicts
data File = File { name :: Text, size :: Int } deriving Show fileParser :: D.Parser
File fileParser = File <$> D.field
"name" D.text
<*> D.field
"metadata" (D.field
"info" (D.field
"size" D.int
))
>>>
D.decode fileParser "d8:metadatad4:infod4:sizei32eee4:name9:hello.txte"
Right (File {name = "hello.txt", size = 32})
Decode a heterogeneous list
data File = File { name :: Text, size :: Int } deriving Show fileParser :: D.Parser
File fileParser = D.list'
$ File <$> D.elem
D.text
<*> D.elem
D.int
>>>
D.decode fileParser "l9:hello.txti32ee"
Right (File {name = "hello.txt", size = 32})