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

Safe HaskellNone
LanguageHaskell2010

Mu.Schema.Interpretation.Schemaless

Contents

Description

In the edges of your application it's useful to consider terms for which a type-level schema has not yet been applied. Think of receiving a JSON document: you can parse it but checking the schema is an additional step.

Synopsis

Terms without an associated schema

data Term (w :: * -> *) where Source #

Interpretation of a type in a schema.

Constructors

TRecord :: [Field w] -> Term w

A record given by the value of its fields.

TEnum :: Int -> Term w

An enumeration given by one choice.

TSimple :: FieldValue w -> Term w

A primitive value.

Instances
Eq (w (FieldValue w)) => Eq (Term w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

(==) :: Term w -> Term w -> Bool #

(/=) :: Term w -> Term w -> Bool #

Ord (w (FieldValue w)) => Ord (Term w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

compare :: Term w -> Term w -> Ordering #

(<) :: Term w -> Term w -> Bool #

(<=) :: Term w -> Term w -> Bool #

(>) :: Term w -> Term w -> Bool #

(>=) :: Term w -> Term w -> Bool #

max :: Term w -> Term w -> Term w #

min :: Term w -> Term w -> Term w #

Show (w (FieldValue w)) => Show (Term w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

showsPrec :: Int -> Term w -> ShowS #

show :: Term w -> String #

showList :: [Term w] -> ShowS #

data Field (w :: * -> *) where Source #

Interpretation of a field.

Constructors

Field :: Text -> w (FieldValue w) -> Field w

A single field given by its name and its value. Note that the contents are wrapped in a w type constructor.

Instances
Eq (w (FieldValue w)) => Eq (Field w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

(==) :: Field w -> Field w -> Bool #

(/=) :: Field w -> Field w -> Bool #

Ord (w (FieldValue w)) => Ord (Field w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

compare :: Field w -> Field w -> Ordering #

(<) :: Field w -> Field w -> Bool #

(<=) :: Field w -> Field w -> Bool #

(>) :: Field w -> Field w -> Bool #

(>=) :: Field w -> Field w -> Bool #

max :: Field w -> Field w -> Field w #

min :: Field w -> Field w -> Field w #

Show (w (FieldValue w)) => Show (Field w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

showsPrec :: Int -> Field w -> ShowS #

show :: Field w -> String #

showList :: [Field w] -> ShowS #

data FieldValue (w :: * -> *) where Source #

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

Constructors

FNull :: FieldValue w 
FPrimitive :: (Typeable t, Eq t, Ord t, Show t) => t -> FieldValue w 
FSchematic :: Term w -> FieldValue w 
FOption :: Maybe (FieldValue w) -> FieldValue w 
FList :: [FieldValue w] -> FieldValue w 
FMap :: Map (FieldValue w) (FieldValue w) -> FieldValue w 
Instances
Eq (w (FieldValue w)) => Eq (FieldValue w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

(==) :: FieldValue w -> FieldValue w -> Bool #

(/=) :: FieldValue w -> FieldValue w -> Bool #

Ord (w (FieldValue w)) => Ord (FieldValue w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Show (w (FieldValue w)) => Show (FieldValue w) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Checking and conversion against a schema

checkSchema :: forall (s :: Schema tn fn) (t :: tn) (w :: * -> *). (Traversable w, CheckSchema s (s :/: t)) => Proxy t -> Term w -> Maybe (Term w s (s :/: t)) Source #

Checks that a schemaless Term obbeys the restrictions for tyoe t of schema s. If successful, returns a Term indexed by the corresponding schema and type.

Use this function to check a schemaless terms at the "borders" of your application.

fromSchemalessTerm :: forall sch w t sty. (Traversable w, FromSchema w sch sty t, CheckSchema sch (sch :/: sty)) => Term w -> Maybe t Source #

Converts a schemaless term to a Haskell type by going through the corresponding schema type.

For deserialization to schemaless terms

class ToSchemalessTerm t w where Source #

Deserialization to schemaless terms.

Methods

toSchemalessTerm :: t -> Term w Source #

Turns a document (such as JSON) into a schemaless term. This function should handle the "compound" types in that format, such as records and enumerations.

Instances
Applicative w => ToSchemalessTerm Value w Source # 
Instance details

Defined in Mu.Adapter.Json

class ToSchemalessValue t w where Source #

Deserialization to schemaless values.

Methods

toSchemalessValue :: t -> FieldValue w Source #

Turns a document (such as JSON) into a schemaless term. This function should handle the "primitive" types in that format.

Instances
Applicative w => ToSchemalessValue Value w Source # 
Instance details

Defined in Mu.Adapter.Json

For implementors

class CheckSchema (s :: Schema tn fn) (t :: TypeDef tn fn) Source #

Type class used to define the generic checkSchema.

Exposed for usage in other modules, in particular Registry.

Minimal complete definition

checkSchema'

Instances
CheckSchemaValue s f => CheckSchema (s :: Schema typeName fn) (DSimple f :: TypeDefB Type typeName fn) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

checkSchema' :: Traversable w => Term w -> Maybe (Term w s (DSimple f))

CheckSchemaFields s fields => CheckSchema (s :: Schema typeName fieldName) (DRecord nm fields :: TypeDefB Type typeName fieldName) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

checkSchema' :: Traversable w => Term w -> Maybe (Term w s (DRecord nm fields))

CheckSchemaEnum choices => CheckSchema (s :: Schema tn fn) (DEnum nm choices :: TypeDefB Type tn fn) Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

checkSchema' :: Traversable w => Term w -> Maybe (Term w s (DEnum nm choices))