Copyright | (c) Fumiaki Kinoshita 2019 |
---|---|
License | BSD3 |
Stability | Provisional |
Safe Haskell | None |
Language | Haskell2010 |
Codec.Winery
Contents
Description
Maintainer : Fumiaki Kinoshita fumiexcel@gmail.com
Synopsis
- type Schema = SchemaP Int
- data SchemaP a
- = SFix !(SchemaP a)
- | SVar !a
- | SVector !(SchemaP a)
- | SProduct !(Vector (SchemaP a))
- | SRecord !(Vector (Text, SchemaP a))
- | SVariant !(Vector (Text, SchemaP a))
- | SBool
- | SChar
- | SWord8
- | SWord16
- | SWord32
- | SWord64
- | SInt8
- | SInt16
- | SInt32
- | SInt64
- | SInteger
- | SFloat
- | SDouble
- | SBytes
- | SText
- | SUTCTime
- | STag !Tag !(SchemaP a)
- | SLet !(SchemaP a) !(SchemaP a)
- data Tag
- class Typeable a => Serialise a where
- schemaGen :: Proxy a -> SchemaGen Schema
- toBuilder :: a -> Builder
- extractor :: Extractor a
- decodeCurrent :: Decoder a
- bundleSerialise :: BundleSerialise a
- testSerialise :: forall a. (Eq a, Show a, Serialise a) => a -> Property
- data DecodeException
- schema :: forall proxy a. Serialise a => proxy a -> Schema
- toBuilderWithSchema :: forall a. Serialise a => a -> Builder
- serialise :: Serialise a => a -> ByteString
- deserialise :: Serialise a => ByteString -> Either WineryException a
- deserialiseBy :: Extractor a -> ByteString -> Either WineryException a
- deserialiseTerm :: ByteString -> Either WineryException (Schema, Term)
- splitSchema :: ByteString -> Either WineryException (Schema, ByteString)
- writeFileSerialise :: Serialise a => FilePath -> a -> IO ()
- readFileDeserialise :: Serialise a => FilePath -> IO a
- serialiseSchema :: Schema -> ByteString
- schemaToBuilder :: Schema -> Builder
- deserialiseSchema :: ByteString -> Either WineryException Schema
- newtype Extractor a = Extractor {
- getExtractor :: Plan (Term -> a)
- unwrapExtractor :: Extractor a -> Schema -> Strategy' (Term -> a)
- data Decoder a
- evalDecoder :: Decoder a -> ByteString -> a
- serialiseOnly :: Serialise a => a -> ByteString
- getDecoder :: forall a. Serialise a => Schema -> Either WineryException (Decoder a)
- getDecoderBy :: Extractor a -> Schema -> Either WineryException (Decoder a)
- data Term
- = TBool !Bool
- | TChar !Char
- | TWord8 !Word8
- | TWord16 !Word16
- | TWord32 !Word32
- | TWord64 !Word64
- | TInt8 !Int8
- | TInt16 !Int16
- | TInt32 !Int32
- | TInt64 !Int64
- | TInteger !Integer
- | TFloat !Float
- | TDouble !Double
- | TBytes !ByteString
- | TText !Text
- | TUTCTime !UTCTime
- | TVector !(Vector Term)
- | TProduct !(Vector Term)
- | TRecord !(Vector (Text, Term))
- | TVariant !Int !Text Term
- encodeTerm :: Term -> Builder
- newtype Subextractor a = Subextractor {
- unSubextractor :: Extractor a
- buildExtractor :: Typeable a => Subextractor a -> Extractor a
- extractListBy :: Typeable a => Extractor a -> Extractor (Vector a)
- extractField :: Serialise a => Text -> Subextractor a
- extractFieldBy :: Extractor a -> Text -> Subextractor a
- extractConstructor :: Serialise a => (Text, a -> r) -> Subextractor r -> Subextractor r
- extractConstructorBy :: Typeable a => (Extractor a, Text, a -> r) -> Subextractor r -> Subextractor r
- extractVoid :: Typeable r => Subextractor r
- data ExtractException = InvalidTerm !Term
- newtype VarInt a = VarInt {
- getVarInt :: a
- data WineryException
- = UnexpectedSchema !(Doc AnsiStyle) !(Doc AnsiStyle) !Schema
- | FieldNotFound !(Doc AnsiStyle) !Text ![Text]
- | TypeMismatch !Int !TypeRep !TypeRep
- | ProductTooSmall !Int
- | UnboundVariable !Int
- | EmptyInput
- | WineryMessage !(Doc AnsiStyle)
- | UnsupportedSchemaVersion !Word8
- prettyWineryException :: WineryException -> Doc AnsiStyle
- unexpectedSchema :: forall f a. Serialise a => Doc AnsiStyle -> Schema -> Strategy' (f a)
- data SchemaGen a
- getSchema :: forall proxy a. Serialise a => proxy a -> SchemaGen Schema
- newtype Plan a = Plan {}
- mkPlan :: forall a. Typeable a => (Schema -> Strategy' (Term -> a)) -> Plan (Term -> a)
- newtype WineryRecord a = WineryRecord {
- unWineryRecord :: a
- newtype WineryVariant a = WineryVariant {
- unWineryVariant :: a
- newtype WineryProduct a = WineryProduct {
- unWineryProduct :: a
- class GSerialiseRecord f
- 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
- gdecodeCurrentRecord :: (GDecodeProduct (Rep a), Generic a) => Decoder a
- class GSerialiseVariant f
- class GConstructorCount f
- class GEncodeVariant f
- class GDecodeVariant f
- 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 :: forall a. (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
- class GEncodeProduct f
- class GDecodeProduct f
- 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
- decodeCurrentDefault :: forall a. Serialise a => Decoder 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
- bootstrapSchema :: Word8 -> Either WineryException Schema
Documentation
type Schema = SchemaP Int Source #
A schema preserves structure of a datatype, allowing users to inspect the data regardless of the current implementation.
"Yeah, it’s just a memento. Just, you know, from the first time we met."
The basic schema datatype
Constructors
SFix !(SchemaP a) | binds a fixpoint |
SVar !a |
|
SVector !(SchemaP a) | |
SProduct !(Vector (SchemaP a)) | |
SRecord !(Vector (Text, SchemaP a)) | |
SVariant !(Vector (Text, SchemaP a)) | |
SBool | |
SChar | |
SWord8 | |
SWord16 | |
SWord32 | |
SWord64 | |
SInt8 | |
SInt16 | |
SInt32 | |
SInt64 | |
SInteger | |
SFloat | |
SDouble | |
SBytes | |
SText | |
SUTCTime | nanoseconds from POSIX epoch |
STag !Tag !(SchemaP a) | |
SLet !(SchemaP a) !(SchemaP a) |
Instances
Tag is an extra value that can be attached to a schema.
Instances
IsList Tag Source # | |
Eq Tag Source # | |
Read Tag Source # | |
Show Tag Source # | |
IsString Tag Source # | |
Defined in Codec.Winery.Base Methods fromString :: String -> Tag # | |
Generic Tag Source # | |
Pretty Tag Source # | |
Defined in Codec.Winery.Base | |
Serialise Tag Source # | |
type Rep Tag Source # | |
Defined in Codec.Winery.Base type Rep Tag = D1 (MetaData "Tag" "Codec.Winery.Base" "winery-1.1.3-1nbpufM5bHiLQUUGyeG9nl" False) (C1 (MetaCons "TagInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: (C1 (MetaCons "TagStr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "TagList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Tag])))) | |
type Item Tag Source # | |
Defined in Codec.Winery.Base |
class Typeable a => Serialise a where Source #
Serialisable datatype
Minimal complete definition
schemaGen, toBuilder, extractor, decodeCurrent | bundleSerialise
Methods
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
testSerialise :: forall a. (Eq a, Show a, Serialise a) => a -> Property Source #
Check the integrity of a Serialise instance.
"No tears in the writer, no tears in the reader. No surprise in the writer, no surprise in the reader."
data DecodeException Source #
Exceptions thrown by a Decoder
Constructors
InsufficientInput | |
IntegerOverflow | |
InvalidTag |
Instances
Eq DecodeException Source # | |
Defined in Codec.Winery.Internal Methods (==) :: DecodeException -> DecodeException -> Bool # (/=) :: DecodeException -> DecodeException -> Bool # | |
Read DecodeException Source # | |
Defined in Codec.Winery.Internal Methods readsPrec :: Int -> ReadS DecodeException # readList :: ReadS [DecodeException] # | |
Show DecodeException Source # | |
Defined in Codec.Winery.Internal Methods showsPrec :: Int -> DecodeException -> ShowS # show :: DecodeException -> String # showList :: [DecodeException] -> ShowS # | |
Exception DecodeException Source # | |
Defined in Codec.Winery.Internal Methods toException :: DecodeException -> SomeException # |
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."
Standalone serialisation
toBuilderWithSchema :: forall a. Serialise a => a -> Builder Source #
Serialise a value with the schema.
serialise :: Serialise a => a -> ByteString Source #
Serialise a value along with its schema.
"Write the vision, and make it plain upon tables, that he may run that readeth it."
deserialise :: Serialise a => ByteString -> Either WineryException a Source #
Deserialise a serialise
d Bytestring
.
"Old wood to burn! Old wine to drink! Old friends to trust! Old authors to read!"
deserialiseBy :: Extractor a -> ByteString -> Either WineryException a Source #
Deserialise a serialise
d Bytestring
using an Extractor
.
deserialiseTerm :: ByteString -> Either WineryException (Schema, Term) Source #
Deserialise a serialise
d Bytestring
.
splitSchema :: ByteString -> Either WineryException (Schema, ByteString) Source #
Split a Schema
from a ByteString
.
writeFileSerialise :: Serialise a => FilePath -> a -> IO () Source #
serialise
then write it to a file.
readFileDeserialise :: Serialise a => FilePath -> IO a Source #
Deserialise a file. Throws WineryException
Separate serialisation
serialiseSchema :: Schema -> ByteString Source #
Serialise a schema (prefix with the version number only).
schemaToBuilder :: Schema -> Builder Source #
deserialiseSchema :: ByteString -> Either WineryException Schema Source #
Deserialise a schema.
Extractor
is a Plan
that creates a function to extract a value from Term.
The Applicative
instance can be used to build a user-defined extractor.
This is also Alternative
, meaning that fallback plans may be added.
"Don't get set into one form, adapt it and build your own, and let it grow, be like water."
Constructors
Extractor | |
Fields
|
The Decoder monad
evalDecoder :: Decoder a -> ByteString -> a Source #
Run a Decoder
serialiseOnly :: Serialise a => a -> ByteString Source #
Serialise a value without its schema.
"Any unsaved progress will be lost."
getDecoder :: forall a. Serialise a => Schema -> Either WineryException (Decoder a) Source #
Obtain a decoder from a schema.
"A reader lives a thousand lives before he dies... The man who never reads lives only one."
getDecoderBy :: Extractor a -> Schema -> Either WineryException (Decoder a) Source #
Get a decoder from a Extractor
and a schema.
Decoding combinators
Common representation for any winery data. Handy for prettyprinting winery-serialised data.
Constructors
TBool !Bool | |
TChar !Char | |
TWord8 !Word8 | |
TWord16 !Word16 | |
TWord32 !Word32 | |
TWord64 !Word64 | |
TInt8 !Int8 | |
TInt16 !Int16 | |
TInt32 !Int32 | |
TInt64 !Int64 | |
TInteger !Integer | |
TFloat !Float | |
TDouble !Double | |
TBytes !ByteString | |
TText !Text | |
TUTCTime !UTCTime | |
TVector !(Vector Term) | |
TProduct !(Vector Term) | |
TRecord !(Vector (Text, Term)) | |
TVariant !Int !Text Term |
encodeTerm :: Term -> Builder Source #
newtype Subextractor a Source #
An extractor for individual fields. This distinction is required for handling recursions correctly.
Recommended extension: ApplicativeDo
Constructors
Subextractor | |
Fields
|
Instances
Functor Subextractor Source # | |
Defined in Codec.Winery Methods fmap :: (a -> b) -> Subextractor a -> Subextractor b # (<$) :: a -> Subextractor b -> Subextractor a # | |
Applicative Subextractor Source # | |
Defined in Codec.Winery Methods 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 Methods empty :: Subextractor a # (<|>) :: Subextractor a -> Subextractor a -> Subextractor a # some :: Subextractor a -> Subextractor [a] # many :: Subextractor a -> Subextractor [a] # |
buildExtractor :: Typeable a => Subextractor a -> Extractor a Source #
Build an extractor from a Subextractor
.
extractListBy :: Typeable a => Extractor a -> Extractor (Vector a) Source #
Extract a list or an array of values.
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
.
extractConstructor :: Serialise a => (Text, a -> r) -> Subextractor r -> Subextractor r infixr 1 Source #
Tries to match on a constructor. If it doesn't match (or constructor doesn't exist at all), leave it to the successor.
extractor = (Just, Just)extractConstructor
(Nothing, () -> Nothing)extractConstructor
extractVoid
extractConstructorBy :: Typeable a => (Extractor a, Text, a -> r) -> Subextractor r -> Subextractor r infixr 1 Source #
Tries to extract a specific constructor of a variant. Useful for implementing backward-compatible extractors.
extractVoid :: Typeable r => Subextractor r Source #
No constructors remaining.
data ExtractException Source #
This may be thrown if illegal Term
is passed to an extractor.
Constructors
InvalidTerm !Term |
Instances
Show ExtractException Source # | |
Defined in Codec.Winery.Base Methods showsPrec :: Int -> ExtractException -> ShowS # show :: ExtractException -> String # showList :: [ExtractException] -> ShowS # | |
Exception ExtractException Source # | |
Defined in Codec.Winery.Base Methods toException :: ExtractException -> SomeException # |
Variable-length quantity
Encoded in variable-length quantity.
Instances
Internal
data WineryException Source #
Exceptions thrown when by an extractor
Constructors
Instances
Show WineryException Source # | |
Defined in Codec.Winery.Base Methods showsPrec :: Int -> WineryException -> ShowS # show :: WineryException -> String # showList :: [WineryException] -> ShowS # | |
IsString WineryException Source # | |
Defined in Codec.Winery.Base Methods fromString :: String -> WineryException # | |
Exception WineryException Source # | |
Defined in Codec.Winery.Base Methods toException :: WineryException -> SomeException # |
prettyWineryException :: WineryException -> Doc AnsiStyle Source #
Pretty-print WineryException
Plan is a monad for computations which interpret Schema
.
mkPlan :: forall a. Typeable a => (Schema -> Strategy' (Term -> a)) -> Plan (Term -> a) Source #
Construct a plan, expanding fixpoints and let bindings.
DerivingVia
newtype WineryRecord a Source #
The Serialise
instance is generically defined for records.
"Remember thee! Yea, from the table of my memory I'll wipe away all trivial fond records."
Constructors
WineryRecord | |
Fields
|
Instances
(GEncodeProduct (Rep a), GSerialiseRecord (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => Serialise (WineryRecord a) Source # | |
Defined in Codec.Winery Methods schemaGen :: Proxy (WineryRecord a) -> SchemaGen Schema Source # toBuilder :: WineryRecord a -> Builder Source # extractor :: Extractor (WineryRecord a) Source # decodeCurrent :: Decoder (WineryRecord a) Source # bundleSerialise :: BundleSerialise (WineryRecord a) Source # |
newtype WineryVariant a Source #
The Serialise
instance is generically defined for variants.
"The one so like the other as could not be distinguish'd but by names."
Constructors
WineryVariant | |
Fields
|
Instances
(GConstructorCount (Rep a), GSerialiseVariant (Rep a), GEncodeVariant (Rep a), GDecodeVariant (Rep a), Generic a, Typeable a) => Serialise (WineryVariant a) Source # | |
Defined in Codec.Winery Methods schemaGen :: Proxy (WineryVariant a) -> SchemaGen Schema Source # toBuilder :: WineryVariant a -> Builder Source # extractor :: Extractor (WineryVariant a) Source # decodeCurrent :: Decoder (WineryVariant a) Source # bundleSerialise :: BundleSerialise (WineryVariant a) Source # |
newtype WineryProduct a Source #
Serialise a value as a product (omits field names).
"I get ideas about what's essential when packing my suitcase."
Constructors
WineryProduct | |
Fields
|
Instances
(GEncodeProduct (Rep a), GSerialiseProduct (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => Serialise (WineryProduct a) Source # | |
Defined in Codec.Winery Methods schemaGen :: Proxy (WineryProduct a) -> SchemaGen Schema Source # toBuilder :: WineryProduct a -> Builder Source # extractor :: Extractor (WineryProduct a) Source # decodeCurrent :: Decoder (WineryProduct a) Source # bundleSerialise :: BundleSerialise (WineryProduct a) Source # |
Generic implementations (for old GHC / custom instances)
class GSerialiseRecord f Source #
Minimal complete definition
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 |
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.
Arguments
:: (GSerialiseRecord (Rep a), Generic a, Typeable a) | |
=> Maybe a | default value (optional) |
-> Extractor a |
Generic implementation of extractor
for a record.
gdecodeCurrentRecord :: (GDecodeProduct (Rep a), Generic a) => Decoder a Source #
Synonym for gdecodeCurrentProduct
class GSerialiseVariant f Source #
Minimal complete definition
Instances
GSerialiseVariant f => GSerialiseVariant (D1 c f :: k -> Type) Source # | |
(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 # | |
class GConstructorCount f Source #
Minimal complete definition
Instances
GConstructorCount f => GConstructorCount (D1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods variantCount :: proxy (D1 i f) -> Int Source # | |
GConstructorCount (C1 i f :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods variantCount :: proxy (C1 i f) -> Int Source # | |
(GConstructorCount f, GConstructorCount g) => GConstructorCount (f :+: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods variantCount :: proxy (f :+: g) -> Int Source # |
class GEncodeVariant f Source #
Minimal complete definition
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 GDecodeVariant f Source #
Minimal complete definition
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 |
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 :: forall a. (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 #
class GEncodeProduct f Source #
Encode all the fields
Minimal complete definition
Instances
GEncodeProduct (U1 :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods productEncoder :: U1 x -> Builder Source # | |
GEncodeProduct f => GEncodeProduct (D1 c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods productEncoder :: D1 c f x -> Builder Source # | |
GEncodeProduct f => GEncodeProduct (C1 c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods productEncoder :: 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 Methods productEncoder :: (f :*: g) x -> Builder Source # |
class GDecodeProduct f Source #
Minimal complete definition
Instances
GDecodeProduct (U1 :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods productDecoder :: Decoder (U1 x) Source # | |
(GDecodeProduct f, GDecodeProduct g) => GDecodeProduct (f :*: g :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods productDecoder :: Decoder ((f :*: g) x) Source # | |
Serialise a => GDecodeProduct (K1 i a :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods productDecoder :: Decoder (K1 i a x) Source # | |
GDecodeProduct f => GDecodeProduct (M1 i c f :: k -> Type) Source # | |
Defined in Codec.Winery.Class Methods productDecoder :: Decoder (M1 i c f x) Source # |
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.
decodeCurrentDefault :: forall a. Serialise a => Decoder a Source #
decodeCurrent
in terms of extractor
; note that it's very slow.
Bundles
data BundleSerialise a Source #
A bundle of Serialise
methods
Constructors
BundleSerialise | |
Fields
|
bundleRecord :: (GEncodeProduct (Rep a), GSerialiseRecord (Rep a), GDecodeProduct (Rep a), Generic a, Typeable a) => (Extractor a -> Extractor a) -> BundleSerialise a Source #
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 #
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 #
A bundle of generic implementations for variants
Preset schema
bootstrapSchema :: Word8 -> Either WineryException Schema Source #
Obtain the schema of the schema corresponding to the specified version.