avro-0.6.1.2: Avro serialization support for Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Avro.Schema.Schema

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

data Schema Source #

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.

Bundled Patterns

pattern Int' :: Schema 
pattern Long' :: Schema 
pattern Bytes' :: Schema 
pattern String' :: Schema 

Instances

Instances details
FromJSON Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

ToJSON Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep Schema :: Type -> Type #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

Show Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: Schema -> () #

Eq Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

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

Ord Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift Schema Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => Schema -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Schema -> Code m Schema #

type Rep Schema Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep Schema = D1 ('MetaData "Schema" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (((C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Boolean" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Int" 'PrefixI 'True) (S1 ('MetaSel ('Just "logicalTypeI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogicalTypeInt))))) :+: ((C1 ('MetaCons "Long" 'PrefixI 'True) (S1 ('MetaSel ('Just "logicalTypeL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogicalTypeLong))) :+: C1 ('MetaCons "Float" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Double" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bytes" 'PrefixI 'True) (S1 ('MetaSel ('Just "logicalTypeB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogicalTypeBytes)))))) :+: (((C1 ('MetaCons "String" 'PrefixI 'True) (S1 ('MetaSel ('Just "logicalTypeS") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogicalTypeString))) :+: C1 ('MetaCons "Array" 'PrefixI 'True) (S1 ('MetaSel ('Just "item") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema))) :+: (C1 ('MetaCons "Map" 'PrefixI 'True) (S1 ('MetaSel ('Just "values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema)) :+: C1 ('MetaCons "NamedType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TypeName)))) :+: ((C1 ('MetaCons "Record" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TypeName) :*: S1 ('MetaSel ('Just "aliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TypeName])) :*: (S1 ('MetaSel ('Just "doc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "fields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Field]))) :+: C1 ('MetaCons "Enum" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TypeName) :*: S1 ('MetaSel ('Just "aliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TypeName])) :*: (S1 ('MetaSel ('Just "doc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "symbols") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Text))))) :+: (C1 ('MetaCons "Union" 'PrefixI 'True) (S1 ('MetaSel ('Just "options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Schema))) :+: C1 ('MetaCons "Fixed" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TypeName) :*: S1 ('MetaSel ('Just "aliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TypeName])) :*: (S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "logicalTypeF") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe LogicalTypeFixed))))))))

data DefaultValue Source #

Constructors

DNull 
DBoolean !Bool 
DInt Schema Int32 
DLong Schema Int64 
DFloat Schema Float 
DDouble Schema Double 
DBytes Schema ByteString 
DString Schema Text 
DArray (Vector DefaultValue)

Dynamically enforced monomorphic type.

DMap (HashMap Text DefaultValue)

Dynamically enforced monomorphic type

DRecord Schema (HashMap Text DefaultValue) 
DUnion (Vector Schema) Schema DefaultValue

Set of union options, schema for selected option, and the actual value.

DFixed Schema !ByteString 
DEnum Schema Int Text

An enum is a set of the possible symbols (the schema) and the selected symbol

Instances

Instances details
ToJSON DefaultValue Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic DefaultValue Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep DefaultValue :: Type -> Type #

Show DefaultValue Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData DefaultValue Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: DefaultValue -> () #

Eq DefaultValue Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord DefaultValue Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift DefaultValue Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => DefaultValue -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DefaultValue -> Code m DefaultValue #

type Rep DefaultValue Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep DefaultValue = D1 ('MetaData "DefaultValue" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (((C1 ('MetaCons "DNull" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DBoolean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "DInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32)))) :+: ((C1 ('MetaCons "DLong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int64)) :+: C1 ('MetaCons "DFloat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Float))) :+: (C1 ('MetaCons "DDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "DBytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))) :+: ((C1 ('MetaCons "DString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "DArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector DefaultValue))) :+: C1 ('MetaCons "DMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap Text DefaultValue))))) :+: ((C1 ('MetaCons "DRecord" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap Text DefaultValue))) :+: C1 ('MetaCons "DUnion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Schema)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DefaultValue)))) :+: (C1 ('MetaCons "DFixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "DEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Schema) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))))))

data Field Source #

Instances

Instances details
Generic Field Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep Field :: Type -> Type #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

Show Field Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

NFData Field Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: Field -> () #

Eq Field Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

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

Ord Field Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

compare :: Field -> Field -> Ordering #

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

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

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

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

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

Lift Field Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => Field -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Field -> Code m Field #

type Rep Field Source # 
Instance details

Defined in Data.Avro.Schema.Schema

data Order Source #

Constructors

Ascending 
Descending 
Ignore 

Instances

Instances details
FromJSON Order Source # 
Instance details

Defined in Data.Avro.Schema.Schema

ToJSON Order Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic Order Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep Order :: Type -> Type #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

Show Order Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

NFData Order Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: Order -> () #

Eq Order Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

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

Ord Order Source # 
Instance details

Defined in Data.Avro.Schema.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 #

Lift Order Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => Order -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Order -> Code m Order #

type Rep Order Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep Order = D1 ('MetaData "Order" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (C1 ('MetaCons "Ascending" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Descending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ignore" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances details
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.Schema

Generic TypeName Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep TypeName :: Type -> Type #

Methods

from :: TypeName -> Rep TypeName x #

to :: Rep TypeName x -> TypeName #

Show TypeName Source #

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

Instance details

Defined in Data.Avro.Schema.Schema

NFData TypeName Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: TypeName -> () #

Eq TypeName Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord TypeName Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Hashable TypeName Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

hashWithSalt :: Int -> TypeName -> Int #

hash :: TypeName -> Int #

Lift TypeName Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => TypeName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TypeName -> Code m TypeName #

type Rep TypeName Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep TypeName = D1 ('MetaData "TypeName" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (C1 ('MetaCons "TN" 'PrefixI 'True) (S1 ('MetaSel ('Just "baseName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "namespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text])))

data Decimal Source #

The decimal logical type represents arbitrary-precision decimal numbers. Numbers are represented as unscaled * (10 ** -scale) where scale is part of the logical type and unscaled is an integer represented by the underlying primitive type.

Instances of the decimal logical type need to specify a scale and precision.

decimal can be encoded as one of several different primitive types:

  • bytes
  • fixed
  • long
  • int

For long and int, unscaled is the underlying number.

For bytes and fixed, unscaled is represented as a two's-complement signed integer in big-endian byte order.

Note: int and long representations for decimal are not part of the current Avro specification, but they are supported by some language implementations including the official Java library. Implementations that do not support this should ignore the logical type and use the underlying primitive type instead.

Constructors

Decimal 

Fields

  • precision :: Integer

    The maximum number of digits that can be represented by this decimal type.

    precision > 0
  • scale :: Integer

    The scale in unscaled * (10 ** -scale) for this type.

    0 ≤ scale ≤ precision

Instances

Instances details
Generic Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep Decimal :: Type -> Type #

Methods

from :: Decimal -> Rep Decimal x #

to :: Rep Decimal x -> Decimal #

Show Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: Decimal -> () #

Eq Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

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

Ord Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift Decimal Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => Decimal -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Decimal -> Code m Decimal #

type Rep Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep Decimal = D1 ('MetaData "Decimal" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (C1 ('MetaCons "Decimal" 'PrefixI 'True) (S1 ('MetaSel ('Just "precision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "scale") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)))

newtype LogicalTypeBytes Source #

Constructors

DecimalB Decimal

An arbitrary-precision signed decimal number. See Decimal.

Instances

Instances details
Generic LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeBytes :: Type -> Type #

Show LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: LogicalTypeBytes -> () #

Eq LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => LogicalTypeBytes -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => LogicalTypeBytes -> Code m LogicalTypeBytes #

type Rep LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep LogicalTypeBytes = D1 ('MetaData "LogicalTypeBytes" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'True) (C1 ('MetaCons "DecimalB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Decimal)))

data LogicalTypeFixed Source #

Constructors

DecimalF Decimal

An arbitrary-precision signed decimal number. See Decimal.

Duration

An interval of time, represented as some number of months, days and milliseconds.

Encoded as three little-endian unsigned integers for months, days and milliseconds respectively.

Instances

Instances details
Generic LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeFixed :: Type -> Type #

Show LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: LogicalTypeFixed -> () #

Eq LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => LogicalTypeFixed -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => LogicalTypeFixed -> Code m LogicalTypeFixed #

type Rep LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep LogicalTypeFixed = D1 ('MetaData "LogicalTypeFixed" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (C1 ('MetaCons "DecimalF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Decimal)) :+: C1 ('MetaCons "Duration" 'PrefixI 'False) (U1 :: Type -> Type))

data LogicalTypeInt Source #

Constructors

DecimalI Decimal

An arbitrary-precision signed decimal number. See Decimal.

Date

A date (eg 2020-01-10) with no timezone/locale.

Encoded as the number of days before/after the Unix epoch (1970-01-01).

TimeMillis

A time of day with millisecond precision.

Encoded as the number of milliseconds after midnight.

Instances

Instances details
Generic LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeInt :: Type -> Type #

Show LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: LogicalTypeInt -> () #

Eq LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => LogicalTypeInt -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => LogicalTypeInt -> Code m LogicalTypeInt #

type Rep LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep LogicalTypeInt = D1 ('MetaData "LogicalTypeInt" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (C1 ('MetaCons "DecimalI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Decimal)) :+: (C1 ('MetaCons "Date" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeMillis" 'PrefixI 'False) (U1 :: Type -> Type)))

data LogicalTypeLong Source #

Constructors

DecimalL Decimal

An arbitrary-precision signed decimal number. See Decimal.

TimeMicros

A time of day with microsecond precision.

Encoded as the number of microseconds after midnight.

TimestampMillis

A UTC timestamp with millisecond precision.

Encoded as the number of milliseconds before/after the Unix epoch (1970-01-01 00:00:00.000).

TimestampMicros

A UTC timestamp with microsecond precision.

Encoded as the number of microseconds before/after the Unix epoch (1970-01-01 00:00:00.000000).

LocalTimestampMillis

A timestamp in the local timezone, whatever that happens to be, with millisecond precision.

Encoded as the number of milliseconds before/after the Unix epoch (1970-01-01 00:00:00.000).

LocalTimestampMicros

A timestamp in the local timezone, whatever that happens to be, with microsecond precision.

Encoded as the number of microseconds before/after the Unix epoch (1970-01-01 00:00:00.000000).

Instances

Instances details
Generic LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeLong :: Type -> Type #

Show LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: LogicalTypeLong -> () #

Eq LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => LogicalTypeLong -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => LogicalTypeLong -> Code m LogicalTypeLong #

type Rep LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep LogicalTypeLong = D1 ('MetaData "LogicalTypeLong" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) ((C1 ('MetaCons "DecimalL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Decimal)) :+: (C1 ('MetaCons "TimeMicros" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimestampMillis" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TimestampMicros" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LocalTimestampMillis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LocalTimestampMicros" 'PrefixI 'False) (U1 :: Type -> Type))))

data LogicalTypeString Source #

Constructors

UUID

A Universally Unique Identifier (UUID).

Encoded as a string that is valid according to RFC 4122.

Instances

Instances details
Generic LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeString :: Type -> Type #

Show LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

NFData LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: LogicalTypeString -> () #

Eq LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Lift LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Quote m => LogicalTypeString -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => LogicalTypeString -> Code m LogicalTypeString #

type Rep LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep LogicalTypeString = D1 ('MetaData "LogicalTypeString" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (C1 ('MetaCons "UUID" 'PrefixI 'False) (U1 :: Type -> Type))

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.

-> Schema 

Build an Schema value from its components.

mkUnion :: NonEmpty Schema -> Schema 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 :: Schema -> Text Source #

Get the name of the type. In the case of unions, get the name of the first value in the union schema.

typeAliases :: Schema -> [TypeName] Source #

Get the aliases of the type.

buildTypeEnvironment Source #

Arguments

:: Applicative m 
=> (TypeName -> m Schema)

Callback to handle type names not in the schema.

-> Schema

The schema that we're generating a lookup function for.

-> TypeName -> m Schema 

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 :: Schema -> HashMap TypeName Schema 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

Instances details
MonadFail Result Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

fail :: String -> Result a #

Foldable Result Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

foldMap :: Monoid m => (a -> m) -> Result a -> 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.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.Schema

Methods

empty :: Result a #

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

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

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

Applicative Result Source # 
Instance details

Defined in Data.Avro.Schema.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 #

Functor Result Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

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

Monad Result Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

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

return :: a -> Result a #

MonadPlus Result Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

mzero :: Result a #

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

MonadError String Result Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

throwError :: String -> Result a #

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

Monoid (Result a) Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

mempty :: Result a #

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

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

Semigroup (Result a) Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

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

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

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

Generic (Result a) Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep (Result a) :: Type -> Type #

Methods

from :: Result a -> Rep (Result a) x #

to :: Rep (Result a) x -> Result a #

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

Defined in Data.Avro.Schema.Schema

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

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

Defined in Data.Avro.Schema.Schema

Methods

rnf :: Result a -> () #

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

Defined in Data.Avro.Schema.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.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 #

type Rep (Result a) Source # 
Instance details

Defined in Data.Avro.Schema.Schema

type Rep (Result a) = D1 ('MetaData "Result" "Data.Avro.Schema.Schema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" 'False) (C1 ('MetaCons "Success" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)))

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

matches :: Schema -> Schema -> 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

:: (Schema -> Value -> Result DefaultValue)

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 Schema) 
-> Schema 
-> Value 
-> Result DefaultValue 

Parse JSON-encoded avro data.

overlay :: Schema -> Schema -> Schema Source #

Merge two schemas to produce a third. Specifically, overlay schema reference fills in NamedTypes in schema using any matching definitions from reference.

subdefinition :: Schema -> Text -> Maybe Schema Source #

Extract the named inner type definition as its own schema.