avro-0.6.1.0: Avro serialization support for Haskell
Safe HaskellNone
LanguageHaskell2010

Data.Avro.Encoding.FromAvro

Synopsis

Documentation

class FromAvro a where Source #

Descrives how to convert a given intermediate Value into a Haskell data type.

Instances

Instances details
FromAvro Bool Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro Double Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro Float Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro Int Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro Int32 Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro Int64 Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro () Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro ByteString Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro ByteString Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro UTCTime Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro Text Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro LocalTime Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro DiffTime Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro Day Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro UUID Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro a => FromAvro [a] Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

Methods

fromAvro :: Value -> Either String [a] Source #

FromAvro a => FromAvro (Maybe a) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro a => FromAvro (Identity a) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

(Unbox a, FromAvro a) => FromAvro (Vector a) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro a => FromAvro (Vector a) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

(FromAvro a, FromAvro b) => FromAvro (Either a b) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro a => FromAvro (Map Text a) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

FromAvro a => FromAvro (HashMap Text a) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

(KnownNat p, KnownNat s) => FromAvro (Decimal p s) Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

(FromAvro a, FromAvro b, FromAvro c) => FromAvro (Either3 a b c) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either3 a b c) Source #

(FromAvro a, FromAvro b, FromAvro c, FromAvro d) => FromAvro (Either4 a b c d) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either4 a b c d) Source #

(FromAvro a, FromAvro b, FromAvro c, FromAvro d, FromAvro e) => FromAvro (Either5 a b c d e) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either5 a b c d e) Source #

(FromAvro a, FromAvro b, FromAvro c, FromAvro d, FromAvro e, FromAvro f) => FromAvro (Either6 a b c d e f) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either6 a b c d e f) Source #

(FromAvro a, FromAvro b, FromAvro c, FromAvro d, FromAvro e, FromAvro f, FromAvro g) => FromAvro (Either7 a b c d e f g) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either7 a b c d e f g) Source #

(FromAvro a, FromAvro b, FromAvro c, FromAvro d, FromAvro e, FromAvro f, FromAvro g, FromAvro h) => FromAvro (Either8 a b c d e f g h) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either8 a b c d e f g h) Source #

(FromAvro a, FromAvro b, FromAvro c, FromAvro d, FromAvro e, FromAvro f, FromAvro g, FromAvro h, FromAvro i) => FromAvro (Either9 a b c d e f g h i) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either9 a b c d e f g h i) Source #

(FromAvro a, FromAvro b, FromAvro c, FromAvro d, FromAvro e, FromAvro f, FromAvro g, FromAvro h, FromAvro i, FromAvro j) => FromAvro (Either10 a b c d e f g h i j) Source # 
Instance details

Defined in Data.Avro.EitherN

Methods

fromAvro :: Value -> Either String (Either10 a b c d e f g h i j) Source #

For internal use

data Value Source #

An intermediate data structute for decoding between Avro bytes and Haskell types.

Because reader and writer schemas, and therefore expected data types and layout can be different, deserialising bytes into Haskell types directly is not possible.

To overcome this issue this intermediate data structure is used: bytes are decoded into values of type Value (using reader's layout and rules) and then translated to target Haskell types using FromAvro type class machinery.

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

Methods

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

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

Show Value Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

NFData Value Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

Methods

rnf :: Value -> () #

type Rep Value Source # 
Instance details

Defined in Data.Avro.Encoding.FromAvro

type Rep Value = D1 ('MetaData "Value" "Data.Avro.Encoding.FromAvro" "avro-0.6.1.0-9WMp5t0QC4JDZvUJwEXo6V" 'False) (((C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Boolean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32)))) :+: ((C1 ('MetaCons "Long" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int64)) :+: C1 ('MetaCons "Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Float))) :+: (C1 ('MetaCons "Double" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "Bytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))) :+: ((C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Value))) :+: C1 ('MetaCons "Map" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap Text Value))))) :+: ((C1 ('MetaCons "Record" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Value))) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)))) :+: (C1 ('MetaCons "Fixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Enum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReadSchema) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))))))