Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Assoc a = Assoc {
- unAssoc :: a
- data Object
- class MessagePack a where
- toObject :: Config -> a -> Object
- fromObjectWith :: (Applicative m, Monad m, MonadValidate DecodeError m) => Config -> Object -> m a
- data Config
- defaultConfig :: Config
- data DecodeError
- decodeError :: String -> DecodeError
- errorMessages :: DecodeError -> [String]
- fromObject :: (MonadFail m, MessagePack a) => Object -> m a
Documentation
Instances
Eq a => Eq (Assoc a) Source # | |
Ord a => Ord (Assoc a) Source # | |
Defined in Data.MessagePack.Types.Assoc | |
Read a => Read (Assoc a) Source # | |
Show a => Show (Assoc a) Source # | |
Arbitrary a => Arbitrary (Assoc a) Source # | |
NFData a => NFData (Assoc a) Source # | |
Defined in Data.MessagePack.Types.Assoc | |
(MessagePack a, MessagePack b) => MessagePack (Assoc [(a, b)]) Source # | |
Defined in Data.MessagePack.Types.Class toObject :: Config -> Assoc [(a, b)] -> Object Source # fromObjectWith :: (Applicative m, Monad m, MonadValidate DecodeError m) => Config -> Object -> m (Assoc [(a, b)]) Source # |
Object Representation of MessagePack data.
ObjectNil | represents nil |
ObjectBool Bool | represents true or false |
ObjectInt Int64 | represents a negative integer |
ObjectWord Word64 | represents a positive integer |
ObjectFloat Float | represents a floating point number |
ObjectDouble Double | represents a floating point number |
ObjectStr Text | extending Raw type represents a UTF-8 string |
ObjectBin ByteString | extending Raw type represents a byte array |
ObjectArray (Vector Object) | represents a sequence of objects |
ObjectMap (Vector (Object, Object)) | represents key-value pairs of objects |
ObjectExt Word8 ByteString | represents a tuple of an integer and a byte array where the integer represents type information and the byte array represents data. |
Instances
class MessagePack a where Source #
Nothing
toObject :: Config -> a -> Object Source #
fromObjectWith :: (Applicative m, Monad m, MonadValidate DecodeError m) => Config -> Object -> m a Source #
default fromObjectWith :: (Applicative m, Monad m, MonadValidate DecodeError m, Generic a, GMessagePack (Rep a)) => Config -> Object -> m a Source #
Instances
data DecodeError Source #
Instances
Show DecodeError Source # | |
Defined in Data.MessagePack.Types.DecodeError showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # | |
IsString DecodeError Source # | |
Defined in Data.MessagePack.Types.DecodeError fromString :: String -> DecodeError # | |
Semigroup DecodeError Source # | |
Defined in Data.MessagePack.Types.DecodeError (<>) :: DecodeError -> DecodeError -> DecodeError # sconcat :: NonEmpty DecodeError -> DecodeError # stimes :: Integral b => b -> DecodeError -> DecodeError # | |
MonadValidate DecodeError ReadPrec Source # | |
Defined in Data.MessagePack.Types.DecodeError |
decodeError :: String -> DecodeError Source #
errorMessages :: DecodeError -> [String] Source #
fromObject :: (MonadFail m, MessagePack a) => Object -> m a Source #
Similar to fromObjectWith
defaultConfig
but returns the result in
a MonadFail
.