Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type family FIndex (r :: Symbol) (rs :: [(Symbol, Schema)]) :: Nat where ...
- class i ~ FIndex fn rs => FElem (fn :: Symbol) (rs :: [(Symbol, Schema)]) (i :: Nat) where
- type family FImage (rs :: [(Symbol, Schema)]) (ss :: [(Symbol, Schema)]) :: [Nat] where ...
- class is ~ FImage rs ss => FSubset (rs :: [(Symbol, Schema)]) (ss :: [(Symbol, Schema)]) is where
- obj :: Iso' (JsonRepr (SchemaObject fields)) (Rec FieldRepr fields)
- arr :: Iso' (JsonRepr (SchemaArray cs schema)) (Vector (JsonRepr schema))
- uni :: Iso' (JsonRepr (SchemaUnion (h ': tl))) (Union JsonRepr (h ': tl))
- txt :: Iso' (JsonRepr (SchemaText cs)) Text
- num :: Iso' (JsonRepr (SchemaNumber cs)) Scientific
- opt :: Iso' (JsonRepr (SchemaOptional schema)) (Maybe (JsonRepr schema))
- bln :: Iso' (JsonRepr SchemaBoolean) Bool
- textRepr :: (KnownSymbol fn, SingI cs) => Iso' (FieldRepr '(fn, SchemaText cs)) Text
- numberRepr :: (KnownSymbol fn, SingI cs) => Iso' (FieldRepr '(fn, SchemaNumber cs)) Scientific
- boolRepr :: KnownSymbol fn => Iso' (FieldRepr '(fn, SchemaBoolean)) Bool
- arrayRepr :: (KnownSymbol fn, SingI cs, SingI schema) => Iso' (FieldRepr '(fn, SchemaArray cs schema)) (Vector (JsonRepr schema))
- objectRepr :: (KnownSymbol fn, SingI fields) => Iso' (FieldRepr '(fn, SchemaObject fields)) (Rec FieldRepr fields)
- optionalRepr :: (KnownSymbol fn, SingI schema) => Iso' (FieldRepr '(fn, SchemaOptional schema)) (Maybe (JsonRepr schema))
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.
class i ~ FIndex fn rs => FElem (fn :: Symbol) (rs :: [(Symbol, Schema)]) (i :: Nat) where Source #
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 ((,) fn r ': rs) Z Source # | |
Defined in Data.Schematic.Lens flens :: Functor g => (f (fn, ByField fn ((fn, r) ': rs) Z) -> g (f (fn, ByField fn ((fn, r) ': rs) Z))) -> Rec f ((fn, r) ': rs) -> g (Rec f ((fn, r) ': rs)) Source # fget :: FGetter fn f ((fn, r) ': rs) Z Source # fput :: f (fn, ByField fn ((fn, r) ': rs) Z) -> Rec f ((fn, r) ': rs) -> Rec f ((fn, r) ': rs) Source # | |
(FIndex r (s ': rs) ~ S i, FElem r rs i) => FElem r (s ': rs) (S i) Source # | |
Defined in Data.Schematic.Lens |
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.
class is ~ FImage rs ss => FSubset (rs :: [(Symbol, Schema)]) (ss :: [(Symbol, Schema)]) is where Source #
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)
num :: Iso' (JsonRepr (SchemaNumber cs)) Scientific Source #
textRepr :: (KnownSymbol fn, SingI cs) => Iso' (FieldRepr '(fn, SchemaText cs)) Text Source #
numberRepr :: (KnownSymbol fn, SingI cs) => Iso' (FieldRepr '(fn, SchemaNumber cs)) Scientific Source #
boolRepr :: KnownSymbol fn => Iso' (FieldRepr '(fn, SchemaBoolean)) Bool Source #
arrayRepr :: (KnownSymbol fn, SingI cs, SingI schema) => Iso' (FieldRepr '(fn, SchemaArray cs schema)) (Vector (JsonRepr schema)) Source #
objectRepr :: (KnownSymbol fn, SingI fields) => Iso' (FieldRepr '(fn, SchemaObject fields)) (Rec FieldRepr fields) Source #
optionalRepr :: (KnownSymbol fn, SingI schema) => Iso' (FieldRepr '(fn, SchemaOptional schema)) (Maybe (JsonRepr schema)) Source #