schematic-0.1.0.0: JSON-biased spec and validation tool

Safe HaskellNone
LanguageHaskell2010

Data.Schematic.Schema

Documentation

type family All (c :: k -> Constraint) (s :: [k]) :: Constraint where ... Source #

Equations

All c '[] = () 
All c (a ': as) = (c a, All c as) 

data TextConstraint Source #

Constructors

TEq Nat 
TLe Nat 
TGt Nat 
TRegex Symbol 
TEnum [Symbol] 

Instances

Generic TextConstraint Source # 

Associated Types

type Rep TextConstraint :: * -> * #

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 # 
KnownNat n => Known (Sing TextConstraint (TEq n)) Source # 
KnownNat n => Known (Sing TextConstraint (TLe n)) Source # 
KnownNat n => Known (Sing TextConstraint (TGt n)) Source # 
(KnownSymbol s, Known (Sing Symbol s)) => Known (Sing TextConstraint (TRegex s)) Source # 
(All Symbol KnownSymbol ss, Known (Sing [Symbol] ss)) => Known (Sing TextConstraint (TEnum ss)) Source # 
type Rep TextConstraint Source # 
data Sing TextConstraint Source # 

data NumberConstraint Source #

Constructors

NLe Nat 
NGt Nat 
NEq Nat 

Instances

Generic NumberConstraint Source # 
Eq (Sing NumberConstraint (NLe n)) Source # 
Eq (Sing NumberConstraint (NGt n)) Source # 
Eq (Sing NumberConstraint (NEq n)) Source # 
KnownNat n => Known (Sing NumberConstraint (NLe n)) Source # 
KnownNat n => Known (Sing NumberConstraint (NGt n)) Source # 
KnownNat n => Known (Sing NumberConstraint (NEq n)) Source # 
type Rep NumberConstraint Source # 
data Sing 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 #

(KnownSymbol name, Known (Sing 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 #

Eq (Sing Schema (SchemaText cs)) 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 # 
Known (Sing [TextConstraint] sl) => Known (Sing Schema (SchemaText sl)) Source # 
Known (Sing [NumberConstraint] sl) => Known (Sing Schema (SchemaNumber sl)) Source # 
Known (Sing [(Symbol, Schema)] stl) => Known (Sing Schema (SchemaObject stl)) Source # 
(Known (Sing [ArrayConstraint] ac), Known (Sing Schema s)) => Known (Sing Schema (SchemaArray ac s)) Source # 

Methods

known :: Sing Schema (SchemaArray ac s) Source #

Known (Sing Schema SchemaNull) Source # 
Known (Sing Schema s) => Known (Sing Schema (SchemaOptional s)) Source # 
type Rep Schema Source # 
data Sing Schema Source # 

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

Constructors

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

Instances

(KnownSymbol name, Known (Sing 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 #

knownFieldName :: forall proxy fieldName schema. KnownSymbol fieldName => proxy '(fieldName, schema) -> Text Source #

knownFieldSchema :: forall proxy fieldName schema. Known (Sing 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 # 
Known (Sing 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 = FalseConstraint spec