Copyright | (c) Dong Han 2020 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides various tools to help user define MessagePack
instance, please import MessagePack
to get more instances.
Synopsis
- class MessagePack a where
- data Value
- defaultSettings :: Settings
- data Settings = Settings {}
- decode :: MessagePack a => Bytes -> (Bytes, Either DecodeError a)
- decode' :: MessagePack a => Bytes -> Either DecodeError a
- decodeChunks :: (MessagePack a, Monad m) => m Bytes -> Bytes -> m (Bytes, Either DecodeError a)
- encode :: MessagePack a => a -> Bytes
- encodeChunks :: MessagePack a => a -> [Bytes]
- type DecodeError = Either ParseError ConvertError
- type ParseError = [Text]
- type ParseChunks (m :: Type -> Type) chunk err x = m chunk -> chunk -> m (chunk, Either err x)
- parseValue :: Bytes -> (Bytes, Either ParseError Value)
- parseValue' :: Bytes -> Either ParseError Value
- parseValueChunks :: Monad m => m Bytes -> Bytes -> m (Bytes, Either ParseError Value)
- parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either ParseError Value)
- gToValue :: GToValue f => Settings -> f a -> Value
- gFromValue :: GFromValue f => Settings -> Value -> Converter (f a)
- gEncodeMessagePack :: GEncodeMessagePack f => Settings -> f a -> Builder ()
- convertValue :: MessagePack a => Value -> Either ConvertError a
- newtype Converter a = Converter {
- runConverter :: forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r
- fail' :: Text -> Converter a
- (<?>) :: Converter a -> PathElement -> Converter a
- prependContext :: Text -> Converter a -> Converter a
- data PathElement
- data ConvertError = ConvertError {
- errPath :: [PathElement]
- errMsg :: Text
- typeMismatch :: Text -> Text -> Value -> Converter a
- fromNil :: Text -> a -> Value -> Converter a
- withBool :: Text -> (Bool -> Converter a) -> Value -> Converter a
- withStr :: Text -> (Text -> Converter a) -> Value -> Converter a
- withBin :: Text -> (Bytes -> Converter a) -> Value -> Converter a
- withArray :: Text -> (Vector Value -> Converter a) -> Value -> Converter a
- withKeyValues :: Text -> (Vector (Value, Value) -> Converter a) -> Value -> Converter a
- withFlatMap :: Text -> (FlatMap Value Value -> Converter a) -> Value -> Converter a
- withFlatMapR :: Text -> (FlatMap Value Value -> Converter a) -> Value -> Converter a
- withBoundedScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a
- withSystemTime :: Text -> (SystemTime -> Converter a) -> Value -> Converter a
- (.:) :: MessagePack a => FlatMap Value Value -> Text -> Converter a
- (.:?) :: MessagePack a => FlatMap Value Value -> Text -> Converter (Maybe a)
- (.:!) :: MessagePack a => FlatMap Value Value -> Text -> Converter (Maybe a)
- convertField :: (Value -> Converter a) -> FlatMap Value Value -> Text -> Converter a
- convertFieldMaybe :: (Value -> Converter a) -> FlatMap Value Value -> Text -> Converter (Maybe a)
- convertFieldMaybe' :: (Value -> Converter a) -> FlatMap Value Value -> Text -> Converter (Maybe a)
- (.=) :: MessagePack v => Text -> v -> (Value, Value)
- object :: [(Value, Value)] -> Value
- (.!) :: MessagePack v => Text -> v -> KVItem
- object' :: KVItem -> Builder ()
- data KVItem
MessagePack Class
class MessagePack a where Source #
Type class for encode & decode MessagePack.
Nothing
fromValue :: Value -> Converter a Source #
toValue :: a -> Value Source #
encodeMessagePack :: a -> Builder () Source #
Instances
Representation of MessagePack data.
Bool !Bool | true or false |
Int !Int64 | an integer |
Float !Float | a floating point number |
Double !Double | a floating point number |
Str !Text | a UTF-8 string |
Bin !Bytes | a byte array |
Array !(Vector Value) | a sequence of objects |
Map !(Vector (Value, Value)) | key-value pairs of objects |
Ext | |
Nil | nil |
Instances
defaultSettings :: Settings Source #
Settings T.pack T.pack False
Generic encode/decode Settings
Encode & Decode
decode :: MessagePack a => Bytes -> (Bytes, Either DecodeError a) Source #
Decode a MessagePack bytes, return any trailing bytes.
decode' :: MessagePack a => Bytes -> Either DecodeError a Source #
Decode a MessagePack doc, trailing bytes are not allowed.
decodeChunks :: (MessagePack a, Monad m) => m Bytes -> Bytes -> m (Bytes, Either DecodeError a) Source #
Decode MessagePack doc chunks, return trailing bytes.
encode :: MessagePack a => a -> Bytes Source #
Directly encode data to MessagePack bytes.
encodeChunks :: MessagePack a => a -> [Bytes] Source #
Encode data to MessagePack bytes chunks.
type DecodeError = Either ParseError ConvertError Source #
type ParseError = [Text] #
Type alias for error message
type ParseChunks (m :: Type -> Type) chunk err x = m chunk -> chunk -> m (chunk, Either err x) #
Type alias for a streaming parser, draw chunk from Monad m (with a initial chunk), return result in Either err x
.
parse into MessagePack Value
parseValue :: Bytes -> (Bytes, Either ParseError Value) Source #
Parse Value
without consuming trailing bytes.
parseValue' :: Bytes -> Either ParseError Value Source #
Parse Value
, if there're bytes left, parsing will fail.
parseValueChunks :: Monad m => m Bytes -> Bytes -> m (Bytes, Either ParseError Value) Source #
Increamental parse Value
without consuming trailing bytes.
parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either ParseError Value) Source #
Increamental parse Value
, if there're bytes left, parsing will fail.
Generic FromValue, ToValue & EncodeMessagePack
gEncodeMessagePack :: GEncodeMessagePack f => Settings -> f a -> Builder () Source #
Convert Value
to Haskell data
convertValue :: MessagePack a => Value -> Either ConvertError a Source #
Run a Converter
with input value.
Converter
provides a monadic interface to convert protocol IR (e.g.Value
) to Haskell ADT.
Converter | |
|
Instances
(<?>) :: Converter a -> PathElement -> Converter a infixl 9 #
Add (JSON) Path context to a converter
When converting a complex structure, it helps to annotate (sub)converters with context, so that if an error occurs, you can find its location.
withFlatMapR "Person" $ \o -> Person <$> o .: "name" <?> Key "name" <*> o .: "age" <?> Key "age"
(Standard methods like (.:)
already do this.)
With such annotations, if an error occurs, you will get a (JSON) Path location of that error.
prependContext :: Text -> Converter a -> Converter a #
Add context to a failure message, indicating the name of the structure being converted.
prependContext "MyType" (fail "[error message]") -- Error: "converting MyType failed, [error message]"
data PathElement #
Elements of a (JSON) Value path used to describe the location of an error.
Key !Text | Path element of a key into an object, "object.key". |
Index !Int | Path element of an index into an array, "array[index]". |
Embedded | path of a embedded (JSON) String |
Instances
data ConvertError #
Error info with (JSON) Path info.
ConvertError | |
|
Instances
:: Text | The name of the type you are trying to convert. |
-> Text | The MessagePack value type you expecting to meet. |
-> Value | The actual value encountered. |
-> Converter a |
Produce an error message like converting XXX failed, expected XXX, encountered XXX
.
withKeyValues :: Text -> (Vector (Value, Value) -> Converter a) -> Value -> Converter a Source #
Directly use Map
as key-values for further converting.
withFlatMap :: Text -> (FlatMap Value Value -> Converter a) -> Value -> Converter a Source #
Take a Map
as an 'FM.FlatMap Value Value', on key duplication prefer first one.
withFlatMapR :: Text -> (FlatMap Value Value -> Converter a) -> Value -> Converter a Source #
Take a Map
as an 'FM.FlatMap Value Value', on key duplication prefer last one.
withBoundedScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a Source #
applies withBoundedScientific
name f valuef
to the Scientific
number
when value
is a Ext
0x00/0x01
with exponent less than or equal to 1024.
withSystemTime :: Text -> (SystemTime -> Converter a) -> Value -> Converter a Source #
(.:) :: MessagePack a => FlatMap Value Value -> Text -> Converter a Source #
Retrieve the value associated with the given key of an Map
.
The result is empty
if the key is not present or the value cannot
be converted to the desired type.
This accessor is appropriate if the key and value must be present
in an object for it to be valid. If the key and value are
optional, use .:?
instead.
(.:?) :: MessagePack a => FlatMap Value Value -> Text -> Converter (Maybe a) Source #
Retrieve the value associated with the given key of an Map
. The
result is Nothing
if the key is not present or if its value is Nil
,
or fail if the value cannot be converted to the desired type.
This accessor is most useful if the key and value can be absent
from an object without affecting its validity. If the key and
value are mandatory, use .:
instead.
convertFieldMaybe :: (Value -> Converter a) -> FlatMap Value Value -> Text -> Converter (Maybe a) Source #
Variant of .:?
with explicit converter function.
convertFieldMaybe' :: (Value -> Converter a) -> FlatMap Value Value -> Text -> Converter (Maybe a) Source #
Variant of .:!
with explicit converter function.
Helper for manually writing instance.
(.=) :: MessagePack v => Text -> v -> (Value, Value) infixr 8 Source #
Connect key and value to a tuple to be used with object
.
A newtype for Builder
, whose semigroup's instance is to connect kv builder and sum kv length.