Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Tools for writing instances of MsgpackDecode
.
Synopsis
- pattern Msgpack :: MsgpackDecode a => a -> Object
- class MsgpackDecode a where
- fromMsgpack :: Object -> Either DecodeError a
- class MissingKey a where
- missingKey :: String -> Map String Object -> Either FieldError a
- class MsgpackEncode a where
- decodeIncompatible :: Typeable a => Object -> Either DecodeError a
- incompatible :: Typeable a => Object -> Either FieldError a
- decodeError :: Typeable a => Text -> Either DecodeError a
- toDecodeError :: Typeable a => Either FieldError a -> Either DecodeError a
- renderError :: DecodeError -> Text
- data FieldError
- data DecodeError = DecodeError {
- mainType :: Text
- fieldError :: FieldError
- decodeFractional :: (Read a, Fractional a, Typeable a) => Object -> Either DecodeError a
- fractionalField :: (Read a, Typeable a, Fractional a) => Object -> Either FieldError a
- decodeIntegral :: (Read a, Integral a, Typeable a) => Object -> Either DecodeError a
- integralField :: (Read a, Integral a, Typeable a) => Object -> Either FieldError a
- readField :: (Read a, Typeable a) => String -> Either FieldError a
- decodeUtf8Lenient :: (Typeable a, ConvertUtf8 a ByteString) => Object -> Either DecodeError a
- decodeByteString :: Typeable a => (ByteString -> Either FieldError a) -> Object -> Either DecodeError a
- decodeString :: (Typeable a, IsString a) => Object -> Either DecodeError a
- stringField :: (Typeable a, IsString a) => Object -> Either FieldError a
- byteStringField :: Typeable a => (ByteString -> Either FieldError a) -> Object -> Either FieldError a
- pattern MsgpackString :: String -> Object
- msgpackMap :: MsgpackMap a => a
- msgpackArray :: MsgpackArray a => a
Documentation
pattern Msgpack :: MsgpackDecode a => a -> Object #
Pattern synonym for decoding an Object
.
class MsgpackDecode a where #
Class of values that can be decoded from MessagePack Object
s.
Nothing
fromMsgpack :: Object -> Either DecodeError a #
Decode a value from a MessagePack Object
.
The default implementation uses generic derivation.
Instances
class MissingKey a where #
This class decides what to return when a key in an ObjectMap
is missing for a corresponding record field.
Primarily used for Maybe
fields, since they should decode to Nothing
when the key is absent.
missingKey :: String -> Map String Object -> Either FieldError a #
Return a fallback value for a missing key in an ObjectMap
.
Instances
MissingKey a | |
Defined in Ribosome.Host.Class.Msgpack.Decode missingKey :: String -> Map String Object -> Either FieldError a # | |
MissingKey (Maybe a) | |
Defined in Ribosome.Host.Class.Msgpack.Decode missingKey :: String -> Map String Object -> Either FieldError (Maybe a) # |
class MsgpackEncode a where #
Class of values that can be encoded to MessagePack Object
s.
Nothing
Encode a value to MessagePack.
The default implementation uses generic derivation.
Instances
decodeIncompatible :: Typeable a => Object -> Either DecodeError a #
Create a DecodeError
for a type when the Object
constructor is wrong, using Typeable
to obtain the type name.
incompatible :: Typeable a => Object -> Either FieldError a #
Create a FieldError
for a field when the Object
constructor is wrong, using Typeable
to obtain the type name.
decodeError :: Typeable a => Text -> Either DecodeError a #
Create a
from a Left
DecodeError
Text
by adding the type name via Typeable
.
toDecodeError :: Typeable a => Either FieldError a -> Either DecodeError a #
Convert a FieldError
in a Left
to a DecodeError
by adding the type name via Typeable
.
renderError :: DecodeError -> Text #
Create a user-friendly message for a DecodeError
.
data FieldError #
A decoding error in a field of a larger type.
May be nested arbitrarily deep.
Instances
data DecodeError #
A messagepack decoding error.
DecodeError | |
|
Instances
decodeFractional :: (Read a, Fractional a, Typeable a) => Object -> Either DecodeError a #
Decode a numeric or string type using Fractional
or Read
.
fractionalField :: (Read a, Typeable a, Fractional a) => Object -> Either FieldError a #
Decode a numeric or string field using Fractional
or Read
.
decodeIntegral :: (Read a, Integral a, Typeable a) => Object -> Either DecodeError a #
integralField :: (Read a, Integral a, Typeable a) => Object -> Either FieldError a #
readField :: (Read a, Typeable a) => String -> Either FieldError a #
Decode a ByteString
field using Read
.
decodeUtf8Lenient :: (Typeable a, ConvertUtf8 a ByteString) => Object -> Either DecodeError a #
Decode a ByteString
type using ConvertUtf8
.
decodeByteString :: Typeable a => (ByteString -> Either FieldError a) -> Object -> Either DecodeError a #
Decode a ByteString
type using IsString
.
decodeString :: (Typeable a, IsString a) => Object -> Either DecodeError a #
Decode a ByteString
type using IsString
.
stringField :: (Typeable a, IsString a) => Object -> Either FieldError a #
Decode a ByteString
field using IsString
.
byteStringField :: Typeable a => (ByteString -> Either FieldError a) -> Object -> Either FieldError a #
Call the continuation if the Object
contains a ByteString
, or an error otherwise.
msgpackMap :: MsgpackMap a => a #
Encode an arbitrary number of heterogeneously typed values to a single MessagePack map. This function is variadic, meaning that it takes an arbitrary number of arguments:
>>>
msgpackMap ("number", 5 :: Int) ("status", "error" :: Text) ("intensity", 3.14 :: Double) :: Object
ObjectMap (Map.fromList [(ObjectString "number", ObjectInt 5), (ObjectString "status", ObjectString "error"), (ObjectString "intensity", ObjectFloat 3.14)])
This avoids the need to call toMsgpack
once for each element and then once more for the map.
msgpackArray :: MsgpackArray a => a #
Encode an arbitrary number of heterogeneously typed values to a single MessagePack array. This function is variadic, meaning that it takes an arbitrary number of arguments:
>>>
msgpackArray (5 :: Int) ("error" :: Text) (3.14 :: Double) :: Object
ObjectArray [ObjectInt 5, ObjectString "error", ObjectFloat 3.14]
This avoids the need to call toMsgpack
once for each element and then once more for the array.