Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module lets us derive Haskell types from an Avro schema that can be serialized/deserialzed to Avro.
Synopsis
- data DeriveOptions = DeriveOptions {
- fieldNameBuilder :: Text -> Field -> Text
- fieldRepresentation :: TypeName -> Field -> (FieldStrictness, FieldUnpackedness)
- namespaceBehavior :: NamespaceBehavior
- data FieldStrictness
- data FieldUnpackedness
- data NamespaceBehavior
- = IgnoreNamespaces
- | HandleNamespaces
- | Custom (Text -> [Text] -> Text)
- defaultDeriveOptions :: DeriveOptions
- mkPrefixedFieldName :: Text -> Field -> Text
- mkAsIsFieldName :: Text -> Field -> Text
- mkLazyField :: TypeName -> Field -> (FieldStrictness, FieldUnpackedness)
- mkStrictPrimitiveField :: TypeName -> Field -> (FieldStrictness, FieldUnpackedness)
- makeSchema :: FilePath -> Q Exp
- makeSchemaFrom :: FilePath -> Text -> Q Exp
- makeSchemaFromByteString :: ByteString -> Q Exp
- deriveAvroWithOptions :: DeriveOptions -> FilePath -> Q [Dec]
- deriveAvroWithOptions' :: DeriveOptions -> Schema -> Q [Dec]
- deriveAvroFromByteString :: ByteString -> Q [Dec]
- deriveAvro :: FilePath -> Q [Dec]
- deriveAvro' :: Schema -> Q [Dec]
- r :: QuasiQuoter
Deriving options
data DeriveOptions Source #
Derives Avro from a given schema file. Generates data types, FromAvro and ToAvro instances.
DeriveOptions | |
|
Instances
Generic DeriveOptions Source # | |
Defined in Data.Avro.Deriving type Rep DeriveOptions :: Type -> Type # from :: DeriveOptions -> Rep DeriveOptions x # to :: Rep DeriveOptions x -> DeriveOptions # | |
type Rep DeriveOptions Source # | |
Defined in Data.Avro.Deriving type Rep DeriveOptions = D1 ('MetaData "DeriveOptions" "Data.Avro.Deriving" "avro-0.6.0.0-DoOm2DJah3nIktWo4nyiQe" '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 !
.
Instances
Generic FieldStrictness Source # | |
Defined in Data.Avro.Deriving type Rep FieldStrictness :: Type -> Type # from :: FieldStrictness -> Rep FieldStrictness x # to :: Rep FieldStrictness x -> FieldStrictness # | |
type Rep FieldStrictness Source # | |
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 # | |
Defined in Data.Avro.Deriving type Rep FieldUnpackedness :: Type -> Type # from :: FieldUnpackedness -> Rep FieldUnpackedness x # to :: Rep FieldUnpackedness x -> FieldUnpackedness # | |
type Rep FieldUnpackedness Source # | |
Defined in Data.Avro.Deriving |
data NamespaceBehavior Source #
How to treat Avro namespaces in the generated Haskell types.
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 |
HandleNamespaces | Haskell types and field names are generated with
namespaces. See The Avro type |
Custom (Text -> [Text] -> Text) | Provide a custom mapping from the name of the Avro type and its namespace that will be used to generate Haskell types and fields. |
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.
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 nameschema'Foo
orschema
, depending on thecom'example
FoonamespaceBehavior
setting. - Haskell types for each named type defined in the schema
HasSchema
instances for each typeFromAvro
instances for each typeToAvro
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:
deriveAvroFromByteString :: ByteString -> Q [Dec] Source #
Same as deriveAvro
but takes a ByteString rather than FilePath
deriveAvro :: FilePath -> Q [Dec] Source #
Same as deriveAvroWithOptions
but uses defaultDeriveOptions
deriveAvro =deriveAvroWithOptions
defaultDeriveOptions
deriveAvro' :: Schema -> Q [Dec] Source #
Same as deriveAvroWithOptions'
but uses defaultDeriveOptions
deriveAvro' =deriveAvroWithOptions'
defaultDeriveOptions
Re-exporting a quasiquoter for raw string literals
r :: QuasiQuoter #
A quasiquoter for raw string literals - that is, string literals that don't
recognise the standard escape sequences (such as '\n'
). Basically, they
make your code more readable by freeing you from the responsibility to escape
backslashes. They are useful when working with regular expressions, DOS/Windows
paths and markup languages (such as XML).
Don't forget the LANGUAGE QuasiQuotes
pragma if you're using this
module in your code.
Usage:
ghci> :set -XQuasiQuotes ghci> import Text.RawString.QQ ghci> let s = [r|\w+@[a-zA-Z_]+?\.[a-zA-Z]{2,3}|] ghci> s "\\w+@[a-zA-Z_]+?\\.[a-zA-Z]{2,3}" ghci> [r|C:\Windows\SYSTEM|] ++ [r|\user32.dll|] "C:\\Windows\\SYSTEM\\user32.dll"
Multiline raw string literals are also supported:
multiline :: String multiline = [r|<HTML> <HEAD> <TITLE>Auto-generated html formated source</TITLE> <META HTTP-EQUIV="Content-Type" CONTENT="text/html; charset=windows-1252"> </HEAD> <BODY LINK="800080" BGCOLOR="#ffffff"> <P> </P> <PRE>|]
Caveat: since the "|]"
character sequence is used to terminate the
quasiquotation, you can't use it inside the raw string literal. Use rQ
if you
want to embed that character sequence inside the raw string.
For more on raw strings, see e.g. http://www.open-std.org/jtc1/sc22/wg21/docs/papers/2006/n2053.html
For more on quasiquotation, see http://www.haskell.org/haskellwiki/Quasiquotation