Safe Haskell | None |
---|---|
Language | Haskell2010 |
Avro encoding and decoding routines.
This library provides a high level interface for encoding (and decoding) Haskell values in Apache's Avro serialization format.
The goal is to match Aeson's API whenever reasonable, meaning user experience with one effectively translate to the other.
Avro RPC is not currently supported.
Library Structure
The library structure includes:
- This module, Data.Avro, providing a high-level interface via
classes of
FromAvro
andToAvro
for decoding and encoding values. - Data.Avro.Schema: Defines the type for Avro schema's and its JSON encoding/decoding.
- Data.Avro.Encode and Data.Avro.Decode: More efficient conversion capable of avoiding the intermediate representation. Also, the implementation of the en/decoding of the intermediate representation.
- Data.Avro.Decode.Lazy: Lazy/Streaming decoding for Avro containers.
- Data.Avro.Deconflict: translate decoded data from an encoder schema to the (potentially different) decoder's schema.
Synopsis
- type Schema = Type
- data Result a
- badValue :: Show t => t -> String -> Result a
- encode :: ToAvro a => a -> ByteString
- decode :: forall a. FromAvro a => ByteString -> Result a
- (.:) :: FromAvro a => HashMap Text (Value Type) -> Text -> Result a
- (.=) :: ToAvro a => Text -> a -> (Text, Value Type)
- record :: Foldable f => Type -> f (Text, Value Type) -> Value Type
- fixed :: Type -> ByteString -> Value Type
- decodeWithSchema :: FromAvro a => Schema -> ByteString -> Result a
- decodeContainer :: forall a. FromAvro a => ByteString -> [[a]]
- decodeContainerWithSchema :: FromAvro a => Schema -> ByteString -> [[a]]
- decodeContainerBytes :: ByteString -> [[ByteString]]
- encodeContainer :: forall a. ToAvro a => [[a]] -> IO ByteString
- encodeContainer' :: forall a. ToAvro a => Codec -> [[a]] -> IO ByteString
- encodeContainerWithSync :: forall a. ToAvro a => (Word64, Word64, Word64, Word64) -> [[a]] -> ByteString
- encodeContainerWithSync' :: forall a. ToAvro a => Codec -> (Word64, Word64, Word64, Word64) -> [[a]] -> ByteString
- class HasAvroSchema a => FromAvro a where
- class HasAvroSchema a => ToAvro a where
- class HasAvroSchema a where
- schemaOf :: HasAvroSchema a => a -> Type
- type Avro a = (FromAvro a, ToAvro a)
Schema
An Avro schema is either
- A "JSON object in the form
{"type":"typeName" ...}
- A "JSON string, naming a defined type" (basic type without free variables)
- A "JSON array, representing a union"
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
.
Encoding and decoding
Instances
encode :: ToAvro a => a -> ByteString Source #
Encodes a value to a lazy ByteString
decode :: forall a. FromAvro a => ByteString -> Result a Source #
Decode a lazy bytestring using a Schema
of the return type.
Working with containers
Decoding containers
decodeWithSchema :: FromAvro a => Schema -> ByteString -> Result a Source #
Decode a lazy bytestring using a provided schema
decodeContainer :: forall a. FromAvro a => ByteString -> [[a]] Source #
Decode a container and de-conflict the writer schema with
a reader schema for a return type.
Like in decodeContainerWithSchema
exceptions are thrown instead of a Result
type to
allow this function to be read lazy (to be done in some later version).
decodeContainerWithSchema :: FromAvro a => Schema -> ByteString -> [[a]] Source #
Decode a container and de-conflict the writer schema with a given
reader-schema. Exceptions are thrown instead of a Result
type to
allow this function to be read lazy (to be done in some later version).
decodeContainerBytes :: ByteString -> [[ByteString]] Source #
Like decodeContainer
but returns the avro-encoded bytes for each
object in the container instead of the Haskell type.
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.
Encoding containers
encodeContainer :: forall a. ToAvro a => [[a]] -> IO ByteString Source #
Encode chunks of objects into a container, using 16 random bytes for the synchronization markers.
encodeContainer' :: forall a. ToAvro a => Codec -> [[a]] -> IO ByteString Source #
encodeContainerWithSync :: forall a. ToAvro a => (Word64, Word64, Word64, Word64) -> [[a]] -> ByteString Source #
Encode chunks of objects into a container, using the provided ByteString as the synchronization markers.
encodeContainerWithSync' :: forall a. ToAvro a => Codec -> (Word64, Word64, Word64, Word64) -> [[a]] -> ByteString Source #
Encode chunks of objects into a container, using the provided ByteString as the synchronization markers.
Classes and instances
class HasAvroSchema a => FromAvro a where Source #
Instances
FromAvro Bool Source # | |
FromAvro Double Source # | |
FromAvro Float Source # | |
FromAvro Int Source # | |
FromAvro Int32 Source # | |
FromAvro Int64 Source # | |
FromAvro ByteString Source # | |
Defined in Data.Avro.FromAvro | |
FromAvro ByteString Source # | |
Defined in Data.Avro.FromAvro | |
FromAvro Text Source # | |
FromAvro Text Source # | |
FromAvro a => FromAvro [a] Source # | |
FromAvro a => FromAvro (Maybe a) Source # | |
(Unbox a, FromAvro a) => FromAvro (Vector a) Source # | |
FromAvro a => FromAvro (Vector a) Source # | |
(FromAvro a, FromAvro b) => FromAvro (Either a b) Source # | |
FromAvro a => FromAvro (HashMap Text a) Source # | |
FromAvro a => FromAvro (Map Text a) Source # | |
(FromAvro a, FromAvro b, FromAvro c) => FromAvro (Either3 a b c) Source # | |
(FromAvro a, FromAvro b, FromAvro c, FromAvro d) => FromAvro (Either4 a b c d) Source # | |
(FromAvro a, FromAvro b, FromAvro c, FromAvro d, FromAvro e) => FromAvro (Either5 a b c d e) Source # | |
class HasAvroSchema a => ToAvro a where Source #
Instances
class HasAvroSchema a where Source #
Instances
schemaOf :: HasAvroSchema a => a -> Type Source #