Safe Haskell | None |
---|---|
Language | Haskell2010 |
Avro Schema
s, represented here as values of type Schema
,
describe the serialization and de-serialization of values.
In Avro schemas are compose-able such that encoding data under a schema and
decoding with a variant, such as newer or older version of the original
schema, can be accomplished by using the Deconflict
module.
Synopsis
- type Schema = Type
- data Type
- data Field = Field {}
- data Order
- data TypeName = TN {}
- renderFullname :: TypeName -> Text
- parseFullname :: Text -> TypeName
- mkEnum :: TypeName -> [TypeName] -> Maybe Text -> [Text] -> Type
- mkUnion :: NonEmpty Type -> Type
- validateSchema :: Schema -> Parser ()
- typeName :: Type -> Text
- buildTypeEnvironment :: Applicative m => (TypeName -> m Type) -> Schema -> TypeName -> m Type
- extractBindings :: Type -> HashMap TypeName Type
- data Result a
- badValue :: Show t => t -> String -> Result a
- resultToEither :: Result b -> Either String b
- matches :: Type -> Type -> Bool
- parseBytes :: Text -> Result ByteString
- serializeBytes :: ByteString -> Text
- parseAvroJSON :: (Type -> Value -> Result (Value Type)) -> (TypeName -> Maybe Type) -> Type -> Value -> Result (Value Type)
- overlay :: Type -> Type -> Type
- subdefinition :: Type -> Text -> Maybe Type
- expandNamedTypes :: Schema -> Schema
Schema description types
An Avro schema is either * A "JSON object in the form `{"type":"typeName" ...` * A "JSON string, naming a defined type" (basic type wo free variablesnames) * A "JSON array, representing a union"
N.B. It is possible to create a Haskell value (of Schema type) that is
not a valid Avro schema by violating one of the above or one of the
conditions called out in validateSchema
.
Avro types are considered either primitive (string, int, etc) or complex/declared (structures, unions etc).
Null | |
Boolean | |
Int | |
Long | |
Float | |
Double | |
Bytes | |
String | |
Array | |
Map | |
NamedType TypeName | |
Record | |
Enum | |
Union | |
Fixed | |
Instances
Instances
Eq Field Source # | |
Show Field Source # | |
Generic Field Source # | |
NFData Field Source # | |
Defined in Data.Avro.Schema | |
type Rep Field Source # | |
Defined in Data.Avro.Schema type Rep Field = D1 (MetaData "Field" "Data.Avro.Schema" "avro-0.4.4.3-JOdgVrx3xwa1lz3aiGCi2O" False) (C1 (MetaCons "Field" PrefixI True) ((S1 (MetaSel (Just "fldName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "fldAliases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]) :*: S1 (MetaSel (Just "fldDoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "fldOrder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Order)) :*: (S1 (MetaSel (Just "fldType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type) :*: S1 (MetaSel (Just "fldDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Value Type))))))) |
A named type in Avro has a name and, optionally, a namespace.
A name is a string that starts with an ASCII letter or underscore followed by letters, underscores and digits:
name ::= [A-Za-z_][A-Za-z0-9_]*
Examples include "_foo7"
, Bar_
and "x"
.
A namespace is a sequence of names with the same lexical
structure. When written as a string, the components of a namespace
are separated with dots ("com.example"
).
TypeName
represents a fullname—a name combined with a
namespace. These are written and parsed as dot-separated
strings. The TypeName
TN Foo ["com", "example"]
is rendered
as "com.example.Foo"
.
Fullnames have to be globally unique inside an Avro schema.
A namespace of []
or [""]
is the "null namespace". In avro
an explicitly null-namespaced identifier is written as ".Foo"
Instances
Eq TypeName Source # | |
Ord TypeName Source # | |
Defined in Data.Avro.Schema | |
Show TypeName Source # | Show the |
IsString TypeName Source # | This lets us write |
Defined in Data.Avro.Schema fromString :: String -> TypeName # | |
Generic TypeName Source # | |
Hashable TypeName Source # | |
Defined in Data.Avro.Schema | |
NFData TypeName Source # | |
Defined in Data.Avro.Schema | |
type Rep TypeName Source # | |
Defined in Data.Avro.Schema type Rep TypeName = D1 (MetaData "TypeName" "Data.Avro.Schema" "avro-0.4.4.3-JOdgVrx3xwa1lz3aiGCi2O" False) (C1 (MetaCons "TN" PrefixI True) (S1 (MetaSel (Just "baseName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "namespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]))) |
renderFullname :: TypeName -> Text Source #
parseFullname :: Text -> TypeName Source #
:: TypeName | The name of the enum (includes namespace). |
-> [TypeName] | Aliases for the enum (if any). |
-> Maybe Text | Optional documentation for the enum. |
-> [Text] | The symbols of the enum. |
-> Type |
Build an Type
value from its components.
mkUnion :: NonEmpty Type -> Type Source #
mkUnion subTypes
Defines a union of the provided subTypes. N.B. it is
invalid Avro to include another union or to have more than one of the same
type as a direct member of the union. No check is done for this condition!
validateSchema :: Schema -> Parser () Source #
Placeholder NO-OP function!
Validates a schema to ensure:
- All types are defined
- Unions do not directly contain other unions
- Unions are not ambiguous (may not contain more than one schema with the same type except for named types of record, fixed and enum)
- Default values for unions can be cast as the type indicated by the first structure.
- Default values can be cast/de-serialize correctly.
- Named types are resolvable
Lower level utilities
typeName :: Type -> Text Source #
Get the name of the type. In the case of unions, get the name of the first value in the union schema.
:: Applicative m | |
=> (TypeName -> m Type) | Callback to handle type names not in the schema. |
-> Schema | The schema that we're generating a lookup function for. |
-> TypeName -> m Type |
buildTypeEnvironment schema
builds a function mapping type names to
the types declared in the traversed schema.
This mapping includes both the base type names and any aliases they have. Aliases and normal names are not differentiated in any way.
extractBindings :: Type -> HashMap TypeName Type Source #
extractBindings schema
traverses a schema and builds a map of all declared
types.
Types declared implicitly in record field definitions are also included. No distinction is made between aliases and normal names.
Instances
matches :: Type -> Type -> Bool Source #
Checks that two schemas match. This is like equality of schemas,
except NamedTypes
match against other types with the same name.
This extends recursively: two records match if they have the same name, the same number of fields and the fields all match.
parseBytes :: Text -> Result ByteString Source #
Parses a string literal into a bytestring in the format expected for bytes and fixed values. Will fail if every character does not have a codepoint between 0 and 255.
serializeBytes :: ByteString -> Text Source #
Turn a ByteString
into a Text
that matches the format Avro
expects from bytes and fixed literals in JSON. Each byte is mapped
to a single Unicode codepoint between 0 and 255.
:: (Type -> Value -> Result (Value Type)) | How to handle unions. The way unions are formatted in JSON depends on whether we're parsing a normal Avro object or we're parsing a default declaration in a schema. This function will only ever be passed |
-> (TypeName -> Maybe Type) | |
-> Type | |
-> Value | |
-> Result (Value Type) |
Parse JSON-encoded avro data.
overlay :: Type -> Type -> Type Source #
Merge two schemas to produce a third.
Specifically, overlay schema reference
fills in NamedTypes
in schema
using any matching definitions from reference
.
subdefinition :: Type -> Text -> Maybe Type Source #
Extract the named inner type definition as its own schema.
expandNamedTypes :: Schema -> Schema Source #