mu-schema-0.3.1.0: Format-independent schemas for serialization
Safe HaskellSafe-Inferred
LanguageHaskell2010

Mu.Schema.Definition

Description

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

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 (Symbols).

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.

Constructors

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

Instances details
FromSchema ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

KnownName n => KnownName ('DEnum n choices :: TypeDefB builtin typeName fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('DEnum n choices) -> String Source #

KnownName n => KnownName ('DRecord n fields :: TypeDefB builtin typeName fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('DRecord n fields) -> String Source #

newtype ChoiceDef fieldName Source #

Defines each of the choices in an enumeration.

Constructors

ChoiceDef fieldName

One single choice from an enumeration.

Instances

Instances details
FromSchema ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

KnownName n => KnownName ('ChoiceDef n :: ChoiceDef fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('ChoiceDef n) -> String Source #

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.

Constructors

FieldDef fieldName (FieldTypeB builtin typeName)

One single field in a record.

Instances

Instances details
FromSchema ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

GToSchemaRecord (sch :: Schema ts fs) (fmap :: Mappings Symbol fs) ('[] :: [FieldDef ts fs]) f Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchemaRecord :: Proxy fmap -> f a -> NP (Field sch) '[] Source #

(GToSchemaRecord sch fmap cs f, GToSchemaRecordSearch sch t f (FindSel f (MappingLeft fmap name))) => GToSchemaRecord (sch :: Schema typeName fieldName) (fmap :: Mappings Symbol fieldName) ('FieldDef name t ': cs :: [FieldDefB Type typeName fieldName]) f Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchemaRecord :: Proxy fmap -> f a -> NP (Field sch) ('FieldDef name t ': cs) Source #

KnownName n => KnownName ('FieldDef n t :: FieldDefB builtin typeName fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('FieldDef n t) -> String Source #

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.

Constructors

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.

Equations

'[] :/: name = TypeError (('Text "Cannot find type " :<>: 'ShowType name) :<>: 'Text " in the schema") 
('DRecord name fields ': rest) :/: name = 'DRecord name fields 
('DEnum name choices ': rest) :/: name = 'DEnum name choices 
(other ': rest) :/: name = rest :/: name 

One-to-one mappings

data Mapping a b Source #

Defines a mapping between two elements.

Constructors

a :-> b 

type Mappings a b = [Mapping a b] Source #

Defines a set of mappings between elements of a and b.

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.

Equations

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.

Equations

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.

Methods

nameVal :: proxy a -> String Source #

Instances

Instances details
KnownName 'False Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy 'False -> String Source #

KnownName 'True Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy 'True -> String Source #

KnownNat n => KnownName (n :: Nat) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy n -> String Source #

KnownSymbol s => KnownName (s :: Symbol) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy s -> String Source #

KnownName n => KnownName ('ChoiceDef n :: ChoiceDef fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('ChoiceDef n) -> String Source #

KnownName n => KnownName ('FieldDef n t :: FieldDefB builtin typeName fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('FieldDef n t) -> String Source #

KnownName n => KnownName ('DEnum n choices :: TypeDefB builtin typeName fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('DEnum n choices) -> String Source #

KnownName n => KnownName ('DRecord n fields :: TypeDefB builtin typeName fieldName) Source # 
Instance details

Defined in Mu.Schema.Definition

Methods

nameVal :: proxy ('DRecord n fields) -> String Source #