Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Schema
- = SSchema !Word8
- | SUnit
- | SBool
- | SChar
- | SWord8
- | SWord16
- | SWord32
- | SWord64
- | SInt8
- | SInt16
- | SInt32
- | SInt64
- | SInteger
- | SFloat
- | SDouble
- | SBytes
- | SText
- | SList !Schema
- | SArray !(VarInt Int) !Schema
- | SProduct [Schema]
- | SProductFixed [(VarInt Int, Schema)]
- | SRecord [(Text, Schema)]
- | SVariant [(Text, [Schema])]
- | SFix Schema
- | SSelf !Word8
- class Typeable a => Serialise a where
- schema :: forall proxy a. Serialise a => proxy a -> Schema
- serialise :: Serialise a => a -> ByteString
- deserialise :: Serialise a => ByteString -> Either StrategyError a
- newtype Deserialiser a = Deserialiser {
- getDeserialiser :: Plan (Decoder a)
- type Decoder = (->) ByteString
- serialiseOnly :: Serialise a => a -> ByteString
- getDecoder :: Serialise a => Schema -> Either StrategyError (Decoder a)
- getDecoderBy :: Deserialiser a -> Schema -> Either StrategyError (Decoder a)
- type Encoding = (Sum Int, Builder)
- encodeMulti :: [Encoding] -> Encoding
- newtype Plan a = Plan {}
- extractListWith :: Deserialiser a -> Deserialiser [a]
- extractField :: Serialise a => Text -> Deserialiser a
- extractFieldWith :: Typeable a => Deserialiser a -> Text -> Deserialiser a
- extractConstructor :: Serialise a => Text -> Deserialiser (Maybe a)
- extractConstructorWith :: Typeable a => Deserialiser a -> Text -> Deserialiser (Maybe a)
- newtype VarInt a = VarInt {
- getVarInt :: a
- unwrapDeserialiser :: Deserialiser a -> Schema -> Strategy (Decoder a)
- data Strategy a
- type StrategyError = Doc AnsiStyle
- class GSerialiseRecord f
- gschemaViaRecord :: forall proxy a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => proxy a -> [TypeRep] -> Schema
- gtoEncodingRecord :: (GSerialiseRecord (Rep a), Generic a) => a -> Encoding
- gdeserialiserRecord :: forall a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => Maybe a -> Deserialiser a
- class GSerialiseVariant f
- gschemaViaVariant :: forall proxy a. (GSerialiseVariant (Rep a), Typeable a, Generic a) => proxy a -> [TypeRep] -> Schema
- gtoEncodingVariant :: (GSerialiseVariant (Rep a), Generic a) => a -> Encoding
- gdeserialiserVariant :: forall a. (GSerialiseVariant (Rep a), Generic a, Typeable a) => Deserialiser a
- bootstrapSchema :: Word8 -> Either StrategyError Schema
Documentation
SSchema !Word8 | |
SUnit | |
SBool | |
SChar | |
SWord8 | |
SWord16 | |
SWord32 | |
SWord64 | |
SInt8 | |
SInt16 | |
SInt32 | |
SInt64 | |
SInteger | |
SFloat | |
SDouble | |
SBytes | |
SText | |
SList !Schema | |
SArray !(VarInt Int) !Schema | |
SProduct [Schema] | |
SProductFixed [(VarInt Int, Schema)] | |
SRecord [(Text, Schema)] | |
SVariant [(Text, [Schema])] | |
SFix Schema | binds a fixpoint |
SSelf !Word8 |
|
class Typeable a => Serialise a where Source #
Serialisable datatype
schemaVia :: Proxy a -> [TypeRep] -> Schema Source #
Obtain the schema of the datatype. [TypeRep]
is for handling recursion.
toEncoding :: a -> Encoding Source #
Serialise a value.
deserialiser :: Deserialiser a Source #
The Deserialiser
constantSize :: Proxy a -> Maybe Int Source #
If this is
, the size of Just
xtoEncoding
must be x
.
deserialiser
must not depend on this value.
schemaVia :: (Generic a, GSerialiseVariant (Rep a)) => Proxy a -> [TypeRep] -> Schema Source #
Obtain the schema of the datatype. [TypeRep]
is for handling recursion.
toEncoding :: (Generic a, GSerialiseVariant (Rep a)) => a -> Encoding Source #
Serialise a value.
deserialiser :: (Generic a, GSerialiseVariant (Rep a)) => Deserialiser a Source #
The Deserialiser
schema :: forall proxy a. Serialise a => proxy a -> Schema Source #
Obtain the schema of the datatype.
Standalone serialisation
serialise :: Serialise a => a -> ByteString Source #
Serialise a value along with its schema.
deserialise :: Serialise a => ByteString -> Either StrategyError a Source #
Deserialise a serialise
d Bytestring
.
Separate serialisation
newtype Deserialiser a Source #
Deserialiser
is a Plan
that creates a Decoder
.
Deserialiser | |
|
type Decoder = (->) ByteString Source #
serialiseOnly :: Serialise a => a -> ByteString Source #
Serialise a value without its schema.
getDecoder :: Serialise a => Schema -> Either StrategyError (Decoder a) Source #
Obtain a decoder from a schema.
getDecoderBy :: Deserialiser a -> Schema -> Either StrategyError (Decoder a) Source #
Get a decoder from a Deserialiser
and a schema.
Encoding combinators
encodeMulti :: [Encoding] -> Encoding Source #
Decoding combinators
extractListWith :: Deserialiser a -> Deserialiser [a] Source #
Extract a list or an array of values.
extractField :: Serialise a => Text -> Deserialiser a Source #
Extract a field of a record.
extractFieldWith :: Typeable a => Deserialiser a -> Text -> Deserialiser a Source #
Extract a field using the supplied Deserialiser
.
extractConstructor :: Serialise a => Text -> Deserialiser (Maybe a) Source #
extractConstructorWith :: Typeable a => Deserialiser a -> Text -> Deserialiser (Maybe a) Source #
Tries to extract a specific constructor of a variant. Useful for implementing backward-compatible deserialisers.
Variable-length quantity
Encoded in variable-length quantity.
Bounded a => Bounded (VarInt a) Source # | |
Enum a => Enum (VarInt a) Source # | |
Eq a => Eq (VarInt a) Source # | |
Integral a => Integral (VarInt a) Source # | |
Num a => Num (VarInt a) Source # | |
Ord a => Ord (VarInt a) Source # | |
Read a => Read (VarInt a) Source # | |
Real a => Real (VarInt a) Source # | |
Show a => Show (VarInt a) Source # | |
Bits a => Bits (VarInt a) Source # | |
(Typeable * a, Integral a, Bits a) => Serialise (VarInt a) Source # | |
Internal
unwrapDeserialiser :: Deserialiser a -> Schema -> Strategy (Decoder a) Source #
type StrategyError = Doc AnsiStyle Source #
Generics
class GSerialiseRecord f Source #
recordSchema, recordEncoder, recordDecoder
GSerialiseRecord k f => GSerialiseRecord k (D1 k c f) Source # | |
GSerialiseRecord k f => GSerialiseRecord k (C1 k c f) Source # | |
(GSerialiseRecord k f, GSerialiseRecord k g) => GSerialiseRecord k ((:*:) k f g) Source # | |
(Serialise a, Selector Meta c) => GSerialiseRecord k (S1 k c (K1 k i a)) Source # | |
gschemaViaRecord :: forall proxy a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => proxy a -> [TypeRep] -> Schema Source #
Generic implementation of schemaVia
for a record.
gtoEncodingRecord :: (GSerialiseRecord (Rep a), Generic a) => a -> Encoding Source #
Generic implementation of toEncoding
for a record.
:: (GSerialiseRecord (Rep a), Generic a, Typeable a) | |
=> Maybe a | default value (optional) |
-> Deserialiser a |
Generic implementation of deserialiser
for a record.
class GSerialiseVariant f Source #
variantCount, variantSchema, variantEncoder, variantDecoder
GSerialiseVariant k f => GSerialiseVariant k (D1 k c f) Source # | |
GSerialiseVariant k f => GSerialiseVariant k (S1 k c f) Source # | |
(GSerialiseProduct k f, Constructor Meta c) => GSerialiseVariant k (C1 k c f) Source # | |
(GSerialiseVariant k f, GSerialiseVariant k g) => GSerialiseVariant k ((:+:) k f g) Source # | |
gschemaViaVariant :: forall proxy a. (GSerialiseVariant (Rep a), Typeable a, Generic a) => proxy a -> [TypeRep] -> Schema Source #
Generic implementation of schemaVia
for an ADT.
gtoEncodingVariant :: (GSerialiseVariant (Rep a), Generic a) => a -> Encoding Source #
Generic implementation of toEncoding
for an ADT.
gdeserialiserVariant :: forall a. (GSerialiseVariant (Rep a), Generic a, Typeable a) => Deserialiser a Source #
Generic implementation of deserialiser
for an ADT.