schematic-0.4.2.0: JSON-biased spec and validation tool

Safe HaskellNone
LanguageHaskell2010

Data.Schematic.Lens

Synopsis

Documentation

type family FIndex (r :: Symbol) (rs :: [(Symbol, Schema)]) :: Nat where ... Source #

A partial relation that gives the index of a value in a list.

Equations

FIndex r ('(r, s) ': rs) = Z 
FIndex r (s ': rs) = S (FIndex r rs) 

class i ~ FIndex fn rs => FElem (fn :: Symbol) (rs :: [(Symbol, Schema)]) (i :: Nat) where Source #

Minimal complete definition

flens, fget, fput

Associated Types

type ByField fn rs i :: Schema Source #

Methods

flens :: Flens fn f g rs i Source #

fget :: FGetter fn f rs i Source #

For Vinyl users who are not using the lens package, we provide a getter.

fput :: f '(fn, ByField fn rs i) -> Rec f rs -> Rec f rs Source #

For Vinyl users who are not using the lens package, we also provide a setter. In general, it will be unambiguous what field is being written to, and so we do not take a proxy argument here.

Instances

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

Associated Types

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

Methods

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

fget :: FGetter fn f (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) Z Source #

fput :: f ((Symbol, Schema) fn (ByField fn (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) Z)) -> Rec (Symbol, Schema) f (((Symbol, Schema) ': (Symbol, Schema) fn r) rs) -> Rec (Symbol, Schema) f (((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 ByField (r :: Symbol) (((Symbol, Schema) ': s) rs :: [(Symbol, Schema)]) (S i :: Nat) :: Schema Source #

Methods

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

fget :: FGetter r f (((Symbol, Schema) ': s) rs) (S i) Source #

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

type family FImage (rs :: [(Symbol, Schema)]) (ss :: [(Symbol, Schema)]) :: [Nat] where ... Source #

A partial relation that gives the indices of a sublist in a larger list.

Equations

FImage '[] ss = '[] 
FImage ('(fn, s) ': rs) ss = FIndex fn ss ': FImage rs ss 

class is ~ FImage rs ss => FSubset (rs :: [(Symbol, Schema)]) (ss :: [(Symbol, Schema)]) is where Source #

Minimal complete definition

fsubset

Methods

fsubset :: Functor g => (Rec f rs -> g (Rec f rs)) -> Rec f ss -> g (Rec f ss) Source #

This is a lens into a slice of the larger record. Morally, we have:

fsubset :: Lens' (Rec FieldRepr ss) (Rec FieldRepr rs)

fcast :: Rec f ss -> Rec f rs Source #

The getter of the fsubset lens is fcast, which takes a larger record to a smaller one by forgetting fields.

freplace :: Rec f rs -> Rec f ss -> Rec f ss Source #

The setter of the fsubset lens is freplace, which allows a slice of a record to be replaced with different values.

Instances

FSubset ([] (Symbol, Schema)) ss ([] Nat) Source # 

Methods

fsubset :: Functor g => (Rec (Symbol, Schema) f [(Symbol, Schema)] -> g (Rec (Symbol, Schema) f [(Symbol, Schema)])) -> Rec (Symbol, Schema) f ss -> g (Rec (Symbol, Schema) f ss) Source #

fcast :: Rec (Symbol, Schema) f ss -> Rec (Symbol, Schema) f [(Symbol, Schema)] Source #

freplace :: Rec (Symbol, Schema) f [(Symbol, Schema)] -> Rec (Symbol, Schema) f ss -> Rec (Symbol, Schema) f ss Source #

((~) Schema (ByField fn ss i) s, FElem fn ss i, FSubset rs ss is) => FSubset ((:) (Symbol, Schema) ((,) Symbol Schema fn s) rs) ss ((:) Nat i is) Source # 

Methods

fsubset :: Functor g => (Rec (Symbol, Schema) f (((Symbol, Schema) ': (Symbol, Schema) fn s) rs) -> g (Rec (Symbol, Schema) f (((Symbol, Schema) ': (Symbol, Schema) fn s) rs))) -> Rec (Symbol, Schema) f ss -> g (Rec (Symbol, Schema) f ss) Source #

fcast :: Rec (Symbol, Schema) f ss -> Rec (Symbol, Schema) f (((Symbol, Schema) ': (Symbol, Schema) fn s) rs) Source #

freplace :: Rec (Symbol, Schema) f (((Symbol, Schema) ': (Symbol, Schema) fn s) rs) -> Rec (Symbol, Schema) f ss -> Rec (Symbol, Schema) f ss Source #

obj :: SingI fields => Iso' (JsonRepr (SchemaObject fields)) (Rec FieldRepr fields) Source #

arr :: SingI schema => Iso' (JsonRepr (SchemaArray cs schema)) (Vector (JsonRepr schema)) Source #

uni :: SingI (h ': tl) => Iso' (JsonRepr (SchemaUnion (h ': tl))) (Union JsonRepr (h ': tl)) Source #

txt :: SingI cs => Iso' (JsonRepr (SchemaText cs)) Text Source #

opt :: SingI schema => Iso' (JsonRepr (SchemaOptional schema)) (Maybe (JsonRepr schema)) Source #

textRepr :: (KnownSymbol fn, SingI fn, SingI cs) => Iso' (FieldRepr '(fn, SchemaText cs)) Text Source #

arrayRepr :: (KnownSymbol fn, SingI fn, SingI cs, SingI schema) => Iso' (FieldRepr '(fn, SchemaArray cs schema)) (Vector (JsonRepr schema)) Source #

objectRepr :: (KnownSymbol fn, SingI fn, SingI fields) => Iso' (FieldRepr '(fn, SchemaObject fields)) (Rec FieldRepr fields) Source #

optionalRepr :: (KnownSymbol fn, SingI fn, SingI schema) => Iso' (FieldRepr '(fn, SchemaOptional schema)) (Maybe (JsonRepr schema)) Source #