| Copyright | (c) Fumiaki Kinoshita 2019 |
|---|---|
| License | BSD3 |
| Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
| Stability | Provisional |
| Safe Haskell | None |
| Language | Haskell2010 |
Codec.Winery.Base
Description
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)
- newtype SchemaGen a = SchemaGen {}
- 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
- data ExtractException = InvalidTerm !Term
- newtype Extractor a = Extractor {
- runExtractor :: Schema -> Strategy' (Term -> a)
- type Strategy' = Strategy WineryException StrategyEnv
- data StrategyBind
- = DynDecoder !Dynamic
- | BoundSchema !Int !Schema
- data StrategyEnv = StrategyEnv !Int ![StrategyBind]
- unwrapExtractor :: Extractor a -> Schema -> Strategy' (Term -> a)
- data WineryException
- = UnexpectedSchema ![TypeRep] !(Doc AnsiStyle) !Schema
- | FieldNotFound ![TypeRep] !Text ![Text]
- | TypeMismatch ![TypeRep] !Int !TypeRep !TypeRep
- | ProductTooSmall ![TypeRep] !Int
- | UnboundVariable ![TypeRep] !Int
- | EmptyInput
- | WineryMessage !(Doc AnsiStyle)
- | UnsupportedSchemaVersion !Word8
- pushTrace :: TypeRep -> WineryException -> WineryException
- 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 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.3.2-KhjWZ07kGaY74i3HCD3TU0" '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
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
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.
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 |
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 # | |
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
| |
data StrategyBind Source #
Constructors
| DynDecoder !Dynamic | A fixpoint of a decoder |
| BoundSchema !Int !Schema |
data StrategyEnv Source #
Constructors
| StrategyEnv !Int ![StrategyBind] |
unwrapExtractor :: Extractor a -> Schema -> Strategy' (Term -> a) Source #
Deprecated: Use runExtractor instead
Run an Extractor.
data WineryException Source #
Exceptions thrown by an extractor
Constructors
| UnexpectedSchema ![TypeRep] !(Doc AnsiStyle) !Schema | |
| FieldNotFound ![TypeRep] !Text ![Text] | |
| TypeMismatch ![TypeRep] !Int !TypeRep !TypeRep | |
| ProductTooSmall ![TypeRep] !Int | |
| UnboundVariable ![TypeRep] !Int | |
| EmptyInput | |
| WineryMessage !(Doc AnsiStyle) | |
| UnsupportedSchemaVersion !Word8 |
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 # | |
pushTrace :: TypeRep -> WineryException -> WineryException Source #
prettyWineryException :: WineryException -> Doc AnsiStyle Source #
Pretty-print WineryException