avro-0.5.2.0: Avro serialization support for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Avro.Schema.ReadSchema

Synopsis

Documentation

data ReadSchema Source #

This type represents a deconflicted version of a Schema. Schema resolution is described in Avro specification: https://avro.apache.org/docs/current/spec.html#Schema+Resolution

This library represents "normal" schema and "deconflicted" schema as different types to avoid confusion between these two usecases (we shouldn't serialise values with such schema) and to be able to accomodate some extra information that links between how data is supposed transformed between what reader wants and what writer has.

Constructors

Null 
Boolean 
Int 
Long 
Float 
Double 
Bytes 
String 
Array 

Fields

Map 

Fields

NamedType TypeName 
Record 
Enum 
Union 

Fields

  • options :: Vector (Int, ReadSchema)

    Order of values represents order in the writer schema, an index represents order in a reader schema

Fixed 
FreeUnion 

Fields

Instances
Eq ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Show ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Generic ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadSchema :: Type -> Type #

NFData ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadSchema -> () #

type Rep ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadSchema = D1 (MetaData "ReadSchema" "Data.Avro.Schema.ReadSchema" "avro-0.5.2.0-1fGNgWfYbHIOeLCKAVcy" 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 DecidedLazy) (Rec0 (Maybe LogicalTypeInt))) :+: C1 (MetaCons "Long" PrefixI True) (S1 (MetaSel (Just "longReadFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReadLong) :*: S1 (MetaSel (Just "logicalTypeL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LogicalTypeLong))))) :+: ((C1 (MetaCons "Float" PrefixI True) (S1 (MetaSel (Just "floatReadFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReadFloat)) :+: C1 (MetaCons "Double" PrefixI True) (S1 (MetaSel (Just "doubleReadFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReadDouble))) :+: (C1 (MetaCons "Bytes" PrefixI True) (S1 (MetaSel (Just "logicalTypeB") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LogicalTypeBytes))) :+: C1 (MetaCons "String" PrefixI True) (S1 (MetaSel (Just "logicalTypeS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LogicalTypeString)))))) :+: (((C1 (MetaCons "Array" PrefixI True) (S1 (MetaSel (Just "item") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReadSchema)) :+: C1 (MetaCons "Map" PrefixI True) (S1 (MetaSel (Just "values") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReadSchema))) :+: (C1 (MetaCons "NamedType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeName)) :+: C1 (MetaCons "Record" PrefixI True) ((S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeName) :*: S1 (MetaSel (Just "aliases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeName])) :*: (S1 (MetaSel (Just "doc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "fields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ReadField]))))) :+: ((C1 (MetaCons "Enum" PrefixI True) ((S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeName) :*: S1 (MetaSel (Just "aliases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeName])) :*: (S1 (MetaSel (Just "doc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "symbols") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Text)))) :+: C1 (MetaCons "Union" PrefixI True) (S1 (MetaSel (Just "options") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Int, ReadSchema))))) :+: (C1 (MetaCons "Fixed" PrefixI True) ((S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeName) :*: S1 (MetaSel (Just "aliases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TypeName])) :*: (S1 (MetaSel (Just "size") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "logicalTypeF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LogicalTypeFixed)))) :+: C1 (MetaCons "FreeUnion" PrefixI True) (S1 (MetaSel (Just "pos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "ty") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ReadSchema))))))

data ReadField Source #

Deconflicted record field.

Constructors

ReadField 

Fields

Instances
Eq ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Show ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Generic ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadField :: Type -> Type #

NFData ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadField -> () #

type Rep ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

data ReadLong Source #

How to decode a value of target type Long. This type controls how many bits are needed to be read from the encoded bytestring. The number of bits can be different depending on differences between reader and writer schemas.

The rules are described in https://avro.apache.org/docs/current/spec.html#Schema+Resolution

Constructors

LongFromInt

Read Int (32 bits) and cast it to Long (Rule: int is promotable to long, float, or double)

ReadLong

Read Long (64 bits) and use as is

Instances
Eq ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Show ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Generic ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadLong :: Type -> Type #

Methods

from :: ReadLong -> Rep ReadLong x #

to :: Rep ReadLong x -> ReadLong #

NFData ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadLong -> () #

type Rep ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadLong = D1 (MetaData "ReadLong" "Data.Avro.Schema.ReadSchema" "avro-0.5.2.0-1fGNgWfYbHIOeLCKAVcy" False) (C1 (MetaCons "LongFromInt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ReadLong" PrefixI False) (U1 :: Type -> Type))

data ReadFloat Source #

How to decode a value of target type Float. This type controls how many bits are needed to be read from the encoded bytestring. The number of bits can be different depending on differences between reader and writer schemas.

The rules are described in https://avro.apache.org/docs/current/spec.html#Schema+Resolution

Constructors

FloatFromInt

Read Int (32 bits) and cast it to Float

FloatFromLong

Read Long (64 bits) and cast it to Float (Rule: long is promotable to float or double)

ReadFloat

Read Float and use as is

Instances
Eq ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Show ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Generic ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadFloat :: Type -> Type #

NFData ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadFloat -> () #

type Rep ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadFloat = D1 (MetaData "ReadFloat" "Data.Avro.Schema.ReadSchema" "avro-0.5.2.0-1fGNgWfYbHIOeLCKAVcy" False) (C1 (MetaCons "FloatFromInt" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "FloatFromLong" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ReadFloat" PrefixI False) (U1 :: Type -> Type)))

data ReadDouble Source #

How to decode a value of target type Double. This type controls how many bits are needed to be read from the encoded bytestring. The number of bits can be different depending on differences between reader and writer schemas.

The rules are described in https://avro.apache.org/docs/current/spec.html#Schema+Resolution

Constructors

DoubleFromInt

Read Int (32 bits) and cast it to Double (Rule: int is promotable to long, float, or double)

DoubleFromFloat

Read Float (64 bits) and cast it to Double (Rule: float is promotable to float or double)

DoubleFromLong

Read Long (64 bits) and cast it to Double (Rule: long is promotable to float or double)

ReadDouble 
Instances
Eq ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Show ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Generic ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadDouble :: Type -> Type #

NFData ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadDouble -> () #

type Rep ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadDouble = D1 (MetaData "ReadDouble" "Data.Avro.Schema.ReadSchema" "avro-0.5.2.0-1fGNgWfYbHIOeLCKAVcy" False) ((C1 (MetaCons "DoubleFromInt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DoubleFromFloat" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DoubleFromLong" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ReadDouble" PrefixI False) (U1 :: Type -> Type)))

fromSchema :: Schema -> ReadSchema Source #

Converts Avro Schema to ReaderSchema trivially. This function is useful when no deconflicting is required.

extractBindings :: ReadSchema -> HashMap TypeName ReadSchema 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 Decimal Source #

Constructors

Decimal 
Instances
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

Show Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

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 #

Lift Decimal Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: Decimal -> Q Exp #

NFData Decimal Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: 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.5.2.0-1fGNgWfYbHIOeLCKAVcy" 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 
Instances
Eq LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Show LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeBytes :: Type -> Type #

Lift LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: LogicalTypeBytes -> Q Exp #

NFData LogicalTypeBytes Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: 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.5.2.0-1fGNgWfYbHIOeLCKAVcy" True) (C1 (MetaCons "DecimalB" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decimal)))

data LogicalTypeFixed Source #

Constructors

DecimalF Decimal 
Duration 
Instances
Eq LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Show LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeFixed :: Type -> Type #

Lift LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: LogicalTypeFixed -> Q Exp #

NFData LogicalTypeFixed Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: 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.5.2.0-1fGNgWfYbHIOeLCKAVcy" 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 #

Instances
Eq LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Show LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeInt :: Type -> Type #

Lift LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: LogicalTypeInt -> Q Exp #

NFData LogicalTypeInt Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: 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.5.2.0-1fGNgWfYbHIOeLCKAVcy" 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 #

Instances
Eq LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Show LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeLong :: Type -> Type #

Lift LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

Methods

lift :: LogicalTypeLong -> Q Exp #

NFData LogicalTypeLong Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: 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.5.2.0-1fGNgWfYbHIOeLCKAVcy" 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)))

data LogicalTypeString Source #

Constructors

UUID 
Instances
Eq LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Ord LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Show LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Generic LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Associated Types

type Rep LogicalTypeString :: Type -> Type #

Lift LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Deriving.Lift

NFData LogicalTypeString Source # 
Instance details

Defined in Data.Avro.Schema.Schema

Methods

rnf :: 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.5.2.0-1fGNgWfYbHIOeLCKAVcy" False) (C1 (MetaCons "UUID" PrefixI False) (U1 :: Type -> Type))

data FieldStatus Source #

Depending on differences between reader and writer schemas, a record field can be found:

  • Present in the reader schema but missing from the writer schema. In this case the reader field is marked as Defaulted with the default value from the reader schema. An index value represents the position of the field in the reader schema.
  • Present in the writer schema but missing from the reader schema. In this case the record field is marked as Ignored: the corresponding bytes still need to be read from the payload (to advance the position in a bytestring), but the result is discarded.
  • Present in both reader and writer schemas. In this case the field is marked to be read AsIs with an index that represents the field's position in the reader schema.
Instances
Eq FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Show FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Generic FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep FieldStatus :: Type -> Type #

NFData FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: FieldStatus -> () #

type Rep FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema