Copyright | (c) Fumiaki Kinoshita 2019 |
---|---|
License | BSD3 |
Stability | Provisional |
Safe Haskell | None |
Language | Haskell2010 |
Maintainer : Fumiaki Kinoshita fumiexcel@gmail.com
Basic types
Synopsis
- data Tag
- 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)
- currentSchemaVersion :: Word8
- bootstrapSchema :: Word8 -> Either WineryException Schema
- 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 Extractor a = Extractor {
- getExtractor :: Plan (Term -> a)
- type Strategy' = Strategy WineryException StrategyEnv
- data StrategyBind
- = DynDecoder !Dynamic
- | BoundSchema !Int !Schema
- data StrategyEnv = StrategyEnv !Int ![StrategyBind]
- newtype Plan a = Plan {}
- unwrapExtractor :: Extractor a -> Schema -> Strategy' (Term -> 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
Documentation
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 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.1-IJNRMEpxwog9H471ljyF0Q" 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 |
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
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
currentSchemaVersion :: Word8 Source #
The current version of the schema
bootstrapSchema :: Word8 -> Either WineryException Schema Source #
Obtain the schema of the schema corresponding to the specified version.
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 |
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 | |
|
data StrategyBind Source #
DynDecoder !Dynamic | A fixpoint of a decoder |
BoundSchema !Int !Schema |
data StrategyEnv Source #
Plan is a monad for computations which interpret Schema
.
data WineryException Source #
Exceptions thrown when by an extractor
Instances
Show WineryException Source # | |
Defined in Codec.Winery.Base showsPrec :: Int -> WineryException -> ShowS # show :: WineryException -> String # showList :: [WineryException] -> ShowS # | |
IsString WineryException Source # | |
Defined in Codec.Winery.Base fromString :: String -> WineryException # | |
Exception WineryException Source # | |
Defined in Codec.Winery.Base |
prettyWineryException :: WineryException -> Doc AnsiStyle Source #
Pretty-print WineryException