avro-0.3.4.0: Avro serialization support for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Avro.Deriving

Contents

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 Rep DeriveOptions Source # 
Instance details

Defined in Data.Avro.Deriving

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

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 Rep FieldStrictness Source # 
Instance details

Defined in Data.Avro.Deriving

type Rep FieldStrictness = D1 (MetaData "FieldStrictness" "Data.Avro.Deriving" "avro-0.3.4.0-34hPSeedTkSEI2IMmRBubJ" False) (C1 (MetaCons "StrictField" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LazyField" PrefixI False) (U1 :: * -> *))

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 Rep FieldUnpackedness Source # 
Instance details

Defined in Data.Avro.Deriving

type Rep FieldUnpackedness = D1 (MetaData "FieldUnpackedness" "Data.Avro.Deriving" "avro-0.3.4.0-34hPSeedTkSEI2IMmRBubJ" False) (C1 (MetaCons "UnpackedField" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NonUnpackedField" PrefixI False) (U1 :: * -> *))

defaultDeriveOptions :: DeriveOptions Source #

Default deriving options

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

mkPrefixedFieldName :: TypeName -> 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 :: TypeName -> 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, Float, Double.

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 #

Generates Haskell classes and FromAvro and ToAvro instances given the Avro schema file

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

Generates Haskell classes and FromAvro and ToAvro instances given the Avro schema

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

Derives "read only" Avro from a given schema file. Generates data types and FromAvro.

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

Same as deriveAvroWithOptions but uses defaultDeriveOptions

deriveAvro' = deriveAvroWithOptions' defaultDeriveOptions

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

Derives "read only" Avro from a given schema file. Generates data types and FromAvro.