| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- data Term (w :: * -> *) where
- data Field (w :: * -> *) where- Field :: Text -> w (FieldValue w) -> Field w
 
- data FieldValue (w :: * -> *) where- 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
 
- 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))
- fromSchemalessTerm :: forall sch w t sty. (Traversable w, FromSchema w sch sty t, CheckSchema sch (sch :/: sty)) => Term w -> Maybe t
- class ToSchemalessTerm t w where- toSchemalessTerm :: t -> Term w
 
- class ToSchemalessValue t w where- toSchemalessValue :: t -> FieldValue w
 
- class CheckSchema (s :: Schema tn fn) (t :: TypeDef tn fn)
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. | 
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  | 
Instances
| Eq (w (FieldValue w)) => Eq (Field w) Source # | |
| Ord (w (FieldValue w)) => Ord (Field w) Source # | |
| Defined in Mu.Schema.Interpretation.Schemaless | |
| Show (w (FieldValue w)) => Show (Field w) Source # | |
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 # | |
| Defined in Mu.Schema.Interpretation.Schemaless | |
| Ord (w (FieldValue w)) => Ord (FieldValue w) Source # | |
| Defined in Mu.Schema.Interpretation.Schemaless Methods compare :: FieldValue w -> FieldValue w -> Ordering # (<) :: FieldValue w -> FieldValue w -> Bool # (<=) :: FieldValue w -> FieldValue w -> Bool # (>) :: FieldValue w -> FieldValue w -> Bool # (>=) :: FieldValue w -> FieldValue w -> Bool # max :: FieldValue w -> FieldValue w -> FieldValue w # min :: FieldValue w -> FieldValue w -> FieldValue w # | |
| Show (w (FieldValue w)) => Show (FieldValue w) Source # | |
| Defined in Mu.Schema.Interpretation.Schemaless Methods showsPrec :: Int -> FieldValue w -> ShowS # show :: FieldValue w -> String # showList :: [FieldValue w] -> ShowS # | |
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 #
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 # | |
| Defined in Mu.Adapter.Json Methods toSchemalessTerm :: Value -> Term w Source # | |
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 # | |
| Defined in Mu.Adapter.Json Methods toSchemalessValue :: Value -> FieldValue w Source # | |
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 # | |
| 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 # | |
| 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 # | |
| Defined in Mu.Schema.Interpretation.Schemaless Methods checkSchema' :: Traversable w => Term w -> Maybe (Term w s (DEnum nm choices)) | |