Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 where
- data Field where
- Field :: Text -> FieldValue -> Field
- data FieldValue where
- FNull :: FieldValue
- FPrimitive :: (Typeable t, Eq t, Ord t, Show t) => t -> FieldValue
- FSchematic :: Term -> FieldValue
- FOption :: Maybe FieldValue -> FieldValue
- FList :: [FieldValue] -> FieldValue
- FMap :: Map FieldValue FieldValue -> FieldValue
- checkSchema :: forall tn fn (s :: Schema tn fn) (t :: tn). CheckSchema s (s :/: t) => Proxy t -> Term -> Maybe (Term s (s :/: t))
- fromSchemalessTerm :: forall sch t sty. (FromSchema sch sty t, CheckSchema sch (sch :/: sty)) => Term -> Maybe t
- class ToSchemalessTerm t where
- toSchemalessTerm :: t -> Term
- class ToSchemalessValue t where
- toSchemalessValue :: t -> FieldValue
- class CheckSchema (s :: Schema tn fn) (t :: TypeDef tn fn)
Terms without an associated schema
Interpretation of a type in a schema.
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. |
Interpretation of a field.
Field :: Text -> FieldValue -> Field | A single field given by its name and its value. |
data FieldValue where Source #
Interpretation of a field type, by giving a value of that type.
FNull :: FieldValue | |
FPrimitive :: (Typeable t, Eq t, Ord t, Show t) => t -> FieldValue | |
FSchematic :: Term -> FieldValue | |
FOption :: Maybe FieldValue -> FieldValue | |
FList :: [FieldValue] -> FieldValue | |
FMap :: Map FieldValue FieldValue -> FieldValue |
Instances
Eq FieldValue Source # | |
Defined in Mu.Schema.Interpretation.Schemaless (==) :: FieldValue -> FieldValue -> Bool # (/=) :: FieldValue -> FieldValue -> Bool # | |
Ord FieldValue Source # | |
Defined in Mu.Schema.Interpretation.Schemaless compare :: FieldValue -> FieldValue -> Ordering # (<) :: FieldValue -> FieldValue -> Bool # (<=) :: FieldValue -> FieldValue -> Bool # (>) :: FieldValue -> FieldValue -> Bool # (>=) :: FieldValue -> FieldValue -> Bool # max :: FieldValue -> FieldValue -> FieldValue # min :: FieldValue -> FieldValue -> FieldValue # | |
Show FieldValue Source # | |
Defined in Mu.Schema.Interpretation.Schemaless showsPrec :: Int -> FieldValue -> ShowS # show :: FieldValue -> String # showList :: [FieldValue] -> ShowS # |
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 #
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.
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
ToSchemalessTerm Value Source # | |
Defined in Mu.Adapter.Json toSchemalessTerm :: Value -> Term Source # |
class ToSchemalessValue t where Source #
Deserialization to schemaless values.
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
ToSchemalessValue Value Source # | |
Defined in Mu.Adapter.Json toSchemalessValue :: Value -> FieldValue 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
.
checkSchema'
Instances
CheckSchemaValue s f => CheckSchema (s :: Schema typeName fn) ('DSimple f :: TypeDefB Type typeName fn) Source # | |
Defined in Mu.Schema.Interpretation.Schemaless checkSchema' :: Term -> Maybe (Term 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 checkSchema' :: Term -> Maybe (Term 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 checkSchema' :: Term -> Maybe (Term s ('DEnum nm choices)) |