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

Mu.Schema.Interpretation.Anonymous

Description

This module provides "anonymous terms". These terms can be used when you don't want to write your own Haskell type, but simply have a quick and dirty interpretation for a schema type. An important limitation is that anonymous terms may only contain primitive fields.

The names of the types exposed in this module refer to the amount of fields in the record. Hence, use V0 for empty record, V1 for a record with one field, V2 for two, and so forth.

Synopsis

Documentation

data V0 sch sty where Source #

Anonymous term for a record with zero fields.

Constructors

V0 :: (sch :/: sty) ~ 'DRecord nm '[] => V0 sch sty 

Instances

Instances details
(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 ('[] :: [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 #

Eq (V0 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

(==) :: V0 sch sty -> V0 sch sty -> Bool #

(/=) :: V0 sch sty -> V0 sch sty -> Bool #

Ord (V0 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

compare :: V0 sch sty -> V0 sch sty -> Ordering #

(<) :: V0 sch sty -> V0 sch sty -> Bool #

(<=) :: V0 sch sty -> V0 sch sty -> Bool #

(>) :: V0 sch sty -> V0 sch sty -> Bool #

(>=) :: V0 sch sty -> V0 sch sty -> Bool #

max :: V0 sch sty -> V0 sch sty -> V0 sch sty #

min :: V0 sch sty -> V0 sch sty -> V0 sch sty #

Show (V0 sch sty) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Anonymous

Methods

showsPrec :: Int -> V0 sch sty -> ShowS #

show :: V0 sch sty -> String #

showList :: [V0 sch sty] -> ShowS #

data V1 sch sty where Source #

Anonymous term for a record with one field.

Constructors

V1 :: (sch :/: sty) ~ 'DRecord nm '['FieldDef f ('TPrimitive a)] => a -> V1 sch sty 

Instances

Instances details
(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)] => 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 #

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

(==) :: V1 sch sty -> V1 sch sty -> Bool #

(/=) :: V1 sch sty -> V1 sch sty -> Bool #

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

compare :: V1 sch sty -> V1 sch sty -> Ordering #

(<) :: V1 sch sty -> V1 sch sty -> Bool #

(<=) :: V1 sch sty -> V1 sch sty -> Bool #

(>) :: V1 sch sty -> V1 sch sty -> Bool #

(>=) :: V1 sch sty -> V1 sch sty -> Bool #

max :: V1 sch sty -> V1 sch sty -> V1 sch sty #

min :: V1 sch sty -> V1 sch sty -> V1 sch sty #

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

showsPrec :: Int -> V1 sch sty -> ShowS #

show :: V1 sch sty -> String #

showList :: [V1 sch sty] -> ShowS #

data V2 sch sty where Source #

Anonymous term for a record with two fields.

Constructors

V2 :: (sch :/: sty) ~ 'DRecord nm '['FieldDef f ('TPrimitive a), 'FieldDef g ('TPrimitive b)] => a -> b -> V2 sch sty 

Instances

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

(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 #

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

(==) :: V2 sch sty -> V2 sch sty -> Bool #

(/=) :: V2 sch sty -> V2 sch sty -> Bool #

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

compare :: V2 sch sty -> V2 sch sty -> Ordering #

(<) :: V2 sch sty -> V2 sch sty -> Bool #

(<=) :: V2 sch sty -> V2 sch sty -> Bool #

(>) :: V2 sch sty -> V2 sch sty -> Bool #

(>=) :: V2 sch sty -> V2 sch sty -> Bool #

max :: V2 sch sty -> V2 sch sty -> V2 sch sty #

min :: V2 sch sty -> V2 sch sty -> V2 sch sty #

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

Defined in Mu.Schema.Interpretation.Anonymous

Methods

showsPrec :: Int -> V2 sch sty -> ShowS #

show :: V2 sch sty -> String #

showList :: [V2 sch sty] -> ShowS #