Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type family CRepr (s :: Schema) :: Type where ...
- data TextConstraint
- data DemotedTextConstraint
- data NumberConstraint
- data DemotedNumberConstraint
- data ArrayConstraint = AEq Nat
- data DemotedArrayConstraint = DAEq Integer
- data Schema
- data DemotedSchema
- data FieldRepr :: (Symbol, Schema) -> Type where
- FieldRepr :: (SingI schema, KnownSymbol name) => JsonRepr schema -> FieldRepr '(name, schema)
- toJsonRepr :: FieldRepr '(fn, sch) -> JsonRepr sch
- knownFieldName :: forall proxy fieldName schema. KnownSymbol fieldName => proxy '(fieldName, schema) -> Text
- knownFieldSchema :: forall proxy fieldName schema. SingI schema => proxy '(fieldName, schema) -> Sing schema
- data JsonRepr :: Schema -> Type where
- ReprText :: Text -> JsonRepr (SchemaText cs)
- ReprNumber :: Scientific -> JsonRepr (SchemaNumber cs)
- ReprBoolean :: Bool -> JsonRepr SchemaBoolean
- 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)
- fromOptional :: SingI s => Sing (SchemaOptional s) -> Value -> Parser (Maybe (JsonRepr s))
- class FalseConstraint a
- type family TopLevel (schema :: Schema) :: Constraint where ...
Documentation
type family CRepr (s :: Schema) :: Type where ... Source #
CRepr (SchemaText cs) = TextConstraint | |
CRepr (SchemaNumber cs) = NumberConstraint | |
CRepr (SchemaObject fs) = (String, Schema) | |
CRepr (SchemaArray ar s) = ArrayConstraint |
data TextConstraint Source #
Generic TextConstraint Source # | |
SingKind TextConstraint Source # | |
KnownNat n => SingI TextConstraint (TEq n) Source # | |
KnownNat n => SingI TextConstraint (TLt n) Source # | |
KnownNat n => SingI TextConstraint (TLe n) Source # | |
KnownNat n => SingI TextConstraint (TGt n) Source # | |
KnownNat n => SingI TextConstraint (TGe n) Source # | |
(KnownSymbol s, SingI Symbol s) => SingI TextConstraint (TRegex s) Source # | |
SingI [Symbol] ss => SingI TextConstraint (TEnum ss) Source # | |
Eq (Sing TextConstraint (TEq n)) Source # | |
Eq (Sing TextConstraint (TLt n)) Source # | |
Eq (Sing TextConstraint (TLe n)) Source # | |
Eq (Sing TextConstraint (TGt n)) Source # | |
Eq (Sing TextConstraint (TGe n)) Source # | |
Eq (Sing TextConstraint (TRegex t)) Source # | |
Eq (Sing TextConstraint (TEnum ss)) Source # | |
type Rep TextConstraint Source # | |
data Sing TextConstraint Source # | |
type DemoteRep TextConstraint Source # | |
data DemotedTextConstraint Source #
data NumberConstraint Source #
Generic NumberConstraint Source # | |
SingKind NumberConstraint Source # | |
KnownNat n => SingI NumberConstraint (NLe n) Source # | |
KnownNat n => SingI NumberConstraint (NLt n) Source # | |
KnownNat n => SingI NumberConstraint (NGt n) Source # | |
KnownNat n => SingI NumberConstraint (NGe n) Source # | |
KnownNat n => SingI NumberConstraint (NEq n) Source # | |
Eq (Sing NumberConstraint (NLe n)) Source # | |
Eq (Sing NumberConstraint (NLt n)) Source # | |
Eq (Sing NumberConstraint (NGt n)) Source # | |
Eq (Sing NumberConstraint (NGe n)) Source # | |
Eq (Sing NumberConstraint (NEq n)) Source # | |
type Rep NumberConstraint Source # | |
data Sing NumberConstraint Source # | |
type DemoteRep NumberConstraint Source # | |
data ArrayConstraint Source #
Generic ArrayConstraint Source # | |
SingKind ArrayConstraint Source # | |
KnownNat n => SingI ArrayConstraint (AEq n) Source # | |
Eq (Sing ArrayConstraint (AEq n)) Source # | |
type Rep ArrayConstraint Source # | |
data Sing ArrayConstraint Source # | |
type DemoteRep ArrayConstraint Source # | |
SchemaText [TextConstraint] | |
SchemaBoolean | |
SchemaNumber [NumberConstraint] | |
SchemaObject [(Symbol, Schema)] | |
SchemaArray [ArrayConstraint] Schema | |
SchemaNull | |
SchemaOptional Schema |
data DemotedSchema Source #
data FieldRepr :: (Symbol, Schema) -> Type where Source #
FieldRepr :: (SingI schema, KnownSymbol name) => JsonRepr schema -> FieldRepr '(name, schema) |
toJsonRepr :: FieldRepr '(fn, sch) -> JsonRepr sch Source #
Forgetful Functor Ufr
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 #
ReprText :: Text -> JsonRepr (SchemaText cs) | |
ReprNumber :: Scientific -> JsonRepr (SchemaNumber cs) | |
ReprBoolean :: Bool -> JsonRepr SchemaBoolean | |
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) |
fromOptional :: SingI s => Sing (SchemaOptional s) -> Value -> Parser (Maybe (JsonRepr s)) Source #
class FalseConstraint a Source #
type family TopLevel (schema :: Schema) :: Constraint where ... Source #
TopLevel (SchemaArray acs s) = () | |
TopLevel (SchemaObject o) = () | |
TopLevel spec = True ~ False |