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

Mu.Schema.Interpretation.Schemaless

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 where Source #

Interpretation of a type in a schema.

Constructors

TRecord :: [Field] -> Term

A record given by the value of its fields.

TEnum :: Int -> Term

An enumeration given by one choice.

TSimple :: FieldValue -> Term

A primitive value.

Instances

Instances details
Eq Term Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

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

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

Ord Term Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

compare :: Term -> Term -> Ordering #

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

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

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

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

max :: Term -> Term -> Term #

min :: Term -> Term -> Term #

Show Term Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

data Field where Source #

Interpretation of a field.

Constructors

Field :: Text -> FieldValue -> Field

A single field given by its name and its value.

Instances

Instances details
Eq Field Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

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

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

Ord Field Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

compare :: Field -> Field -> Ordering #

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

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

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

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

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

Show Field Source # 
Instance details

Defined in Mu.Schema.Interpretation.Schemaless

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

data FieldValue where Source #

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

Checking and conversion against a schema

checkSchema :: forall tn fn (s :: Schema tn fn) (t :: tn). CheckSchema s (s :/: t) => Proxy t -> Term -> Maybe (Term 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 t sty. (FromSchema sch sty t, CheckSchema sch (sch :/: sty)) => Term -> 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 where Source #

Deserialization to schemaless terms.

Methods

toSchemalessTerm :: t -> Term 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

Instances details
ToSchemalessTerm Value Source # 
Instance details

Defined in Mu.Adapter.Json

class ToSchemalessValue t where Source #

Deserialization to schemaless values.

Methods

toSchemalessValue :: t -> FieldValue Source #

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

Instances

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

Instances details
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' :: Term -> Maybe (Term 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' :: Term -> Maybe (Term 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' :: Term -> Maybe (Term s ('DEnum nm choices))