avro-0.4.2.0: Avro serialization support for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Avro.Schema

Contents

Description

Avro Schemas, 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

Schema description types

type Schema = Type Source #

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.

data Type Source #

Avro types are considered either primitive (string, int, etc) or complex/declared (structures, unions etc).

Instances
Eq Type Source # 
Instance details

Defined in Data.Avro.Schema

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Show Type Source # 
Instance details

Defined in Data.Avro.Schema

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

ToJSON Type Source # 
Instance details

Defined in Data.Avro.Schema

FromJSON Type Source # 
Instance details

Defined in Data.Avro.Schema

ToJSON (Value Type) Source # 
Instance details

Defined in Data.Avro.Schema

EncodeAvro (Value Type) Source # 
Instance details

Defined in Data.Avro.Encode

Methods

avro :: Value Type -> AvroM Source #

data Field Source #

Instances
Eq Field Source # 
Instance details

Defined in Data.Avro.Schema

Methods

(==) :: Field -> Field -> Bool #

(/=) :: Field -> Field -> Bool #

Show Field Source # 
Instance details

Defined in Data.Avro.Schema

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

data Order Source #

Constructors

Ascending 
Descending 
Ignore 
Instances
Eq Order Source # 
Instance details

Defined in Data.Avro.Schema

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

Ord Order Source # 
Instance details

Defined in Data.Avro.Schema

Methods

compare :: Order -> Order -> Ordering #

(<) :: Order -> Order -> Bool #

(<=) :: Order -> Order -> Bool #

(>) :: Order -> Order -> Bool #

(>=) :: Order -> Order -> Bool #

max :: Order -> Order -> Order #

min :: Order -> Order -> Order #

Show Order Source # 
Instance details

Defined in Data.Avro.Schema

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

ToJSON Order Source # 
Instance details

Defined in Data.Avro.Schema

FromJSON Order Source # 
Instance details

Defined in Data.Avro.Schema

data TypeName Source #

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"

Constructors

TN 

Fields

Instances
Eq TypeName Source # 
Instance details

Defined in Data.Avro.Schema

Ord TypeName Source # 
Instance details

Defined in Data.Avro.Schema

Show TypeName Source #

Show the TypeName as a string literal compatible with its IsString instance.

Instance details

Defined in Data.Avro.Schema

IsString TypeName Source #

This lets us write TypeNames as string literals in a fully qualified style. "com.example.foo" is the name "foo" with the namespace "com.example"; "foo" is the name "foo" with no namespace.

Instance details

Defined in Data.Avro.Schema

Hashable TypeName Source # 
Instance details

Defined in Data.Avro.Schema

Methods

hashWithSalt :: Int -> TypeName -> Int #

hash :: TypeName -> Int #

renderFullname :: TypeName -> Text Source #

Render a fullname as a dot separated string.

> renderFullname (TN Foo ["com", "example"])
"com.example.Foo"
> renderFullname (TN Foo [])
".Foo"

parseFullname :: Text -> TypeName Source #

Parses a fullname into a TypeName, assuming the string representation is valid.

> parseFullname "com.example.Foo"
TN { baseName = Foo, components = ["com", "example"] }

mkEnum Source #

Arguments

:: 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.

buildTypeEnvironment Source #

Arguments

:: 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.

data Result a Source #

Constructors

Success a 
Error String 
Instances
Monad Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b #

(>>) :: Result a -> Result b -> Result b #

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

MonadFail Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

fail :: String -> Result a #

Applicative Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Foldable Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldr :: (a -> b -> b) -> b -> Result a -> b #

foldr' :: (a -> b -> b) -> b -> Result a -> b #

foldl :: (b -> a -> b) -> b -> Result a -> b #

foldl' :: (b -> a -> b) -> b -> Result a -> b #

foldr1 :: (a -> a -> a) -> Result a -> a #

foldl1 :: (a -> a -> a) -> Result a -> a #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Traversable Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b) #

sequenceA :: Applicative f => Result (f a) -> f (Result a) #

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b) #

sequence :: Monad m => Result (m a) -> m (Result a) #

Alternative Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

empty :: Result a #

(<|>) :: Result a -> Result a -> Result a #

some :: Result a -> Result [a] #

many :: Result a -> Result [a] #

MonadPlus Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

mzero :: Result a #

mplus :: Result a -> Result a -> Result a #

MonadError String Result Source # 
Instance details

Defined in Data.Avro.Schema

Methods

throwError :: String -> Result a #

catchError :: Result a -> (String -> Result a) -> Result a #

Eq a => Eq (Result a) Source # 
Instance details

Defined in Data.Avro.Schema

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Ord a => Ord (Result a) Source # 
Instance details

Defined in Data.Avro.Schema

Methods

compare :: Result a -> Result a -> Ordering #

(<) :: Result a -> Result a -> Bool #

(<=) :: Result a -> Result a -> Bool #

(>) :: Result a -> Result a -> Bool #

(>=) :: Result a -> Result a -> Bool #

max :: Result a -> Result a -> Result a #

min :: Result a -> Result a -> Result a #

Show a => Show (Result a) Source # 
Instance details

Defined in Data.Avro.Schema

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Semigroup (Result a) Source # 
Instance details

Defined in Data.Avro.Schema

Methods

(<>) :: Result a -> Result a -> Result a #

sconcat :: NonEmpty (Result a) -> Result a #

stimes :: Integral b => b -> Result a -> Result a #

Monoid (Result a) Source # 
Instance details

Defined in Data.Avro.Schema

Methods

mempty :: Result a #

mappend :: Result a -> Result a -> Result a #

mconcat :: [Result a] -> Result a #

badValue :: Show t => t -> String -> Result a Source #

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.

parseAvroJSON Source #

Arguments

:: (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 Union schemas. It should error out if this is not the case—it represents a bug in this code.

-> (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.