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

Safe HaskellNone
LanguageHaskell2010

Mu.Schema.Registry

Contents

Description

A registry of schemas saves the different schemas supported by an application. Since messages and protocols may evolve, it's useful to keep an updated view of the different shapes of data we can handle.

Examples of registries are found in Kafka and Compendium.

Synopsis

Registry of schemas

type Registry = Mappings Nat Schema' Source #

A Registry is defined as a map from version numbers to type-level schemas.

Implementation note: you must write newer schemas at the head of the Registry. Otherwise, older schemas take precedence during conversion.

fromRegistry :: forall r t w. FromRegistry w r t => Term w -> Maybe t Source #

Converts a schemaless term into a value by checking all the possible schemas in a Registry.

Implementation note: schemas are checked in the same order in which they appear in the Registry definition.

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