Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Typeable a => Serialise a where
- schemaGen :: Proxy a -> SchemaGen Schema
- toBuilder :: a -> Builder
- extractor :: Extractor a
- decodeCurrent :: Decoder a
- bundleSerialise :: BundleSerialise a
- newtype VarInt a = VarInt {
- getVarInt :: a
- data BundleSerialise a = BundleSerialise {
- bundleSchemaGen :: Proxy a -> SchemaGen Schema
- bundleToBuilder :: a -> Builder
- bundleExtractor :: Extractor a
- bundleDecodeCurrent :: Decoder a
- bundleRecord :: (GEncodeProduct (Rep a), GSerialiseRecord (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => (Extractor a -> Extractor a) -> BundleSerialise a
- bundleRecordDefault :: (GEncodeProduct (Rep a), GSerialiseRecord (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => a -> (Extractor a -> Extractor a) -> BundleSerialise a
- bundleVariant :: (GSerialiseVariant (Rep a), GConstructorCount (Rep a), GEncodeVariant (Rep a), GDecodeVariant (Rep a), Generic a, Typeable a) => (Extractor a -> Extractor a) -> BundleSerialise a
- getSchema :: forall proxy a. Serialise a => proxy a -> SchemaGen Schema
- schema :: forall proxy a. Serialise a => proxy a -> Schema
- unexpectedSchema :: forall f a. Serialise a => Schema -> Strategy' (f a)
- mkExtractor :: forall a. Typeable a => (Schema -> Strategy' (Term -> a)) -> Extractor a
- extractListBy :: Typeable a => Extractor a -> Extractor (Vector a)
- buildVariantExtractor :: (Generic a, Typeable a) => HashMap Text (Extractor a) -> Extractor a
- gschemaGenRecord :: forall proxy a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => proxy a -> SchemaGen Schema
- gtoBuilderRecord :: (GEncodeProduct (Rep a), Generic a) => a -> Builder
- gextractorRecord :: forall a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => Maybe a -> Extractor a
- extractorRecord' :: GSerialiseRecord f => Maybe (f x) -> Schema -> Strategy' (Term -> f x)
- gdecodeCurrentRecord :: (GDecodeProduct (Rep a), Generic a) => Decoder a
- class GEncodeProduct f where
- productEncoder :: f x -> Builder
- class GDecodeProduct f where
- productDecoder :: Decoder (f x)
- class GSerialiseRecord f where
- recordSchema :: proxy f -> SchemaGen [(Text, Schema)]
- recordExtractor :: Maybe (f x) -> TransFusion (FieldDecoder Text) ((->) Term) (Term -> f x)
- class GSerialiseProduct f where
- productSchema :: proxy f -> SchemaGen [Schema]
- productExtractor :: Compose (State Int) (TransFusion (FieldDecoder Int) ((->) Term)) (Term -> f x)
- gschemaGenProduct :: forall proxy a. (Generic a, GSerialiseProduct (Rep a)) => proxy a -> SchemaGen Schema
- gtoBuilderProduct :: (Generic a, GEncodeProduct (Rep a)) => a -> Builder
- gextractorProduct :: forall a. (GSerialiseProduct (Rep a), Generic a, Typeable a) => Extractor a
- gdecodeCurrentProduct :: forall a. (GDecodeProduct (Rep a), Generic a) => Decoder a
- extractorProduct' :: GSerialiseProduct f => Schema -> Strategy' (Term -> f x)
- class GConstructorCount f where
- variantCount :: proxy f -> Int
- class GDecodeVariant f where
- variantDecoder :: Int -> Int -> Decoder (f x)
- class GEncodeVariant f where
- variantEncoder :: Int -> Int -> f x -> Builder
- class GSerialiseVariant f where
- variantSchema :: proxy f -> SchemaGen [(Text, Schema)]
- variantExtractor :: HashMap Text (Extractor (f x))
- gschemaGenVariant :: forall proxy a. (GSerialiseVariant (Rep a), Typeable a, Generic a) => proxy a -> SchemaGen Schema
- gtoBuilderVariant :: forall a. (GConstructorCount (Rep a), GEncodeVariant (Rep a), Generic a) => a -> Builder
- gextractorVariant :: (GSerialiseVariant (Rep a), Generic a, Typeable a) => Extractor a
- gdecodeCurrentVariant :: forall a. (GConstructorCount (Rep a), GEncodeVariant (Rep a), GDecodeVariant (Rep a), Generic a) => Decoder a
- gvariantExtractors :: (GSerialiseVariant (Rep a), Generic a) => HashMap Text (Extractor a)
- newtype Subextractor a = Subextractor {
- unSubextractor :: Extractor a
- extractField :: Serialise a => Text -> Subextractor a
- extractFieldBy :: Extractor a -> Text -> Subextractor a
- buildExtractor :: Typeable a => Subextractor a -> Extractor a
- buildRecordExtractor :: (Typeable b, TraversableB b) => b Subextractor -> Extractor (b Identity)
- bextractors :: forall b. (ConstraintsB b, AllB Serialise b, FieldNamesB b) => b Subextractor
- buildRecordExtractorF :: (Typeable b, Typeable h, TraversableB b) => b (Compose Subextractor h) -> Extractor (b h)
- bextractorsF :: forall b h. (ConstraintsB b, AllBF Serialise h b, FieldNamesB b) => b (Compose Subextractor h)
Documentation
class Typeable a => Serialise a where Source #
Serialisable datatype
schemaGen :: Proxy a -> SchemaGen Schema Source #
Obtain the schema of the datatype.
toBuilder :: a -> Builder Source #
Serialise a value.
extractor :: Extractor a Source #
A value of 'Extractor a' interprets a schema and builds a function from
Term
to a
. This must be equivalent to decodeCurrent
when the schema
is the current one.
If
returns a function, the function must return a
non-bottom for any extractor
sTerm
returns.decodeTerm
s
It must not return a function if an unsupported schema is supplied.
getDecoderBy extractor (schema (Proxy
a)) must be
Right d
where
d@ is equivalent to decodeCurrent
.
decodeCurrent :: Decoder a Source #
Decode a value with the current schema.
bundleSerialise :: BundleSerialise a Source #
Instead of the four methods above, you can supply a bundle.
Instances
Encoded in variable-length quantity.
Instances
data BundleSerialise a Source #
A bundle of Serialise
methods
BundleSerialise | |
|
bundleRecord :: (GEncodeProduct (Rep a), GSerialiseRecord (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => (Extractor a -> Extractor a) -> BundleSerialise a Source #
Deprecated: Use bundleVia instead
A bundle of generic implementations for records
bundleRecordDefault :: (GEncodeProduct (Rep a), GSerialiseRecord (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => a -> (Extractor a -> Extractor a) -> BundleSerialise a Source #
Deprecated: Use bundleVia instead
A bundle of generic implementations for records, with a default value
bundleVariant :: (GSerialiseVariant (Rep a), GConstructorCount (Rep a), GEncodeVariant (Rep a), GDecodeVariant (Rep a), Generic a, Typeable a) => (Extractor a -> Extractor a) -> BundleSerialise a Source #
Deprecated: Use bundleVia instead
A bundle of generic implementations for variants
schema :: forall proxy a. Serialise a => proxy a -> Schema Source #
Obtain the schema of the datatype.
"Tell me what you drink, and I will tell you what you are."
extractListBy :: Typeable a => Extractor a -> Extractor (Vector a) Source #
Extract a list or an array of values.
buildVariantExtractor :: (Generic a, Typeable a) => HashMap Text (Extractor a) -> Extractor a Source #
gschemaGenRecord :: forall proxy a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => proxy a -> SchemaGen Schema Source #
Generic implementation of schemaGen
for a record.
gtoBuilderRecord :: (GEncodeProduct (Rep a), Generic a) => a -> Builder Source #
Generic implementation of toBuilder
for a record.
:: forall a. (GSerialiseRecord (Rep a), Generic a, Typeable a) | |
=> Maybe a | default value (optional) |
-> Extractor a |
Generic implementation of extractor
for a record.
:: GSerialiseRecord f | |
=> Maybe (f x) | default value (optional) |
-> Schema | |
-> Strategy' (Term -> f x) |
Generic implementation of extractor
for a record.
gdecodeCurrentRecord :: (GDecodeProduct (Rep a), Generic a) => Decoder a Source #
Synonym for gdecodeCurrentProduct
class GEncodeProduct f where Source #
Encode all the fields
productEncoder :: f x -> Builder Source #
Instances
GEncodeProduct (U1 :: k -> Type) Source # | |
Defined in Codec.Winery.Class productEncoder :: forall (x :: k0). U1 x -> Builder Source # | |
GEncodeProduct f => GEncodeProduct (D1 c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class productEncoder :: forall (x :: k0). D1 c f x -> Builder Source # | |
GEncodeProduct f => GEncodeProduct (C1 c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class productEncoder :: forall (x :: k0). C1 c f x -> Builder Source # | |
Serialise a => GEncodeProduct (S1 c (K1 i a :: k -> Type) :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
(GEncodeProduct f, GEncodeProduct g) => GEncodeProduct (f :*: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class productEncoder :: forall (x :: k0). (f :*: g) x -> Builder Source # |
class GDecodeProduct f where Source #
productDecoder :: Decoder (f x) Source #
Instances
GDecodeProduct (U1 :: k -> Type) Source # | |
Defined in Codec.Winery.Class productDecoder :: forall (x :: k0). Decoder (U1 x) Source # | |
(GDecodeProduct f, GDecodeProduct g) => GDecodeProduct (f :*: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class productDecoder :: forall (x :: k0). Decoder ((f :*: g) x) Source # | |
Serialise a => GDecodeProduct (K1 i a :: k -> Type) Source # | |
Defined in Codec.Winery.Class productDecoder :: forall (x :: k0). Decoder (K1 i a x) Source # | |
GDecodeProduct f => GDecodeProduct (M1 i c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class productDecoder :: forall (x :: k0). Decoder (M1 i c f x) Source # |
class GSerialiseRecord f where Source #
recordSchema :: proxy f -> SchemaGen [(Text, Schema)] Source #
recordExtractor :: Maybe (f x) -> TransFusion (FieldDecoder Text) ((->) Term) (Term -> f x) Source #
Instances
GSerialiseRecord f => GSerialiseRecord (D1 c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
GSerialiseRecord f => GSerialiseRecord (C1 c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
(Serialise a, Selector c) => GSerialiseRecord (S1 c (K1 i a :: k -> Type) :: k -> Type) Source # | |
(GSerialiseRecord f, GSerialiseRecord g) => GSerialiseRecord (f :*: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class |
class GSerialiseProduct f where Source #
productSchema :: proxy f -> SchemaGen [Schema] Source #
productExtractor :: Compose (State Int) (TransFusion (FieldDecoder Int) ((->) Term)) (Term -> f x) Source #
Instances
GSerialiseProduct (U1 :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
(GSerialiseProduct f, GSerialiseProduct g) => GSerialiseProduct (f :*: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
Serialise a => GSerialiseProduct (K1 i a :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
GSerialiseProduct f => GSerialiseProduct (M1 i c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class |
gschemaGenProduct :: forall proxy a. (Generic a, GSerialiseProduct (Rep a)) => proxy a -> SchemaGen Schema Source #
gtoBuilderProduct :: (Generic a, GEncodeProduct (Rep a)) => a -> Builder Source #
gextractorProduct :: forall a. (GSerialiseProduct (Rep a), Generic a, Typeable a) => Extractor a Source #
Generic implementation of extractor
for a record.
gdecodeCurrentProduct :: forall a. (GDecodeProduct (Rep a), Generic a) => Decoder a Source #
Generic implementation of extractor
for a record.
extractorProduct' :: GSerialiseProduct f => Schema -> Strategy' (Term -> f x) Source #
class GConstructorCount f where Source #
variantCount :: proxy f -> Int Source #
Instances
GConstructorCount f => GConstructorCount (D1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class variantCount :: proxy (D1 i f) -> Int Source # | |
GConstructorCount (C1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class variantCount :: proxy (C1 i f) -> Int Source # | |
(GConstructorCount f, GConstructorCount g) => GConstructorCount (f :+: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class variantCount :: proxy (f :+: g) -> Int Source # |
class GDecodeVariant f where Source #
Instances
GDecodeVariant f => GDecodeVariant (D1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
GDecodeProduct f => GDecodeVariant (C1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
(GDecodeVariant f, GDecodeVariant g) => GDecodeVariant (f :+: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class |
class GEncodeVariant f where Source #
Instances
GEncodeVariant f => GEncodeVariant (D1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
GEncodeProduct f => GEncodeVariant (C1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
(GEncodeVariant f, GEncodeVariant g) => GEncodeVariant (f :+: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class |
class GSerialiseVariant f where Source #
Instances
GSerialiseVariant f => GSerialiseVariant (D1 c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class | |
(GSerialiseRecord f, KnownSymbol name) => GSerialiseVariant (C1 ('MetaCons name fixity 'True) f :: k -> Type) Source # | |
(GSerialiseProduct f, KnownSymbol name) => GSerialiseVariant (C1 ('MetaCons name fixity 'False) f :: k -> Type) Source # | |
(GSerialiseVariant f, GSerialiseVariant g) => GSerialiseVariant (f :+: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class |
gschemaGenVariant :: forall proxy a. (GSerialiseVariant (Rep a), Typeable a, Generic a) => proxy a -> SchemaGen Schema Source #
Generic implementation of schemaGen
for an ADT.
gtoBuilderVariant :: forall a. (GConstructorCount (Rep a), GEncodeVariant (Rep a), Generic a) => a -> Builder Source #
Generic implementation of toBuilder
for an ADT.
gextractorVariant :: (GSerialiseVariant (Rep a), Generic a, Typeable a) => Extractor a Source #
Generic implementation of extractor
for an ADT.
gdecodeCurrentVariant :: forall a. (GConstructorCount (Rep a), GEncodeVariant (Rep a), GDecodeVariant (Rep a), Generic a) => Decoder a Source #
gvariantExtractors :: (GSerialiseVariant (Rep a), Generic a) => HashMap Text (Extractor a) Source #
Collect extractors as a HashMap
keyed by constructor names
newtype Subextractor a Source #
An extractor for individual fields. This distinction is required for handling recursions correctly.
Recommended extension: ApplicativeDo
Instances
Functor Subextractor Source # | |
Defined in Codec.Winery.Class fmap :: (a -> b) -> Subextractor a -> Subextractor b # (<$) :: a -> Subextractor b -> Subextractor a # | |
Applicative Subextractor Source # | |
Defined in Codec.Winery.Class pure :: a -> Subextractor a # (<*>) :: Subextractor (a -> b) -> Subextractor a -> Subextractor b # liftA2 :: (a -> b -> c) -> Subextractor a -> Subextractor b -> Subextractor c # (*>) :: Subextractor a -> Subextractor b -> Subextractor b # (<*) :: Subextractor a -> Subextractor b -> Subextractor a # | |
Alternative Subextractor Source # | |
Defined in Codec.Winery.Class empty :: Subextractor a # (<|>) :: Subextractor a -> Subextractor a -> Subextractor a # some :: Subextractor a -> Subextractor [a] # many :: Subextractor a -> Subextractor [a] # |
extractField :: Serialise a => Text -> Subextractor a Source #
Extract a field of a record.
extractFieldBy :: Extractor a -> Text -> Subextractor a Source #
Extract a field using the supplied Extractor
.
buildExtractor :: Typeable a => Subextractor a -> Extractor a Source #
Build an extractor from a Subextractor
.
buildRecordExtractor :: (Typeable b, TraversableB b) => b Subextractor -> Extractor (b Identity) Source #
bextractors :: forall b. (ConstraintsB b, AllB Serialise b, FieldNamesB b) => b Subextractor Source #
Collect extractors for record fields
buildRecordExtractorF :: (Typeable b, Typeable h, TraversableB b) => b (Compose Subextractor h) -> Extractor (b h) Source #
bextractorsF :: forall b h. (ConstraintsB b, AllBF Serialise h b, FieldNamesB b) => b (Compose Subextractor h) Source #
Collect extractors for record fields