Copyright | (c) Fumiaki Kinoshita 2019 |
---|---|
License | BSD3 |
Stability | Provisional |
Safe Haskell | None |
Language | Haskell2010 |
Maintainer : Fumiaki Kinoshita fumiexcel@gmail.com
The standard interface of winery serialisation library
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
- 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 ()
- serialiseSchema :: Schema -> ByteString
- deserialiseSchema :: ByteString -> Either WineryException Schema
- newtype Extractor a = Extractor {
- getExtractor :: Plan (Term -> a)
- unwrapExtractor :: Extractor a -> Schema -> Strategy' (Term -> a)
- type Decoder = State ByteString
- 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
- 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)
- 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
- class GEncodeProduct f
- gtoBuilderRecord :: (GEncodeProduct (Rep a), Generic a) => a -> Builder
- gextractorRecord :: forall a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => Maybe a -> Extractor a
- gdecodeCurrentRecord :: (GSerialiseRecord (Rep a), Generic a) => Decoder a
- class GSerialiseVariant f
- gschemaGenVariant :: forall proxy a. (GSerialiseVariant (Rep a), Typeable a, Generic a) => proxy a -> SchemaGen Schema
- gtoBuilderVariant :: (GSerialiseVariant (Rep a), Generic a) => a -> Builder
- gextractorVariant :: forall a. (GSerialiseVariant (Rep a), Generic a, Typeable a) => Extractor a
- gschemaGenProduct :: forall proxy a. (Generic a, GSerialiseProduct (Rep a)) => proxy a -> SchemaGen Schema
- gtoBuilderProduct :: (Generic a, GEncodeProduct (Rep a)) => a -> Builder
- gdecodeCurrentVariant :: (GSerialiseVariant (Rep a), Generic a) => Decoder a
- gextractorProduct :: forall a. (GSerialiseProduct (Rep a), Generic a, Typeable a) => Extractor a
- gdecodeCurrentProduct :: forall a. (GSerialiseProduct (Rep a), Generic a) => Decoder a
- bootstrapSchema :: Word8 -> 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."
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 Data.Winery.Base fromString :: String -> Tag # | |
Generic Tag Source # | |
Pretty Tag Source # | |
Defined in Data.Winery.Base | |
Serialise Tag Source # | |
type Rep Tag Source # | |
Defined in Data.Winery.Base type Rep Tag = D1 (MetaData "Tag" "Data.Winery.Base" "winery-1-Icmh3EEwZZX4DdnHtaSx4r" 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 Data.Winery.Base |
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.
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 #
Instances
Eq DecodeException Source # | |
Defined in Data.Winery.Internal (==) :: DecodeException -> DecodeException -> Bool # (/=) :: DecodeException -> DecodeException -> Bool # | |
Read DecodeException Source # | |
Defined in Data.Winery.Internal | |
Show DecodeException Source # | |
Defined in Data.Winery.Internal showsPrec :: Int -> DecodeException -> ShowS # show :: DecodeException -> String # showList :: [DecodeException] -> ShowS # | |
Exception DecodeException Source # | |
Defined in Data.Winery.Internal |
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 :: 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
.
writeFileSerialise :: Serialise a => FilePath -> a -> IO () Source #
Serialise a value along with its schema.
Separate serialisation
serialiseSchema :: Schema -> ByteString Source #
Serialise a schema.
deserialiseSchema :: ByteString -> Either WineryException Schema Source #
Serialise 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."
Extractor | |
|
type Decoder = State ByteString Source #
evalDecoder :: Decoder a -> ByteString -> a Source #
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.
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 |
newtype Subextractor a Source #
Instances
Functor Subextractor Source # | |
Defined in Data.Winery fmap :: (a -> b) -> Subextractor a -> Subextractor b # (<$) :: a -> Subextractor b -> Subextractor a # | |
Applicative Subextractor Source # | |
Defined in Data.Winery 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 Data.Winery 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 #
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 #
data ExtractException Source #
This may be thrown if illegal Term
is passed to an extractor.
Instances
Show ExtractException Source # | |
Defined in Data.Winery showsPrec :: Int -> ExtractException -> ShowS # show :: ExtractException -> String # showList :: [ExtractException] -> ShowS # | |
Exception ExtractException Source # | |
Defined in Data.Winery |
Variable-length quantity
Encoded in variable-length quantity.
Instances
Internal
data WineryException Source #
Instances
Show WineryException Source # | |
Defined in Data.Winery.Base showsPrec :: Int -> WineryException -> ShowS # show :: WineryException -> String # showList :: [WineryException] -> ShowS # | |
IsString WineryException Source # | |
Defined in Data.Winery.Base fromString :: String -> WineryException # | |
Exception WineryException Source # | |
Defined in Data.Winery.Base |
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."/
Instances
(GEncodeProduct (Rep a), GSerialiseRecord (Rep a), Generic a, Typeable a) => Serialise (WineryRecord a) Source # | |
Defined in Data.Winery schemaGen :: Proxy (WineryRecord a) -> SchemaGen Schema Source # toBuilder :: WineryRecord a -> Builder Source # extractor :: Extractor (WineryRecord a) Source # decodeCurrent :: Decoder (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."
Instances
(GSerialiseVariant (Rep a), Generic a, Typeable a) => Serialise (WineryVariant a) Source # | |
Defined in Data.Winery schemaGen :: Proxy (WineryVariant a) -> SchemaGen Schema Source # toBuilder :: WineryVariant a -> Builder Source # extractor :: Extractor (WineryVariant a) Source # decodeCurrent :: Decoder (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."
Instances
(GEncodeProduct (Rep a), GSerialiseProduct (Rep a), Generic a, Typeable a) => Serialise (WineryProduct a) Source # | |
Defined in Data.Winery schemaGen :: Proxy (WineryProduct a) -> SchemaGen Schema Source # toBuilder :: WineryProduct a -> Builder Source # extractor :: Extractor (WineryProduct a) Source # decodeCurrent :: Decoder (WineryProduct a) Source # |
Generic implementations (for old GHC / custom instances)
class GSerialiseRecord f Source #
recordSchema, recordExtractor, recordDecoder
Instances
gschemaGenRecord :: forall proxy a. (GSerialiseRecord (Rep a), Generic a, Typeable a) => proxy a -> SchemaGen Schema Source #
Generic implementation of schemaGen
for a record.
class GEncodeProduct f Source #
productEncoder
Instances
GEncodeProduct (U1 :: k -> Type) Source # | |
Defined in Data.Winery productEncoder :: U1 x -> Builder | |
GEncodeProduct f => GEncodeProduct (D1 c f :: k -> Type) Source # | |
Defined in Data.Winery productEncoder :: D1 c f x -> Builder | |
GEncodeProduct f => GEncodeProduct (C1 c f :: k -> Type) Source # | |
Defined in Data.Winery productEncoder :: C1 c f x -> Builder | |
Serialise a => GEncodeProduct (S1 c (K1 i a :: k -> Type) :: k -> Type) Source # | |
Defined in Data.Winery productEncoder :: S1 c (K1 i a) x -> Builder | |
(GEncodeProduct f, GEncodeProduct g) => GEncodeProduct (f :*: g :: k -> Type) Source # | |
Defined in Data.Winery productEncoder :: (f :*: g) x -> Builder |
gtoBuilderRecord :: (GEncodeProduct (Rep a), Generic a) => a -> Builder Source #
Generic implementation of toBuilder
for a record.
:: (GSerialiseRecord (Rep a), Generic a, Typeable a) | |
=> Maybe a | default value (optional) |
-> Extractor a |
Generic implementation of extractor
for a record.
gdecodeCurrentRecord :: (GSerialiseRecord (Rep a), Generic a) => Decoder a Source #
class GSerialiseVariant f Source #
variantCount, variantSchema, variantEncoder, variantExtractor, variantDecoder
Instances
gschemaGenVariant :: forall proxy a. (GSerialiseVariant (Rep a), Typeable a, Generic a) => proxy a -> SchemaGen Schema Source #
Generic implementation of schemaGen
for an ADT.
gtoBuilderVariant :: (GSerialiseVariant (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.
gschemaGenProduct :: forall proxy a. (Generic a, GSerialiseProduct (Rep a)) => proxy a -> SchemaGen Schema Source #
gtoBuilderProduct :: (Generic a, GEncodeProduct (Rep a)) => a -> Builder Source #
gdecodeCurrentVariant :: (GSerialiseVariant (Rep a), Generic a) => Decoder a Source #
gextractorProduct :: forall a. (GSerialiseProduct (Rep a), Generic a, Typeable a) => Extractor a Source #
Generic implementation of extractor
for a record.
gdecodeCurrentProduct :: forall a. (GSerialiseProduct (Rep a), Generic a) => Decoder a Source #
Generic implementation of extractor
for a record.
Preset schema
bootstrapSchema :: Word8 -> Schema Source #