| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Schematic.Schema
Documentation
type family All (c :: k -> Constraint) (s :: [k]) :: Constraint where ... Source #
type family CRepr (s :: Schema) :: Type where ... Source #
Equations
| CRepr (SchemaText cs) = TextConstraint | |
| CRepr (SchemaNumber cs) = NumberConstraint | |
| CRepr (SchemaObject fs) = (String, Schema) | |
| CRepr (SchemaArray ar s) = ArrayConstraint |
data TextConstraint Source #
Instances
| Generic TextConstraint Source # | |
| KnownNat n => SingI TextConstraint (TEq n) Source # | |
| KnownNat n => SingI TextConstraint (TLe n) Source # | |
| KnownNat n => SingI TextConstraint (TGt n) Source # | |
| (KnownSymbol s, SingI Symbol s) => SingI TextConstraint (TRegex s) Source # | |
| (All Symbol KnownSymbol ss, SingI [Symbol] ss) => SingI TextConstraint (TEnum ss) Source # | |
| Eq (Sing TextConstraint (TEq n)) Source # | |
| Eq (Sing TextConstraint (TLe n)) Source # | |
| Eq (Sing TextConstraint (TGt n)) Source # | |
| Eq (Sing TextConstraint (TRegex t)) Source # | |
| Eq (Sing TextConstraint (TEnum ss)) Source # | |
| type Rep TextConstraint Source # | |
| data Sing TextConstraint Source # | |
data NumberConstraint Source #
Instances
| Generic NumberConstraint Source # | |
| KnownNat n => SingI NumberConstraint (NLe n) Source # | |
| KnownNat n => SingI NumberConstraint (NGt n) Source # | |
| KnownNat n => SingI NumberConstraint (NEq n) Source # | |
| Eq (Sing NumberConstraint (NLe n)) Source # | |
| Eq (Sing NumberConstraint (NGt n)) Source # | |
| Eq (Sing NumberConstraint (NEq n)) Source # | |
| type Rep NumberConstraint Source # | |
| data Sing NumberConstraint Source # | |
data ArrayConstraint Source #
Instances
| Generic ArrayConstraint Source # | |
| KnownNat n => SingI ArrayConstraint (AEq n) Source # | |
| Eq (Sing ArrayConstraint (AEq n)) Source # | |
| type Rep ArrayConstraint Source # | |
| data Sing ArrayConstraint Source # | |
Constructors
| SchemaText [TextConstraint] | |
| SchemaNumber [NumberConstraint] | |
| SchemaObject [(Symbol, Schema)] | |
| SchemaArray [ArrayConstraint] Schema | |
| SchemaNull | |
| SchemaOptional Schema |
Instances
data FieldRepr :: (Symbol, Schema) -> Type where Source #
Constructors
| FieldRepr :: (SingI schema, KnownSymbol name) => JsonRepr schema -> FieldRepr '(name, schema) |
Instances
knownFieldName :: forall proxy fieldName schema. KnownSymbol fieldName => proxy '(fieldName, schema) -> Text Source #
knownFieldSchema :: forall proxy fieldName schema. SingI schema => proxy '(fieldName, schema) -> Sing schema Source #
data JsonRepr :: Schema -> Type where Source #
Constructors
| ReprText :: Text -> JsonRepr (SchemaText cs) | |
| ReprNumber :: Scientific -> JsonRepr (SchemaNumber cs) | |
| ReprNull :: JsonRepr SchemaNull | |
| ReprArray :: Vector (JsonRepr s) -> JsonRepr (SchemaArray cs s) | |
| ReprObject :: Rec FieldRepr fs -> JsonRepr (SchemaObject fs) | |
| ReprOptional :: Maybe (JsonRepr s) -> JsonRepr (SchemaOptional s) |
Instances
fromOptional :: SingI s => Sing (SchemaOptional s) -> Value -> Parser (Maybe (JsonRepr s)) Source #
class FalseConstraint a Source #
type family TopLevel (schema :: Schema) :: Constraint where ... Source #
Equations
| TopLevel (SchemaArray acs s) = () | |
| TopLevel (SchemaObject o) = () | |
| TopLevel spec = True ~ False |