| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Schematic.DSL
Documentation
type Constructor a = forall b. FSubset (FieldsOf a) b (FImage (FieldsOf a) b) => Rec (Tagged (FieldsOf a) :. FieldRepr) b -> JsonRepr (SchemaObject (FieldsOf a)) Source #
withRepr :: Constructor a Source #
class Representable s where Source #
Minimal complete definition
Instances
| Representable SchemaBoolean Source # | |
| SingI [TextConstraint] cs => Representable (SchemaText cs) Source # | |
| SingI [NumberConstraint] cs => Representable (SchemaNumber cs) Source # | |
| SingI [(Symbol, Schema)] so => Representable (SchemaObject so) Source # | |
| SingI Schema so => Representable (SchemaOptional so) Source # | |
| SingI [Schema] ((:) Schema h tl) => Representable (SchemaUnion ((:) Schema h tl)) Source # | |
| (SingI [ArrayConstraint] cs, SingI Schema sa) => Representable (SchemaArray cs sa) Source # | |
type family FieldsOf (s :: Schema) :: [(Symbol, Schema)] where ... Source #
Equations
| FieldsOf (SchemaObject fs) = fs |
type FieldConstructor fn = forall fs. Representable (ByField fn fs (FIndex fn fs)) => Repr (ByField fn fs (FIndex fn fs)) -> (Tagged fs :. FieldRepr) '(fn, ByField fn fs (FIndex fn fs)) Source #
field :: forall fn. KnownSymbol fn => FieldConstructor fn Source #
type family Repr (s :: Schema) = (ty :: Type) where ... Source #
Equations
| Repr (SchemaObject so) = Rec FieldRepr so | |
| Repr (SchemaArray cs sa) = Vector (JsonRepr sa) | |
| Repr (SchemaText cs) = Text | |
| Repr (SchemaNumber cs) = Scientific | |
| Repr SchemaBoolean = Bool | |
| Repr (SchemaOptional so) = Maybe (JsonRepr so) | |
| Repr (SchemaUnion (h ': tl)) = Union JsonRepr (h ': tl) |