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, Avro
, providing a high-level interface via
classes of FromAvro
and ToAvro
for decoding and encoding values.
* Type
define the types of Avro data, providing a common
(intermediate) representation for any data that is encoded or decoded
by Data.Avro.
* Encode
and Decode
: More
efficient conversion capable of avoiding the intermediate representation.
Also, the implementation of the en/decoding of the intermediate
representation.
* Deconflict
: translate decoded data from an
encoder schema to the (potentially different) decoder's schema.
* Schema
: Defines the type for Avro schema's and its JSON
encoding/decoding.
Example decoding:
Let's say you have an ADT and related schema:
{--} import qualified Data.Avro.Types as Ty import Data.Avro.Schema import Data.Avro import Data.List.NonEmpty (NonEmpty(..)) data MyEnum = A | B | C | D deriving (Eq,Ord,Show,Enum,Generic) data MyStruct = MyStruct (Either MyEnum String) Int meSchema :: Schema meSchema = Schema $ mkEnum MyEnum [] Nothing Nothing [A,B,C,D] msSchema :: Schema msSchema = Struct MyStruct Nothing [] Nothing Nothing [ fld "enumOrString" eOrS (Just $ String "The Default") , fld "int" Int (Just (Ty.Int 1)) ] where fld nm ty def = Field nm [] Nothing Nothing ty def eOrS = mkUnion (meSchema :| [String]) instance ToAvro MyEnum where toAvro = toAvroEnum instance ToAvro MyStruct where toAvro (MyStruct ab i) = record [ "enumOrString" .= ab , "int" .= i ] main = do let val = MyStruct (Right Hello) 1 print (fromAvro (toAvro val) == Success val)
Synopsis
- class HasAvroSchema a => FromAvro a where
- class HasAvroSchema a => ToAvro a where
- class HasAvroSchema a where
- type Avro a = (FromAvro a, ToAvro 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
- data Result a
- badValue :: Value Type -> String -> Result a
- decode :: forall a. FromAvro a => ByteString -> Result a
- decodeWithSchema :: FromAvro a => Schema -> ByteString -> Result a
- decodeContainer :: forall a. FromAvro a => ByteString -> [[a]]
- decodeContainerWithSchema :: FromAvro a => Schema -> ByteString -> [[a]]
- decodeContainerBytes :: ByteString -> [[ByteString]]
- encode :: ToAvro a => a -> ByteString
- encodeContainer :: forall a. ToAvro a => [[a]] -> IO ByteString
- encodeContainerWithSync :: forall a. ToAvro a => (Word64, Word64, Word64, Word64) -> [[a]] -> ByteString
- schemaOf :: HasAvroSchema a => a -> Type
Documentation
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 # | |
(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
ToAvro Bool Source # | |
ToAvro Double Source # | |
ToAvro Float Source # | |
ToAvro Int Source # | |
ToAvro Int32 Source # | |
ToAvro Int64 Source # | |
ToAvro () Source # | |
ToAvro ByteString Source # | |
Defined in Data.Avro.ToAvro | |
ToAvro ByteString Source # | |
Defined in Data.Avro.ToAvro | |
ToAvro Text Source # | |
ToAvro Text Source # | |
ToAvro a => ToAvro [a] Source # | |
ToAvro a => ToAvro (Maybe a) Source # | |
(ToAvro a, ToAvro b) => ToAvro (Either a b) Source # | |
ToAvro a => ToAvro (HashMap String a) Source # | |
ToAvro a => ToAvro (HashMap Text a) Source # | |
ToAvro a => ToAvro (HashMap Text a) Source # | |
ToAvro a => ToAvro (Map String a) Source # | |
ToAvro a => ToAvro (Map Text a) Source # | |
ToAvro a => ToAvro (Map Text a) Source # | |
(ToAvro a, ToAvro b, ToAvro c) => ToAvro (Either3 a b c) Source # | |
(ToAvro a, ToAvro b, ToAvro c, ToAvro d) => ToAvro (Either4 a b c d) Source # | |
(ToAvro a, ToAvro b, ToAvro c, ToAvro d, ToAvro e) => ToAvro (Either5 a b c d e) Source # | |
class HasAvroSchema a where Source #
Instances
Instances
decode :: forall a. FromAvro a => ByteString -> Result a Source #
Decode a lazy bytestring using a Schema for the return type.
decodeWithSchema :: FromAvro a => Schema -> ByteString -> Result a Source #
Decode a lazy bytestring with 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.
encode :: ToAvro a => a -> ByteString Source #
Encodes a value to a lazy ByteString
encodeContainer :: forall a. ToAvro a => [[a]] -> IO ByteString Source #
Encode chunks of objects into a container, using 16 random bytes for the synchronization markers.
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
schemaOf :: HasAvroSchema a => a -> Type Source #