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

Mu.Schema.Class

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   MySchema "MySchemaType" MyHaskellType
           , FromSchema 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 (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 #

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 

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 #

Internal use only

class GToSchemaRecord (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 sch) args Source #

Instances

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