avro-0.4.5.2: Avro serialization support for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Avro.Deriving

Contents

Description

This module lets us derive Haskell types from an Avro schema that can be serialized/deserialzed to Avro.

Synopsis

Deriving options

data DeriveOptions Source #

Derives Avro from a given schema file. Generates data types, FromAvro and ToAvro instances.

Constructors

DeriveOptions 

Fields

Instances
Generic DeriveOptions Source # 
Instance details

Defined in Data.Avro.Deriving

Associated Types

type Rep DeriveOptions :: Type -> Type #

type Rep DeriveOptions Source # 
Instance details

Defined in Data.Avro.Deriving

type Rep DeriveOptions = D1 (MetaData "DeriveOptions" "Data.Avro.Deriving" "avro-0.4.5.2-89PDjFG31L32zdZgn3H2TD" False) (C1 (MetaCons "DeriveOptions" PrefixI True) (S1 (MetaSel (Just "fieldNameBuilder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Text -> Field -> Text)) :*: (S1 (MetaSel (Just "fieldRepresentation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeName -> Field -> (FieldStrictness, FieldUnpackedness))) :*: S1 (MetaSel (Just "namespaceBehavior") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NamespaceBehavior))))

data FieldStrictness Source #

Describes the strictness of a field for a derived data type. The field will be derived as if it were written with a !.

Constructors

StrictField 
LazyField 
Instances
Generic FieldStrictness Source # 
Instance details

Defined in Data.Avro.Deriving

Associated Types

type Rep FieldStrictness :: Type -> Type #

type Rep FieldStrictness Source # 
Instance details

Defined in Data.Avro.Deriving

type Rep FieldStrictness = D1 (MetaData "FieldStrictness" "Data.Avro.Deriving" "avro-0.4.5.2-89PDjFG31L32zdZgn3H2TD" False) (C1 (MetaCons "StrictField" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LazyField" PrefixI False) (U1 :: Type -> Type))

data FieldUnpackedness Source #

Describes the representation of a field for a derived data type. The field will be derived as if it were written with an {--} pragma.

Instances
Generic FieldUnpackedness Source # 
Instance details

Defined in Data.Avro.Deriving

Associated Types

type Rep FieldUnpackedness :: Type -> Type #

type Rep FieldUnpackedness Source # 
Instance details

Defined in Data.Avro.Deriving

type Rep FieldUnpackedness = D1 (MetaData "FieldUnpackedness" "Data.Avro.Deriving" "avro-0.4.5.2-89PDjFG31L32zdZgn3H2TD" False) (C1 (MetaCons "UnpackedField" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NonUnpackedField" PrefixI False) (U1 :: Type -> Type))

data NamespaceBehavior Source #

How to treat Avro namespaces in the generated Haskell types.

Constructors

IgnoreNamespaces

Namespaces are ignored completely. Haskell identifiers are generated from types' base names. This produces nicer types but fails on valid Avro schemas where the same base name occurs in different namespaces.

The Avro type com.example.Foo would generate the Haskell type Foo. If Foo had a field called bar, the generated Haskell record would have a field called fooBar.

HandleNamespaces

Haskell types and field names are generated with namespaces. See deriveAvroWithNamespaces for an example of how this works.

The Avro type com.example.Foo would generate the Haskell type ComexampleFoo. If Foo had a field called bar, the generated Haskell record would have the field comexampleFooBar.

defaultDeriveOptions :: DeriveOptions Source #

Default deriving options

defaultDeriveOptions = DeriveOptions
  { fieldNameBuilder  = mkPrefixedFieldName
  , fieldStrictness   = mkLazyField
  , namespaceBehavior = IgnoreNamespaces
  }

mkPrefixedFieldName :: Text -> Field -> Text Source #

Generates a field name that is prefixed with the type name.

For example, if the schema defines type Person that has a field firstName, then the generated Haskell type will be like

Person { personFirstName :: Text }

mkAsIsFieldName :: Text -> Field -> Text Source #

Generates a field name that matches the field name in schema (sanitised for Haskell, so first letter is lower cased)

For example, if the schema defines type Person that has a field firstName, then the generated Haskell type will be like

Person { firstName :: Text }

You may want to enable DuplicateRecordFields if you want to use this method.

mkLazyField :: TypeName -> Field -> (FieldStrictness, FieldUnpackedness) Source #

Marks any field as non-strict in the generated data types.

mkStrictPrimitiveField :: TypeName -> Field -> (FieldStrictness, FieldUnpackedness) Source #

Make a field strict and unpacked if it has a primitive representation. Primitive types are types which GHC has either a static or an unlifted representation: `()`, Boolean, Int32, Int64, Type, Type.

Deriving Haskell types from Avro schema

makeSchema :: FilePath -> Q Exp Source #

Generates the value of type Schema that it can later be used with deriveAvro' or deriveAvroWithOptions'.

mySchema :: Schema
mySchema = $(makeSchema "schemas/my-schema.avsc")

deriveAvroWithOptions :: DeriveOptions -> FilePath -> Q [Dec] Source #

Derives Haskell types from the given Avro schema file. These Haskell types support both reading and writing to Avro.

For an Avro schema with a top-level record called com.example.Foo, this generates:

  • a Schema with the name schema'Foo or schemacom'exampleFoo, depending on the namespaceBehavior setting.
  • Haskell types for each named type defined in the schema
  • HasSchema instances for each type
  • FromAvro instances for each type
  • ToAvro instances for each type

This function ignores namespaces when generated Haskell type and field names. This will fail on valid Avro schemas which contain types with the same base name in different namespaces. It will also fail for schemas that contain types with base names that are the same except for the capitalization of the first letter.

The type com.example.Foo will generate a Haskell type Foo. If com.example.Foo has a field named Bar, the field in the Haskell record will be called fooBar.

deriveAvroWithOptions' :: DeriveOptions -> Schema -> Q [Dec] Source #

Derive Haskell types from the given Avro schema.

For an Avro schema with a top-level definition com.example.Foo, this generates:

  • a Schema with the name schema'Foo or schemacom'exampleFoo depending on namespace handling
  • Haskell types for each named type defined in the schema
  • HasSchema instances for each type
  • FromAvro instances for each type
  • ToAvro instances for each type

deriveFromAvroWithOptions :: DeriveOptions -> FilePath -> Q [Dec] Source #

Derives "read only" Avro from a given schema file. For a schema with a top-level definition com.example.Foo, this generates:

  • a Schema value with the name schema'Foo
  • Haskell types for each named type defined in the schema
  • HasSchema instances for each type
  • FromAvro instances for each type

deriveAvroFromByteString :: ByteString -> Q [Dec] Source #

Same as deriveAvro but takes a ByteString rather than FilePath

deriveFromAvro :: FilePath -> Q [Dec] Source #

Same as deriveFromAvroWithOptions but uses defaultDeriveOptions.

deriveFromAvro = deriveFromAvroWithOptions defaultDeriveOptions