avro-0.3.0.5: 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).

mkEnum :: TypeName -> [TypeName] -> Maybe Text -> Maybe Text -> [Text] -> Type Source #

mkEnum name aliases namespace docs syms Constructs an Enum schema using the enumeration type's name, aliases (if any), namespace, documentation, and list of symbols that inhabit the enumeration.

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 :: Applicative m => (TypeName -> m Type) -> Type -> TypeName -> m Type Source #

buildTypeEnvironment schema builds a function mapping type names to the types declared in the traversed schema. Notice this function does not currently handle namespaces in a correct manner, possibly allowing for bad environment lookups when used on complex schemas.

data Result a Source #

Constructors

Success a 
Error String 

Instances

Monad Result Source # 

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 # 

Methods

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

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

MonadFail Result Source # 

Methods

fail :: String -> Result a #

Applicative Result Source # 

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 # 

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 # 

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 # 

Methods

empty :: Result a #

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

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

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

MonadPlus Result Source # 

Methods

mzero :: Result a #

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

MonadError String Result Source # 

Methods

throwError :: String -> Result a #

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

Eq a => Eq (Result a) Source # 

Methods

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

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

Ord a => Ord (Result a) Source # 

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 # 

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Monoid (Result a) Source # 

Methods

mempty :: Result a #

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

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

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.

-> (Text -> Maybe Type) 
-> Type 
-> Value 
-> Result (Value Type) 

Parse JSON-encoded avro data.