mu-schema-0.1.0.0: Format-independent schemas for serialization

Safe HaskellNone
LanguageHaskell2010

Mu.Schema.Class

Contents

Description

This module defines a couple of type classes ToSchema and FromSchema to turn Haskell types back and forth mu-haskell Terms.

In most cases, the instances can be automatically derived. If you enable the extensions DeriveGeneric and DeriveAnyClass, you can do:

data MyHaskellType = ...
  deriving ( ToSchema   f MySchema "MySchemaType" MyHaskellType
           , FromSchema f MySchema "MySchemaType" MyHaskellType)

If the default mapping which required identical names for fields in the Haskell and schema types does not suit you, use CustomFieldMapping.

Synopsis

Documentation

newtype WithSchema (w :: Type -> Type) (sch :: Schema tn fn) (sty :: tn) a Source #

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

Constructors

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

Defined in Mu.Adapter.Json

Methods

toJSON :: WithSchema w sch sty a -> Value #

toEncoding :: WithSchema w sch sty a -> Encoding #

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

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

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

Defined in Mu.Adapter.Json

Methods

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

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

class FromSchema (w :: Type -> Type) (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 w sch (sch :/: sty) -> t Source #

Conversion from schema term to Haskell type.

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

Conversion from schema term to Haskell type.

Instances
FromSchema f ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema Identity ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

FromSchema Identity ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

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

Defined in Mu.Schema.Class

Methods

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

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

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

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

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

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

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

fromSchema' :: forall fn tn (sch :: Schema tn fn) w t sty. FromSchema w sch sty t => Term w 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 (w :: Type -> Type) (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 w sch (sch :/: sty) Source #

Conversion from Haskell type to schema term.

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

Conversion from Haskell type to schema term.

Instances
ToSchema f ExampleSchema "gender" Gender Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema Identity ExampleSchema "address" Address Source # 
Instance details

Defined in Mu.Schema.Examples

ToSchema Identity ExampleSchema "person" Person Source # 
Instance details

Defined in Mu.Schema.Examples

(Generic t, GToSchemaTypeDef w sch fmap (sch :/: sty) (Rep t)) => ToSchema w (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 w sch (sch :/: sty) Source #

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

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

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

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

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

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

toSchema' :: forall fn tn (sch :: Schema tn fn) w t sty. ToSchema w sch sty t => t -> Term w 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
(Generic t, GFromSchemaTypeDef w sch fmap (sch :/: sty) (Rep t)) => FromSchema w (sch :: Schema typeName fieldName) (sty :: typeName) (CustomFieldMapping sty fmap t) Source # 
Instance details

Defined in Mu.Schema.Class

Methods

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

(Generic t, GToSchemaTypeDef w sch fmap (sch :/: sty) (Rep t)) => ToSchema w (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 w sch (sch :/: sty) Source #

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.

Equations

MappingRight '[] (v :: Symbol) = v 
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.

Equations

MappingLeft '[] (v :: Symbol) = v 
MappingLeft '[] v = TypeError (Text "Cannot find value " :<>: ShowType v) 
MappingLeft ((x :-> y) ': rest) y = x 
MappingLeft (other ': rest) y = MappingLeft rest y 

transSchema :: forall fn tn (sch :: Schema tn fn) sty u v a b. (ToSchema u sch sty a, FromSchema v sch sty b, Functor u, forall k. Ord (FieldValue u sch k) => Ord (FieldValue v sch k)) => (forall x. u x -> v x) -> Proxy sch -> a -> b Source #

Changes the underlying wrapper of a Haskell type, by converting back and forth Terms with those wrappers.

Internal use only

class GToSchemaRecord (w :: * -> *) (sch :: Schema ts fs) (fmap :: Mappings Symbol fs) (args :: [FieldDef ts fs]) (f :: * -> *) where Source #

For internal use only: generic conversion of a list of fields.

Methods

toSchemaRecord :: Proxy fmap -> f a -> NP (Field w sch) args Source #

Instances
GToSchemaRecord w (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 w sch) [] Source #

(GToSchemaRecord w sch fmap cs f, GToSchemaRecordSearch w sch t f (FindSel f (MappingLeft fmap name))) => GToSchemaRecord w (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 w sch) (FieldDef name t ': cs) Source #