avro-0.4.2.0: Avro serialization support for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Avro.Decode.Lazy

Contents

Synopsis

Documentation

decodeAvro :: Schema -> ByteString -> LazyValue Type Source #

Decode bytes into a Value as described by Schema.

decodeContainer :: forall a. FromLazyAvro a => ByteString -> [Either String a] Source #

Decodes the container as a lazy list of values of the requested type.

The schema for the requested type will be de-conflicted with the schema embedded with the container.

Errors are reported as a part of the list and the list will stop at first error. This means that the consumer will get all the "good" content from the container until the error is detected, then this error and then the list is finished.

decodeContainer' :: forall a. FromLazyAvro a => ByteString -> Either String [[Either String a]] Source #

Decodes the container as a lazy list of values of the requested type.

The schema for the requested type will be de-conflicted with the schema embedded with the container.

The content of the container is returned as a list of "blocks" of values inside this container, so the notion of blocks in the container is preserved. Since decoding is lazy it should be safe to concat these values into one lazy list.

The "outer" error represents the error in opening the container itself (including problems like reading schemas embedded into the container.)

The "inner" errors represent problems in decoding individual values.

Note that this function will not stop decoding at the first occurance of the "inner" error, and will continue attempting decoding values, so it is possible to get Right after Left. It is up to the user to decide whether it is correct or not to continue after errors (most likely it will not be correct).

decodeContainer function makes a choice to stop after the first error.

decodeContainerWithSchema :: FromLazyAvro a => Schema -> ByteString -> [Either String a] Source #

Same as decodeContainer but uses provided schema as a reader schema for the container instead of the schema obtained from the type of a.

It is up to the user to make sure that the provided schema is compatible with a and with the container's writer schema.

decodeContainerWithSchema' :: FromLazyAvro a => Schema -> ByteString -> Either String [[Either String a]] Source #

Same as decodeContainer' but uses provided schema as a reader schema for the container instead of the schema obtained from the type of a.

It is up to the user to make sure that the provided schema is compatible with a and with the container's writer schema.

Bypass decoding

decodeRawBlocks :: ByteString -> Either String (Schema, [Either String (Int, ByteString)]) Source #

Reads the container as a list of blocks without decoding them into actual values.

This can be useful for streaming splitting merging Avro containers without paying the cost for Avro encoding/decoding.

Each block is returned as a raw ByteString annotated with the number of Avro values that are contained in this block.

The "outer" error represents the error in opening the container itself (including problems like reading schemas embedded into the container.)

Lower level interface

getContainerValues :: ByteString -> Either String (Schema, [[LazyValue Type]]) Source #

Decodes the container into a list of blocks of raw Avro values.

The content of the container is returned as a list of "blocks" of values inside this container, so the notion of blocks in the container is preserved. Since decoding is lazy it should be safe to concat these values into one lazy list.

Each LazyValue can be an Error and this function doesn't make any attempts of dealing with them leaving it up to the user.

The "outer" error represents the error in opening the container itself (including problems like reading schemas embedded into the container.)

getContainerValuesBytes :: ByteString -> Either String (Schema, [Either String ByteString]) Source #

Splits container into a list of individual avro-encoded values.

This is particularly useful when slicing up containers into one or more smaller files. By extracting the original bytestring it is possible to avoid re-encoding data.

getContainerValuesBytes' :: ByteString -> Either String (Schema, [Either String (Value Type, ByteString)]) Source #

Splits container into a list of individual avro-encoded values. This version provides both encoded and decoded values.

This is particularly useful when slicing up containers into one or more smaller files. By extracting the original bytestring it is possible to avoid re-encoding data.

class GetAvro a where Source #

Methods

getAvro :: Get a Source #

Instances
GetAvro Bool Source # 
Instance details

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get Bool Source #

GetAvro Double Source # 
Instance details

Defined in Data.Avro.Decode.Get

GetAvro Float Source # 
Instance details

Defined in Data.Avro.Decode.Get

GetAvro Int32 Source # 
Instance details

Defined in Data.Avro.Decode.Get

GetAvro Int64 Source # 
Instance details

Defined in Data.Avro.Decode.Get

GetAvro ByteString Source # 
Instance details

Defined in Data.Avro.Decode.Get

GetAvro ByteString Source # 
Instance details

Defined in Data.Avro.Decode.Get

GetAvro Text Source # 
Instance details

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get Text Source #

GetAvro String Source # 
Instance details

Defined in Data.Avro.Decode.Get

GetAvro ContainerHeader Source # 
Instance details

Defined in Data.Avro.Decode.Get

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

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get [a] Source #

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

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get (Maybe a) Source #

(GetAvro a, Ord a) => GetAvro (Set a) Source # 
Instance details

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get (Set a) Source #

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

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get (Vector a) Source #

GetAvro ty => GetAvro (Map Text ty) Source # 
Instance details

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get (Map Text ty) Source #

GetAvro a => GetAvro (Array Int a) Source # 
Instance details

Defined in Data.Avro.Decode.Get

Methods

getAvro :: Get (Array Int a) Source #

class HasAvroSchema a => FromLazyAvro a where Source #

FromLazyAvro is a clone of FromAvro except that it works for lazy values (LazyValue).

Decoding from LazyValue directly without converting to strict Value and then FromAvro can be very beneficial from the performance point of view.

Instances
FromLazyAvro Bool Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro Double Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro Float Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro Int Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro Int32 Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro Int64 Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro ByteString Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro ByteString Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro Text Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

FromLazyAvro Text Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.Decode.Lazy.FromLazyAvro

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

Defined in Data.Avro.EitherN

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

Defined in Data.Avro.EitherN

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

Defined in Data.Avro.EitherN

Methods

fromLazyAvro :: LazyValue Type -> Result (Either5 a b c d e) Source #

data LazyValue f Source #

Constructors

Null 
Boolean Bool 
Int Int32 
Long Int64 
Float Float 
Double Double 
Bytes ByteString 
String Text 
Array (Vector (LazyValue f))

Dynamically enforced monomorphic type.

Map (HashMap Text (LazyValue f))

Dynamically enforced monomorphic type

Record f (HashMap Text (LazyValue f)) 
Union (NonEmpty f) f (LazyValue f)

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

Fixed f ByteString 
Enum f Int Text

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

Error !String 
Instances
Eq f => Eq (LazyValue f) Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.LazyValue

Methods

(==) :: LazyValue f -> LazyValue f -> Bool #

(/=) :: LazyValue f -> LazyValue f -> Bool #

Show f => Show (LazyValue f) Source # 
Instance details

Defined in Data.Avro.Decode.Lazy.LazyValue

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