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

Mu.Schema

Description

Definition and interpretation of schemas in the vein of Avro, Protocol Buffers, or JSON Schema.

Each Schema is made out of types (which in turn be records or enumerations). A value which obbeys such a schema is called a Term. Conversion between Haskell types and schema types is mediated by the type classes ToSchema and FromSchema.

Synopsis

Schema definition

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 Schema' = Schema Symbol Symbol Source #

A set of type definitions, where the names of types and fields are defined by type-level strings (Symbols).

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 #

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.

Lookup type in schema

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 

Interpretation of schemas

data Term (sch :: Schema typeName fieldName) (t :: TypeDef typeName fieldName) where Source #

Interpretation of a type in a schema.

Constructors

TRecord :: NP (Field sch) args -> Term sch ('DRecord name args)

A record given by the value of its fields.

TEnum :: NS Proxy choices -> Term sch ('DEnum name choices)

An enumeration given by one choice.

TSimple :: FieldValue sch t -> Term sch ('DSimple t)

A primitive value.

Instances

Instances details
(sch :/: sty) ~ ('DEnum sty choices :: TypeDefB Type typeName fieldName) => FromSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DEnum sty choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

fromSchema :: Term sch (sch :/: sty) -> Term sch ('DEnum sty choices) Source #

(sch :/: sty) ~ 'DRecord sty fields => FromSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DRecord sty fields)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

fromSchema :: Term sch (sch :/: sty) -> Term sch ('DRecord sty fields) Source #

(sch :/: sty) ~ ('DEnum sty choices :: TypeDefB Type typeName fieldName) => ToSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DEnum sty choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchema :: Term sch ('DEnum sty choices) -> Term sch (sch :/: sty) Source #

(sch :/: sty) ~ 'DRecord sty fields => ToSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DRecord sty fields)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchema :: Term sch ('DRecord sty fields) -> Term sch (sch :/: sty) Source #

Eq (FieldValue sch t) => Eq (Term sch ('DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Term sch ('DSimple t) -> Term sch ('DSimple t) -> Bool #

(/=) :: Term sch ('DSimple t) -> Term sch ('DSimple t) -> Bool #

All (Compose Eq (Proxy :: ChoiceDef fieldName -> Type)) choices => Eq (Term sch ('DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Term sch ('DEnum name choices) -> Term sch ('DEnum name choices) -> Bool #

(/=) :: Term sch ('DEnum name choices) -> Term sch ('DEnum name choices) -> Bool #

All (Compose Eq (Field sch)) args => Eq (Term sch ('DRecord name args)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Term sch ('DRecord name args) -> Term sch ('DRecord name args) -> Bool #

(/=) :: Term sch ('DRecord name args) -> Term sch ('DRecord name args) -> Bool #

Show (FieldValue sch t) => Show (Term sch ('DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Term sch ('DSimple t) -> ShowS #

show :: Term sch ('DSimple t) -> String #

showList :: [Term sch ('DSimple t)] -> ShowS #

(KnownName name, All (KnownName :: ChoiceDef fieldName -> Constraint) choices, All (Compose Show (Proxy :: ChoiceDef fieldName -> Type)) choices) => Show (Term sch ('DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Term sch ('DEnum name choices) -> ShowS #

show :: Term sch ('DEnum name choices) -> String #

showList :: [Term sch ('DEnum name choices)] -> ShowS #

(KnownName name, All (Compose Show (Field sch)) args) => Show (Term sch ('DRecord name args)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Term sch ('DRecord name args) -> ShowS #

show :: Term sch ('DRecord name args) -> String #

showList :: [Term sch ('DRecord name args)] -> ShowS #

ToJSON (FieldValue sch t) => ToJSON (Term sch ('DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: Term sch ('DSimple t) -> Value #

toEncoding :: Term sch ('DSimple t) -> Encoding #

toJSONList :: [Term sch ('DSimple t)] -> Value #

toEncodingList :: [Term sch ('DSimple t)] -> Encoding #

ToJSONFields sch args => ToJSON (Term sch ('DRecord name args)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: Term sch ('DRecord name args) -> Value #

toEncoding :: Term sch ('DRecord name args) -> Encoding #

toJSONList :: [Term sch ('DRecord name args)] -> Value #

toEncodingList :: [Term sch ('DRecord name args)] -> Encoding #

ToJSONEnum choices => ToJSON (Term sch ('DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: Term sch ('DEnum name choices) -> Value #

toEncoding :: Term sch ('DEnum name choices) -> Encoding #

toJSONList :: [Term sch ('DEnum name choices)] -> Value #

toEncodingList :: [Term sch ('DEnum name choices)] -> Encoding #

FromJSON (FieldValue sch t) => FromJSON (Term sch ('DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (Term sch ('DSimple t)) #

parseJSONList :: Value -> Parser [Term sch ('DSimple t)] #

FromJSONFields sch args => FromJSON (Term sch ('DRecord name args)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (Term sch ('DRecord name args)) #

parseJSONList :: Value -> Parser [Term sch ('DRecord name args)] #

FromJSONEnum choices => FromJSON (Term sch ('DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (Term sch ('DEnum name choices)) #

parseJSONList :: Value -> Parser [Term sch ('DEnum name choices)] #

data Field (sch :: Schema typeName fieldName) (f :: FieldDef typeName fieldName) where Source #

Interpretation of a field.

Constructors

Field :: FieldValue sch t -> Field sch ('FieldDef name t)

A single field. Note that the contents are wrapped in a w type constructor.

Instances

Instances details
Eq (FieldValue sch t) => Eq (Field sch ('FieldDef name t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Field sch ('FieldDef name t) -> Field sch ('FieldDef name t) -> Bool #

(/=) :: Field sch ('FieldDef name t) -> Field sch ('FieldDef name t) -> Bool #

(KnownName name, Show (FieldValue sch t)) => Show (Field sch ('FieldDef name t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Field sch ('FieldDef name t) -> ShowS #

show :: Field sch ('FieldDef name t) -> String #

showList :: [Field sch ('FieldDef name t)] -> ShowS #

data FieldValue (sch :: Schema typeName fieldName) (t :: FieldType typeName) where Source #

Interpretation of a field type, by giving a value of that type.

Constructors

FNull :: FieldValue sch 'TNull

Null value, as found in Avro and JSON.

FPrimitive :: t -> FieldValue sch ('TPrimitive t)

Value of a primitive type.

FSchematic :: Term sch (sch :/: t) -> FieldValue sch ('TSchematic t)

Term of another type in the schema.

FOption :: Maybe (FieldValue sch t) -> FieldValue sch ('TOption t)

Optional value.

FList :: [FieldValue sch t] -> FieldValue sch ('TList t)

List of values.

FMap :: Ord (FieldValue sch k) => Map (FieldValue sch k) (FieldValue sch v) -> FieldValue sch ('TMap k v)

Dictionary (key-value map) of values.

FUnion :: NS (FieldValue sch) choices -> FieldValue sch ('TUnion choices)

One single value of one of the specified types.

Instances

Instances details
All (Compose Eq (FieldValue sch)) choices => Eq (FieldValue sch ('TUnion choices)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> Bool #

(/=) :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> Bool #

(Eq (FieldValue sch k), Eq (FieldValue sch v)) => Eq (FieldValue sch ('TMap k v)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> Bool #

(/=) :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> Bool #

Eq (FieldValue sch t) => Eq (FieldValue sch ('TList t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> Bool #

(/=) :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> Bool #

Eq (FieldValue sch t) => Eq (FieldValue sch ('TOption t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> Bool #

(/=) :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> Bool #

Eq (Term sch (sch :/: t)) => Eq (FieldValue sch ('TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> Bool #

(/=) :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> Bool #

Eq t => Eq (FieldValue sch ('TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> Bool #

(/=) :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> Bool #

Eq (FieldValue sch ('TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue sch 'TNull -> FieldValue sch 'TNull -> Bool #

(/=) :: FieldValue sch 'TNull -> FieldValue sch 'TNull -> Bool #

(All (Compose Ord (FieldValue sch)) choices, All (Compose Eq (FieldValue sch)) choices) => Ord (FieldValue sch ('TUnion choices)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> Ordering #

(<) :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> Bool #

(<=) :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> Bool #

(>) :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> Bool #

(>=) :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> Bool #

max :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) #

min :: FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) -> FieldValue sch ('TUnion choices) #

(Ord (FieldValue sch k), Ord (FieldValue sch v)) => Ord (FieldValue sch ('TMap k v)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> Ordering #

(<) :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> Bool #

(<=) :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> Bool #

(>) :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> Bool #

(>=) :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> Bool #

max :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) #

min :: FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) -> FieldValue sch ('TMap k v) #

Ord (FieldValue sch t) => Ord (FieldValue sch ('TList t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> Ordering #

(<) :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> Bool #

(<=) :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> Bool #

(>) :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> Bool #

(>=) :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> Bool #

max :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> FieldValue sch ('TList t) #

min :: FieldValue sch ('TList t) -> FieldValue sch ('TList t) -> FieldValue sch ('TList t) #

Ord (FieldValue sch t) => Ord (FieldValue sch ('TOption t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> Ordering #

(<) :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> Bool #

(<=) :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> Bool #

(>) :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> Bool #

(>=) :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> Bool #

max :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) #

min :: FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) -> FieldValue sch ('TOption t) #

Ord (Term sch (sch :/: t)) => Ord (FieldValue sch ('TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> Ordering #

(<) :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> Bool #

(<=) :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> Bool #

(>) :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> Bool #

(>=) :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> Bool #

max :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) #

min :: FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) -> FieldValue sch ('TSchematic t) #

Ord t => Ord (FieldValue sch ('TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> Ordering #

(<) :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> Bool #

(<=) :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> Bool #

(>) :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> Bool #

(>=) :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> Bool #

max :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) #

min :: FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) -> FieldValue sch ('TPrimitive t) #

Ord (FieldValue sch ('TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

All (Compose Show (FieldValue sch)) choices => Show (FieldValue sch ('TUnion choices)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue sch ('TUnion choices) -> ShowS #

show :: FieldValue sch ('TUnion choices) -> String #

showList :: [FieldValue sch ('TUnion choices)] -> ShowS #

(Show (FieldValue sch k), Show (FieldValue sch v)) => Show (FieldValue sch ('TMap k v)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue sch ('TMap k v) -> ShowS #

show :: FieldValue sch ('TMap k v) -> String #

showList :: [FieldValue sch ('TMap k v)] -> ShowS #

Show (FieldValue sch t) => Show (FieldValue sch ('TList t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue sch ('TList t) -> ShowS #

show :: FieldValue sch ('TList t) -> String #

showList :: [FieldValue sch ('TList t)] -> ShowS #

Show (FieldValue sch t) => Show (FieldValue sch ('TOption t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue sch ('TOption t) -> ShowS #

show :: FieldValue sch ('TOption t) -> String #

showList :: [FieldValue sch ('TOption t)] -> ShowS #

Show (Term sch (sch :/: t)) => Show (FieldValue sch ('TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue sch ('TSchematic t) -> ShowS #

show :: FieldValue sch ('TSchematic t) -> String #

showList :: [FieldValue sch ('TSchematic t)] -> ShowS #

Show t => Show (FieldValue sch ('TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue sch ('TPrimitive t) -> ShowS #

show :: FieldValue sch ('TPrimitive t) -> String #

showList :: [FieldValue sch ('TPrimitive t)] -> ShowS #

Show (FieldValue sch ('TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

(ToJSONKey (FieldValue sch k), ToJSON (FieldValue sch v)) => ToJSON (FieldValue sch ('TMap k v)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: FieldValue sch ('TMap k v) -> Value #

toEncoding :: FieldValue sch ('TMap k v) -> Encoding #

toJSONList :: [FieldValue sch ('TMap k v)] -> Value #

toEncodingList :: [FieldValue sch ('TMap k v)] -> Encoding #

ToJSON (FieldValue sch t) => ToJSON (FieldValue sch ('TList t)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: FieldValue sch ('TList t) -> Value #

toEncoding :: FieldValue sch ('TList t) -> Encoding #

toJSONList :: [FieldValue sch ('TList t)] -> Value #

toEncodingList :: [FieldValue sch ('TList t)] -> Encoding #

ToJSON (FieldValue sch t) => ToJSON (FieldValue sch ('TOption t)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSON (Term sch (sch :/: t)) => ToJSON (FieldValue sch ('TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSON t => ToJSON (FieldValue sch ('TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSON (FieldValue sch ('TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSONUnion sch us => ToJSON (FieldValue sch ('TUnion us)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: FieldValue sch ('TUnion us) -> Value #

toEncoding :: FieldValue sch ('TUnion us) -> Encoding #

toJSONList :: [FieldValue sch ('TUnion us)] -> Value #

toEncodingList :: [FieldValue sch ('TUnion us)] -> Encoding #

ToJSONKey t => ToJSONKey (FieldValue sch ('TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

(FromJSONKey (FieldValue sch k), FromJSON (FieldValue sch v), Ord (FieldValue sch k)) => FromJSON (FieldValue sch ('TMap k v)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (FieldValue sch ('TMap k v)) #

parseJSONList :: Value -> Parser [FieldValue sch ('TMap k v)] #

FromJSON (FieldValue sch t) => FromJSON (FieldValue sch ('TList t)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (FieldValue sch ('TList t)) #

parseJSONList :: Value -> Parser [FieldValue sch ('TList t)] #

FromJSON (FieldValue sch t) => FromJSON (FieldValue sch ('TOption t)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSON (Term sch (sch :/: t)) => FromJSON (FieldValue sch ('TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSON t => FromJSON (FieldValue sch ('TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSON (FieldValue sch ('TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSONUnion sch us => FromJSON (FieldValue sch ('TUnion us)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (FieldValue sch ('TUnion us)) #

parseJSONList :: Value -> Parser [FieldValue sch ('TUnion us)] #

FromJSONKey t => FromJSONKey (FieldValue sch ('TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

data NS (a :: k -> Type) (b :: [k]) where #

An n-ary sum.

The sum is parameterized by a type constructor f and indexed by a type-level list xs. The length of the list determines the number of choices in the sum and if the i-th element of the list is of type x, then the i-th choice of the sum is of type f x.

The constructor names are chosen to resemble Peano-style natural numbers, i.e., Z is for "zero", and S is for "successor". Chaining S and Z chooses the corresponding component of the sum.

Examples:

Z         :: f x -> NS f (x ': xs)
S . Z     :: f y -> NS f (x ': y ': xs)
S . S . Z :: f z -> NS f (x ': y ': z ': xs)
...

Note that empty sums (indexed by an empty list) have no non-bottom elements.

Two common instantiations of f are the identity functor I and the constant functor K. For I, the sum becomes a direct generalization of the Either type to arbitrarily many choices. For K a, the result is a homogeneous choice type, where the contents of the type-level list are ignored, but its length specifies the number of options.

In the context of the SOP approach to generic programming, an n-ary sum describes the top-level structure of a datatype, which is a choice between all of its constructors.

Examples:

Z (I 'x')      :: NS I       '[ Char, Bool ]
S (Z (I True)) :: NS I       '[ Char, Bool ]
S (Z (K 1))    :: NS (K Int) '[ Char, Bool ]

Constructors

Z :: forall k (a :: k -> Type) (x :: k) (xs :: [k]). a x -> NS a (x ': xs) 
S :: forall k (a :: k -> Type) (xs :: [k]) (x :: k). NS a xs -> NS a (x ': xs) 

Instances

Instances details
HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod NS) (LiftedCoercible f g) xs ys => NS f xs -> NS g ys #

HAp (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod NS (f -.-> g) xs -> NS f xs -> NS g xs #

HCollapse (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN NS xs => NS (K a) xs -> CollapseTo NS a #

HTraverse_ (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () #

HSequence (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

HIndex (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type) (xs :: l). NS f xs -> Int #

HApInjs (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type). SListIN NS xs => Prod NS f xs -> [NS f xs] #

HExpand (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN (Prod NS) xs => (forall (x :: k0). f x) -> NS f xs -> Prod NS f xs #

hcexpand :: forall c (xs :: l) proxy f. AllN (Prod NS) c xs => proxy c -> (forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs #

All (Compose Eq f) xs => Eq (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

(==) :: NS f xs -> NS f xs -> Bool #

(/=) :: NS f xs -> NS f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

compare :: NS f xs -> NS f xs -> Ordering #

(<) :: NS f xs -> NS f xs -> Bool #

(<=) :: NS f xs -> NS f xs -> Bool #

(>) :: NS f xs -> NS f xs -> Bool #

(>=) :: NS f xs -> NS f xs -> Bool #

max :: NS f xs -> NS f xs -> NS f xs #

min :: NS f xs -> NS f xs -> NS f xs #

All (Compose Show f) xs => Show (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

showsPrec :: Int -> NS f xs -> ShowS #

show :: NS f xs -> String #

showList :: [NS f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NS f xs)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.NS

Methods

rnf :: NS f xs -> () #

type Same (NS :: (k1 -> Type) -> [k1] -> Type) 
Instance details

Defined in Data.SOP.NS

type Same (NS :: (k1 -> Type) -> [k1] -> Type) = NS :: (k2 -> Type) -> [k2] -> Type
type Prod (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type Prod (NS :: (k -> Type) -> [k] -> Type) = NP :: (k -> Type) -> [k] -> Type
type SListIN (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type SListIN (NS :: (k -> Type) -> [k] -> Type) = SListI :: [k] -> Constraint
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NS

type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a = a
type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NS

type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c

data NP (a :: k -> Type) (b :: [k]) where #

An n-ary product.

The product is parameterized by a type constructor f and indexed by a type-level list xs. The length of the list determines the number of elements in the product, and if the i-th element of the list is of type x, then the i-th element of the product is of type f x.

The constructor names are chosen to resemble the names of the list constructors.

Two common instantiations of f are the identity functor I and the constant functor K. For I, the product becomes a heterogeneous list, where the type-level list describes the types of its components. For K a, the product becomes a homogeneous list, where the contents of the type-level list are ignored, but its length still specifies the number of elements.

In the context of the SOP approach to generic programming, an n-ary product describes the structure of the arguments of a single data constructor.

Examples:

I 'x'    :* I True  :* Nil  ::  NP I       '[ Char, Bool ]
K 0      :* K 1     :* Nil  ::  NP (K Int) '[ Char, Bool ]
Just 'x' :* Nothing :* Nil  ::  NP Maybe   '[ Char, Bool ]

Constructors

Nil :: forall k (a :: k -> Type). NP a ('[] :: [k]) 
(:*) :: forall k (a :: k -> Type) (x :: k) (xs :: [k]). a x -> NP a xs -> NP a (x ': xs) infixr 5 

Instances

Instances details
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). AllZipN (Prod NP) (LiftedCoercible f g) xs ys => NP f xs -> NP g ys #

HPure (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: forall c (xs :: l) proxy f. AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

HAp (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

HCollapse (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

HTraverse_ (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () #

HSequence (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

All (Compose Eq f) xs => Eq (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

(==) :: NP f xs -> NP f xs -> Bool #

(/=) :: NP f xs -> NP f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

compare :: NP f xs -> NP f xs -> Ordering #

(<) :: NP f xs -> NP f xs -> Bool #

(<=) :: NP f xs -> NP f xs -> Bool #

(>) :: NP f xs -> NP f xs -> Bool #

(>=) :: NP f xs -> NP f xs -> Bool #

max :: NP f xs -> NP f xs -> NP f xs #

min :: NP f xs -> NP f xs -> NP f xs #

All (Compose Show f) xs => Show (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

showsPrec :: Int -> NP f xs -> ShowS #

show :: NP f xs -> String #

showList :: [NP f xs] -> ShowS #

All (Compose Semigroup f) xs => Semigroup (NP f xs)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

(<>) :: NP f xs -> NP f xs -> NP f xs #

sconcat :: NonEmpty (NP f xs) -> NP f xs #

stimes :: Integral b => b -> NP f xs -> NP f xs #

(All (Compose Monoid f) xs, All (Compose Semigroup f) xs) => Monoid (NP f xs)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

mempty :: NP f xs #

mappend :: NP f xs -> NP f xs -> NP f xs #

mconcat :: [NP f xs] -> NP f xs #

All (Compose NFData f) xs => NFData (NP f xs)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.NP

Methods

rnf :: NP f xs -> () #

type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) = AllZip c
type Same (NP :: (k1 -> Type) -> [k1] -> Type) 
Instance details

Defined in Data.SOP.NP

type Same (NP :: (k1 -> Type) -> [k1] -> Type) = NP :: (k2 -> Type) -> [k2] -> Type
type Prod (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

type Prod (NP :: (k -> Type) -> [k] -> Type) = NP :: (k -> Type) -> [k] -> Type
type UnProd (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type UnProd (NP :: (k -> Type) -> [k] -> Type) = NS :: (k -> Type) -> [k] -> Type
type SListIN (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

type SListIN (NP :: (k -> Type) -> [k] -> Type) = SListI :: [k] -> Constraint
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NP

type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a = [a]
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c

data Proxy (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldMap' :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a #

(>$) :: b -> Proxy b -> Proxy a #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

ToJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Proxy a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding #

FromJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy a] #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

type Rep1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t) 
Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

Conversion from types to schemas

newtype WithSchema (sch :: Schema tn fn) (sty :: tn) a where Source #

Tags a value with its schema. For usage with deriving via.

Constructors

WithSchema :: forall tn fn (sch :: Schema tn fn) (sty :: tn) a. a -> WithSchema sch sty a 

Instances

Instances details
(ToSchema sch sty a, ToJSON (Term sch (sch :/: sty))) => ToJSON (WithSchema sch sty a) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: WithSchema sch sty a -> Value #

toEncoding :: WithSchema sch sty a -> Encoding #

toJSONList :: [WithSchema sch sty a] -> Value #

toEncodingList :: [WithSchema sch sty a] -> Encoding #

(FromSchema sch sty a, FromJSON (Term sch (sch :/: sty))) => FromJSON (WithSchema sch sty a) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (WithSchema sch sty a) #

parseJSONList :: Value -> Parser [WithSchema sch sty a] #

unWithSchema :: forall tn fn (sch :: Schema tn fn) (sty :: tn) a. WithSchema sch sty a -> a Source #

Accessor for WithSchema. Intended for usage with TypeApplications.

class FromSchema (sch :: Schema typeName fieldName) (sty :: typeName) (t :: Type) | sch t -> sty where Source #

Defines the conversion from a Term which follows the schema sch into a type t. You can give an optional mapping between the field names of t and that of sty by means of CustomFieldMapping.

Minimal complete definition

Nothing

Methods

fromSchema :: Term sch (sch :/: sty) -> t Source #

Conversion from schema term to Haskell type.

default fromSchema :: (Generic t, GFromSchemaTypeDef sch '[] (sch :/: sty) (Rep t)) => Term sch (sch :/: sty) -> t Source #

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

(sch :/: sty) ~ ('DEnum sty choices :: TypeDefB Type typeName fieldName) => FromSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DEnum sty choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

fromSchema :: Term sch (sch :/: sty) -> Term sch ('DEnum sty choices) Source #

(sch :/: sty) ~ 'DRecord sty fields => FromSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DRecord sty fields)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

fromSchema :: Term sch (sch :/: sty) -> Term sch ('DRecord sty fields) Source #

(sch :/: sty) ~ 'DRecord nm ('[] :: [FieldDefB Type k f]) => FromSchema (sch :: Schema k f) (sty :: k) (V0 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

fromSchema :: Term sch (sch :/: sty) -> V0 sch sty Source #

(sch :/: sty) ~ 'DRecord nm '['FieldDef f2 ('TPrimitive a :: FieldTypeB Type k)] => FromSchema (sch :: Schema k f1) (sty :: k) (V1 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

fromSchema :: Term sch (sch :/: sty) -> V1 sch sty Source #

(sch :/: sty) ~ 'DRecord nm '['FieldDef f2 ('TPrimitive a :: FieldTypeB Type k), 'FieldDef g ('TPrimitive b :: FieldTypeB Type k)] => FromSchema (sch :: Schema k f1) (sty :: k) (V2 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

fromSchema :: Term sch (sch :/: sty) -> V2 sch sty Source #

(Generic t, GFromSchemaTypeDef sch fmap (sch :/: sty) (Rep t)) => FromSchema (sch :: Schema typeName fieldName) (sty :: typeName) (CustomFieldMapping sty fmap t) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

fromSchema :: Term sch (sch :/: sty) -> CustomFieldMapping sty fmap t Source #

fromSchema' :: forall fn tn (sch :: Schema tn fn) t sty. FromSchema sch sty t => Term sch (sch :/: sty) -> t Source #

Conversion from schema term to Haskell type. This version is intended for usage with TypeApplications: > fromSchema' @MySchema mySchemaTerm

class ToSchema (sch :: Schema typeName fieldName) (sty :: typeName) (t :: Type) | sch t -> sty where Source #

Defines the conversion of a type t into a Term which follows the schema sch. You can give an optional mapping between the field names of t and that of sty by means of CustomFieldMapping.

Minimal complete definition

Nothing

Methods

toSchema :: t -> Term sch (sch :/: sty) Source #

Conversion from Haskell type to schema term.

default toSchema :: (Generic t, GToSchemaTypeDef sch '[] (sch :/: sty) (Rep t)) => t -> Term sch (sch :/: sty) Source #

Instances

Instances details
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

(sch :/: sty) ~ ('DEnum sty choices :: TypeDefB Type typeName fieldName) => ToSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DEnum sty choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchema :: Term sch ('DEnum sty choices) -> Term sch (sch :/: sty) Source #

(sch :/: sty) ~ 'DRecord sty fields => ToSchema (sch :: Schema typeName fieldName) (sty :: typeName) (Term sch ('DRecord sty fields)) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchema :: Term sch ('DRecord sty fields) -> Term sch (sch :/: sty) Source #

(sch :/: sty) ~ 'DRecord nm ('[] :: [FieldDefB Type k f]) => ToSchema (sch :: Schema k f) (sty :: k) (V0 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

toSchema :: V0 sch sty -> Term sch (sch :/: sty) Source #

(sch :/: sty) ~ 'DRecord nm '['FieldDef f2 ('TPrimitive a :: FieldTypeB Type k)] => ToSchema (sch :: Schema k f1) (sty :: k) (V1 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

toSchema :: V1 sch sty -> Term sch (sch :/: sty) Source #

(sch :/: sty) ~ 'DRecord nm '['FieldDef f2 ('TPrimitive a :: FieldTypeB Type k), 'FieldDef g ('TPrimitive b :: FieldTypeB Type k)] => ToSchema (sch :: Schema k f1) (sty :: k) (V2 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

toSchema :: V2 sch sty -> Term sch (sch :/: sty) Source #

(Generic t, GToSchemaTypeDef sch fmap (sch :/: sty) (Rep t)) => ToSchema (sch :: Schema typeName fieldName) (sty :: typeName) (CustomFieldMapping sty fmap t) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchema :: CustomFieldMapping sty fmap t -> Term sch (sch :/: sty) Source #

toSchema' :: forall fn tn (sch :: Schema tn fn) t sty. ToSchema sch sty t => t -> Term sch (sch :/: sty) Source #

Conversion from Haskell type to schema term. This version is intended for usage with TypeApplications: > toSchema' @MySchema myValue

newtype CustomFieldMapping (sty :: typeName) (fmap :: [Mapping Symbol fieldName]) a Source #

By default, the names of the fields in the Haskell type and those of the schema types must coincide. By using this wrapper you can override this default setting.

This type should be used with DerivingVia, as follows:

type MyCustomFieldMapping = '[ "A" ':-> "a", ...]
data MyHaskellType = ...
  deriving ( ToSchema   f MySchema "MySchemaType" MyHaskellType
           , FromSchema f MySchema "MySchemaType" MyHaskellType)
    via (CustomFieldMapping "MySchemaType" MyCustomFieldMapping MyHaskellType)

Constructors

CustomFieldMapping a 

Instances

Instances details
(Generic t, GFromSchemaTypeDef sch fmap (sch :/: sty) (Rep t)) => FromSchema (sch :: Schema typeName fieldName) (sty :: typeName) (CustomFieldMapping sty fmap t) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

fromSchema :: Term sch (sch :/: sty) -> CustomFieldMapping sty fmap t Source #

(Generic t, GToSchemaTypeDef sch fmap (sch :/: sty) (Rep t)) => ToSchema (sch :: Schema typeName fieldName) (sty :: typeName) (CustomFieldMapping sty fmap t) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

toSchema :: CustomFieldMapping sty fmap t -> Term sch (sch :/: sty) Source #

newtype Underlying basic logical Source #

This 'newtype' is used to wrap types for which we want a "logical" representation as a Haskell type, but the underlying representation is lower level, like UUIDs as ByteStrings.

Constructors

Underlying 

Fields

Instances

Instances details
Eq logical => Eq (Underlying basic logical) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

(==) :: Underlying basic logical -> Underlying basic logical -> Bool #

(/=) :: Underlying basic logical -> Underlying basic logical -> Bool #

Show logical => Show (Underlying basic logical) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

showsPrec :: Int -> Underlying basic logical -> ShowS #

show :: Underlying basic logical -> String #

showList :: [Underlying basic logical] -> ShowS #

class UnderlyingConversion basic logical where Source #

This class defines the actual conversion between a "logical" type and its low-level representation.

Methods

toUnderlying :: logical -> basic Source #

fromUnderlying :: basic -> logical Source #

Mappings between fields

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.

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 

Field annotations

type family AnnotatedSchema domain (sch :: Schema typeName fieldName) :: [Annotation domain typeName fieldName] Source #

This type family links each schema to its corresponding annotations from one domain.

type AnnotationDomain = Type Source #

Each annotation belongs to a domain.

data Annotation domain typeName fieldName where Source #

Annotations proper.

Constructors

AnnSchema :: domain -> Annotation domain typeName fieldName

Annotation over the whole schema.

AnnType :: typeName -> domain -> Annotation domain typeName fieldName

Annotation over a type in the schema.

AnnField :: typeName -> fieldName -> domain -> Annotation domain typeName fieldName

Annotation over a field in a record or a choice in an enumeration.