avro-0.6.1.2: Avro serialization support for Haskell
Safe HaskellSafe-Inferred
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

Instances details
Generic ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadSchema :: Type -> Type #

Show ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

NFData ReadSchema Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadSchema -> () #

Eq ReadSchema Source # 
Instance details

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

Instances details
Generic ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadField :: Type -> Type #

Show ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

NFData ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadField -> () #

Eq ReadField Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

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

Instances details
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 #

Show ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

NFData ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadLong -> () #

Eq ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadLong Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadLong = D1 ('MetaData "ReadLong" "Data.Avro.Schema.ReadSchema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" '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

Instances details
Generic ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadFloat :: Type -> Type #

Show ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

NFData ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadFloat -> () #

Eq ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadFloat Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadFloat = D1 ('MetaData "ReadFloat" "Data.Avro.Schema.ReadSchema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" '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

Instances details
Generic ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep ReadDouble :: Type -> Type #

Show ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

NFData ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: ReadDouble -> () #

Eq ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadDouble Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep ReadDouble = D1 ('MetaData "ReadDouble" "Data.Avro.Schema.ReadSchema" "avro-0.6.1.2-CUddNuGftGHAxf2IYjn53O" '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 #

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))

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

Instances details
Generic FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Associated Types

type Rep FieldStatus :: Type -> Type #

Show FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

NFData FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Methods

rnf :: FieldStatus -> () #

Eq FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

Ord FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema

type Rep FieldStatus Source # 
Instance details

Defined in Data.Avro.Schema.ReadSchema