Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type Registry = Mappings Nat Schema'
- fromRegistry :: forall r t w. FromRegistry w r t => Term w -> Maybe t
- 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
Registry of schemas
fromRegistry :: forall r t w. FromRegistry w r t => Term w -> Maybe t Source #
Terms without an associated schema
data Term (w :: * -> *) where Source #
Interpretation of a type in a schema.
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.
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.
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 (==) :: FieldValue w -> FieldValue w -> Bool # (/=) :: FieldValue w -> FieldValue w -> Bool # | |
Ord (w (FieldValue w)) => Ord (FieldValue w) Source # | |
Defined in Mu.Schema.Interpretation.Schemaless 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 showsPrec :: Int -> FieldValue w -> ShowS # show :: FieldValue w -> String # showList :: [FieldValue w] -> ShowS # |