Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module gives a set of combinators to define schemas in the sense of Avro or Protocol Buffers.
In order to re-use definitions at both
the type and term levels, the actual
constructors are defined in types ending
with B
, and are parametrized by the type
used to describe identifiers.
The versions without the suffix set this
parameter to Type
, and are thought as the
API to be used in the type-level.
If you use reflectSchema
to obtain a term-
level representation, the parameter is set
to TypeRep
.
Synopsis
- type Schema' = Schema Symbol Symbol
- type Schema typeName fieldName = SchemaB Type typeName fieldName
- type SchemaB builtin typeName fieldName = [TypeDefB builtin typeName fieldName]
- type TypeDef = TypeDefB Type
- data TypeDefB builtin typeName fieldName
- newtype ChoiceDef fieldName = ChoiceDef fieldName
- type FieldDef = FieldDefB Type
- data FieldDefB builtin typeName fieldName = FieldDef fieldName (FieldTypeB builtin typeName)
- type FieldType = FieldTypeB Type
- data FieldTypeB builtin typeName
- = TNull
- | TPrimitive builtin
- | TSchematic typeName
- | TOption (FieldTypeB builtin typeName)
- | TList (FieldTypeB builtin typeName)
- | TMap (FieldTypeB builtin typeName) (FieldTypeB builtin typeName)
- | TUnion [FieldTypeB builtin typeName]
- type family (sch :: Schema t f) :/: (name :: t) :: TypeDef t f where ...
- data Mapping a b = a :-> b
- type Mappings a b = [Mapping a b]
- type family MappingRight (ms :: Mappings a b) (v :: a) :: b where ...
- type family MappingLeft (ms :: Mappings a b) (v :: b) :: a where ...
- reflectSchema :: ReflectSchema s => Proxy s -> SchemaB TypeRep String String
- reflectFields :: ReflectFields fs => Proxy fs -> [FieldDefB TypeRep String String]
- reflectChoices :: ReflectChoices cs => Proxy cs -> [ChoiceDef String]
- reflectFieldTypes :: ReflectFieldTypes ts => Proxy ts -> [FieldTypeB TypeRep String]
- reflectFieldType :: ReflectFieldType ty => Proxy ty -> FieldTypeB TypeRep String
- class KnownName (a :: k) where
Definition of schemas
type Schema' = Schema Symbol Symbol Source #
A set of type definitions,
where the names of types and fields are
defined by type-level strings (Symbol
s).
type Schema typeName fieldName = SchemaB Type typeName fieldName Source #
A set of type definitions.
In general, we can use any kind we want for
both type and field names, although in practice
you always want to use Symbol
.
type SchemaB builtin typeName fieldName = [TypeDefB builtin typeName fieldName] Source #
A set of type definitions, parametric on type representations.
type TypeDef = TypeDefB Type Source #
Defines a type in a schema. Each type can be: * a record: a list of key-value pairs, * an enumeration: an element of a list of choices, * a reference to a primitive type.
data TypeDefB builtin typeName fieldName Source #
Defines a type in a schema, parametric on type representations.
DRecord typeName [FieldDefB builtin typeName fieldName] | A list of key-value pairs. |
DEnum typeName [ChoiceDef fieldName] | An element of a list of choices. |
DSimple (FieldTypeB builtin typeName) | A reference to a primitive type. |
Instances
newtype ChoiceDef fieldName Source #
Defines each of the choices in an enumeration.
ChoiceDef fieldName | One single choice from an enumeration. |
Instances
type FieldDef = FieldDefB Type Source #
Defines a field in a record by a name and the corresponding type.
data FieldDefB builtin typeName fieldName Source #
Defines a field in a record, parametric on type representations.
FieldDef fieldName (FieldTypeB builtin typeName) | One single field in a record. |
Instances
type FieldType = FieldTypeB Type Source #
Types of fields of a record.
References to other types in the same schema
are done via the TSchematic
constructor.
data FieldTypeB builtin typeName Source #
Types of fields of a record, parametric on type representations.
TNull | Null, as found in Avro. |
TPrimitive builtin | Reference to a primitive type, such as integers or Booleans. The set of supported primitive types depends on the protocol. |
TSchematic typeName | Reference to another type in the schema. |
TOption (FieldTypeB builtin typeName) | Optional value. |
TList (FieldTypeB builtin typeName) | List of values. |
TMap (FieldTypeB builtin typeName) (FieldTypeB builtin typeName) | Map of values. The set of supported key types depends on the protocol. |
TUnion [FieldTypeB builtin typeName] | Represents a choice between types. |
type family (sch :: Schema t f) :/: (name :: t) :: TypeDef t f where ... Source #
Lookup a type in a schema by its name.
One-to-one mappings
Finding correspondences
type family MappingRight (ms :: Mappings a b) (v :: a) :: b where ... Source #
Finds the corresponding right value of v
in a mapping ms
. When the kinds are Symbol
,
return the same value if not found.
When the return type is Type
, return ' ()'
if the value is not found.
MappingRight '[] (v :: Symbol) = v :: Symbol | |
MappingRight '[] (v :: Symbol) = () :: Type | |
MappingRight '[] v = TypeError ('Text "Cannot find value " :<>: 'ShowType v) | |
MappingRight ((x :-> y) ': rest) x = y | |
MappingRight (other ': rest) x = MappingRight rest x |
type family MappingLeft (ms :: Mappings a b) (v :: b) :: a where ... Source #
Finds the corresponding left value of v
in a mapping ms
. When the kinds are Symbol
,
return the same value if not found.
When the return type is Type
, return ' ()'
if the value is not found.
MappingLeft '[] (v :: Symbol) = v :: Symbol | |
MappingLeft '[] (v :: Symbol) = () :: Type | |
MappingLeft '[] v = TypeError ('Text "Cannot find value " :<>: 'ShowType v) | |
MappingLeft ((x :-> y) ': rest) y = x | |
MappingLeft (other ': rest) y = MappingLeft rest y |
Reflection to term-level
reflectSchema :: ReflectSchema s => Proxy s -> SchemaB TypeRep String String Source #
Reflect a schema into term-level.
reflectFields :: ReflectFields fs => Proxy fs -> [FieldDefB TypeRep String String] Source #
Reflect a list of fields into term-level.
reflectChoices :: ReflectChoices cs => Proxy cs -> [ChoiceDef String] Source #
Reflect a list of enumeration choices into term-level.
reflectFieldTypes :: ReflectFieldTypes ts => Proxy ts -> [FieldTypeB TypeRep String] Source #
Reflect a list of schema types into term-level.
reflectFieldType :: ReflectFieldType ty => Proxy ty -> FieldTypeB TypeRep String Source #
Reflect a schema type into term-level.
Supporting type classes
class KnownName (a :: k) where Source #
Type names and field names can be of any
kind, but for many uses we need a way
to turn them into strings at run-time.
This class generalizes KnownSymbol
.
Instances
KnownName 'False Source # | |
KnownName 'True Source # | |
KnownNat n => KnownName (n :: Nat) Source # | |
Defined in Mu.Schema.Definition | |
KnownSymbol s => KnownName (s :: Symbol) Source # | |
Defined in Mu.Schema.Definition | |
KnownName n => KnownName ('ChoiceDef n :: ChoiceDef fieldName) Source # | |
KnownName n => KnownName ('FieldDef n t :: FieldDefB builtin typeName fieldName) Source # | |
KnownName n => KnownName ('DEnum n choices :: TypeDefB builtin typeName fieldName) Source # | |
KnownName n => KnownName ('DRecord n fields :: TypeDefB builtin typeName fieldName) Source # | |