schematic-0.2.1.0: JSON-biased spec and validation tool

Safe HaskellNone
LanguageHaskell2010

Data.Schematic.Schema

Synopsis

Documentation

data TextConstraint Source #

Instances

Generic TextConstraint Source # 

Associated Types

type Rep TextConstraint :: * -> * #

SingKind TextConstraint Source # 
KnownNat n => SingI TextConstraint (TEq n) Source # 

Methods

sing :: Sing (TEq n) a #

KnownNat n => SingI TextConstraint (TLt n) Source # 

Methods

sing :: Sing (TLt n) a #

KnownNat n => SingI TextConstraint (TLe n) Source # 

Methods

sing :: Sing (TLe n) a #

KnownNat n => SingI TextConstraint (TGt n) Source # 

Methods

sing :: Sing (TGt n) a #

KnownNat n => SingI TextConstraint (TGe n) Source # 

Methods

sing :: Sing (TGe n) a #

(KnownSymbol s, SingI Symbol s) => SingI TextConstraint (TRegex s) Source # 

Methods

sing :: Sing (TRegex s) a #

SingI [Symbol] ss => SingI TextConstraint (TEnum ss) Source # 

Methods

sing :: Sing (TEnum ss) a #

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 #

Constructors

NLe Nat 
NLt Nat 
NGt Nat 
NGe Nat 
NEq Nat 

Instances

Generic NumberConstraint Source # 
SingKind NumberConstraint Source # 
KnownNat n => SingI NumberConstraint (NLe n) Source # 

Methods

sing :: Sing (NLe n) a #

KnownNat n => SingI NumberConstraint (NLt n) Source # 

Methods

sing :: Sing (NLt n) a #

KnownNat n => SingI NumberConstraint (NGt n) Source # 

Methods

sing :: Sing (NGt n) a #

KnownNat n => SingI NumberConstraint (NGe n) Source # 

Methods

sing :: Sing (NGe n) a #

KnownNat n => SingI NumberConstraint (NEq n) Source # 

Methods

sing :: Sing (NEq n) a #

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 Schema Source #

Instances

Generic Schema Source # 

Associated Types

type Rep Schema :: * -> * #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

SingKind Schema Source # 

Associated Types

type DemoteRep Schema :: * #

SingI Schema SchemaBoolean Source # 

Methods

sing :: Sing SchemaBoolean a #

SingI Schema SchemaNull Source # 

Methods

sing :: Sing SchemaNull a #

SingI [TextConstraint] sl => SingI Schema (SchemaText sl) Source # 

Methods

sing :: Sing (SchemaText sl) a #

SingI [NumberConstraint] sl => SingI Schema (SchemaNumber sl) Source # 

Methods

sing :: Sing (SchemaNumber sl) a #

SingI [(Symbol, Schema)] stl => SingI Schema (SchemaObject stl) Source # 

Methods

sing :: Sing (SchemaObject stl) a #

SingI Schema s => SingI Schema (SchemaOptional s) Source # 

Methods

sing :: Sing (SchemaOptional s) a #

(KnownSymbol name, SingI Schema schema, Serial m (JsonRepr schema)) => Serial m (FieldRepr ((,) Symbol Schema name schema)) Source # 

Methods

series :: Series m (FieldRepr ((Symbol, Schema) name schema)) #

(SingI [ArrayConstraint] ac, SingI Schema s) => SingI Schema (SchemaArray ac s) Source # 

Methods

sing :: Sing (SchemaArray ac s) a #

FElem fn ((:) (Symbol, Schema) ((,) Symbol Schema fn r) rs) Z Source # 

Associated Types

type ByRevision (fn :: Symbol) ((:) (Symbol, Schema) ((,) Symbol Schema fn r) rs :: [(Symbol, Schema)]) (Z :: Nat) :: Schema Source #

Methods

flens :: Functor g => proxy fn -> (FieldRepr ((Symbol, Schema) fn (ByRevision fn (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) Z)) -> g (FieldRepr ((Symbol, Schema) fn (ByRevision fn (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) Z)))) -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) -> g (Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': (Symbol, Schema) fn r) rs)) Source #

fget :: proxy fn -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) -> FieldRepr ((Symbol, Schema) fn (ByRevision fn (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) Z)) Source #

fput :: FieldRepr ((Symbol, Schema) fn (ByRevision fn (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) Z)) -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) Source #

((~) Nat (FIndex r ((:) (Symbol, Schema) s rs)) (S i), FElem r rs i) => FElem r ((:) (Symbol, Schema) s rs) (S i) Source # 

Associated Types

type ByRevision (r :: Symbol) ((:) (Symbol, Schema) s rs :: [(Symbol, Schema)]) (S i :: Nat) :: Schema Source #

Methods

flens :: Functor g => proxy r -> (FieldRepr ((Symbol, Schema) r (ByRevision r (((Symbol, Schema) ': s) rs) (S i))) -> g (FieldRepr ((Symbol, Schema) r (ByRevision r (((Symbol, Schema) ': s) rs) (S i))))) -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': s) rs) -> g (Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': s) rs)) Source #

fget :: proxy r -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': s) rs) -> FieldRepr ((Symbol, Schema) r (ByRevision r (((Symbol, Schema) ': s) rs) (S i))) Source #

fput :: FieldRepr ((Symbol, Schema) r (ByRevision r (((Symbol, Schema) ': s) rs) (S i))) -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': s) rs) -> Rec (Symbol, Schema) FieldRepr (((Symbol, Schema) ': s) rs) Source #

Eq (JsonRepr schema) => Eq (FieldRepr ((,) Symbol Schema name schema)) Source # 

Methods

(==) :: FieldRepr ((Symbol, Schema) name schema) -> FieldRepr ((Symbol, Schema) name schema) -> Bool #

(/=) :: FieldRepr ((Symbol, Schema) name schema) -> FieldRepr ((Symbol, Schema) name schema) -> Bool #

Show (JsonRepr schema) => Show (FieldRepr ((,) Symbol Schema name schema)) Source # 

Methods

showsPrec :: Int -> FieldRepr ((Symbol, Schema) name schema) -> ShowS #

show :: FieldRepr ((Symbol, Schema) name schema) -> String #

showList :: [FieldRepr ((Symbol, Schema) name schema)] -> ShowS #

Eq (Sing Schema (SchemaText cs)) Source # 
Eq (Sing Schema SchemaBoolean) Source # 
Eq (Sing Schema (SchemaNumber cs)) Source # 
Eq (Sing Schema (SchemaObject cs)) Source # 
Eq (Sing Schema (SchemaArray as s)) Source # 

Methods

(==) :: Sing Schema (SchemaArray as s) -> Sing Schema (SchemaArray as s) -> Bool #

(/=) :: Sing Schema (SchemaArray as s) -> Sing Schema (SchemaArray as s) -> Bool #

Eq (Sing Schema SchemaNull) Source # 
Eq (Sing Schema (SchemaOptional s)) Source # 
type Rep Schema Source # 
data Sing Schema Source # 
type DemoteRep Schema Source # 
type ByRevision fn ((:) (Symbol, Schema) ((,) Symbol Schema fn r) rs) Z Source # 
type ByRevision fn ((:) (Symbol, Schema) ((,) Symbol Schema fn r) rs) Z = r
type ByRevision fn ((:) (Symbol, Schema) s rs) (S i) Source # 
type ByRevision fn ((:) (Symbol, Schema) s rs) (S i) = ByRevision fn rs i

data DemotedSchema Source #

data FieldRepr :: (Symbol, Schema) -> Type where Source #

Constructors

FieldRepr :: (SingI schema, KnownSymbol name) => JsonRepr schema -> FieldRepr '(name, schema) 

Instances

(KnownSymbol name, SingI Schema schema, Serial m (JsonRepr schema)) => Serial m (FieldRepr ((,) Symbol Schema name schema)) Source # 

Methods

series :: Series m (FieldRepr ((Symbol, Schema) name schema)) #

Eq (JsonRepr schema) => Eq (FieldRepr ((,) Symbol Schema name schema)) Source # 

Methods

(==) :: FieldRepr ((Symbol, Schema) name schema) -> FieldRepr ((Symbol, Schema) name schema) -> Bool #

(/=) :: FieldRepr ((Symbol, Schema) name schema) -> FieldRepr ((Symbol, Schema) name schema) -> Bool #

Show (JsonRepr schema) => Show (FieldRepr ((,) Symbol Schema name schema)) Source # 

Methods

showsPrec :: Int -> FieldRepr ((Symbol, Schema) name schema) -> ShowS #

show :: FieldRepr ((Symbol, Schema) name schema) -> String #

showList :: [FieldRepr ((Symbol, Schema) name schema)] -> ShowS #

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 #

Instances

(Monad m, Serial m (Rec (Symbol, Schema) FieldRepr fs)) => Serial m (JsonRepr (SchemaObject fs)) Source # 

Methods

series :: Series m (JsonRepr (SchemaObject fs)) #

Serial m (JsonRepr s) => Serial m (JsonRepr (SchemaOptional s)) Source # 
Serial m (Vector (JsonRepr s)) => Serial m (JsonRepr (SchemaArray cs s)) Source # 

Methods

series :: Series m (JsonRepr (SchemaArray cs s)) #

Monad m => Serial m (JsonRepr SchemaNull) Source # 
(Monad m, Serial m Scientific) => Serial m (JsonRepr (SchemaNumber cs)) Source # 

Methods

series :: Series m (JsonRepr (SchemaNumber cs)) #

(Monad m, Serial m Text) => Serial m (JsonRepr (SchemaText cs)) Source # 

Methods

series :: Series m (JsonRepr (SchemaText cs)) #

Eq (JsonRepr (SchemaText cs)) Source # 
Eq (JsonRepr (SchemaNumber cs)) Source # 
Eq (Rec (Symbol, Schema) FieldRepr fs) => Eq (JsonRepr (SchemaObject fs)) Source # 
Eq (JsonRepr s) => Eq (JsonRepr (SchemaArray as s)) Source # 

Methods

(==) :: JsonRepr (SchemaArray as s) -> JsonRepr (SchemaArray as s) -> Bool #

(/=) :: JsonRepr (SchemaArray as s) -> JsonRepr (SchemaArray as s) -> Bool #

Eq (JsonRepr SchemaNull) Source # 
Eq (JsonRepr s) => Eq (JsonRepr (SchemaOptional s)) Source # 
Show (JsonRepr (SchemaText cs)) Source # 
Show (JsonRepr (SchemaNumber cs)) Source # 
RecAll (Symbol, Schema) FieldRepr fs Show => Show (JsonRepr (SchemaObject fs)) Source # 
Show (JsonRepr s) => Show (JsonRepr (SchemaArray acs s)) Source # 

Methods

showsPrec :: Int -> JsonRepr (SchemaArray acs s) -> ShowS #

show :: JsonRepr (SchemaArray acs s) -> String #

showList :: [JsonRepr (SchemaArray acs s)] -> ShowS #

Show (JsonRepr SchemaNull) Source # 
Show (JsonRepr s) => Show (JsonRepr (SchemaOptional s)) Source # 
ToJSON (JsonRepr a) Source # 
SingI Schema schema => FromJSON (JsonRepr schema) Source # 

Methods

parseJSON :: Value -> Parser (JsonRepr schema) #

parseJSONList :: Value -> Parser [JsonRepr schema] #

type family TopLevel (schema :: Schema) :: Constraint where ... Source #

Equations

TopLevel (SchemaArray acs s) = () 
TopLevel (SchemaObject o) = () 
TopLevel spec = True ~ False