Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Ten.Field
Description
Provides Generic1
derivation of Representable10
based on Field10
.
Like with Data.Functor.Field, we use parametric functions
forall m. f m -> m a
to identify positions tagged with type a
within
f
. This leads to instances for Representable10
and Update10
.
Synopsis
- newtype Field10 f a = Field10 {
- getField10 :: forall m. f m -> m a
- class FieldPaths10 (rec :: (k -> Type) -> Type) where
- fieldPaths10 :: rec (Const [PathComponent])
- class GFieldPaths10 (rec :: (k -> Type) -> Type) where
- gfieldPaths10 :: (forall a. [PathComponent] -> r a) -> rec r
- class Constrained10 (c :: k -> Constraint) (f :: (k -> Type) -> Type) where
- constrained10 :: f (Dict1 c)
Documentation
A Rep10
type as a parametric accessor function.
Constructors
Field10 | |
Fields
|
Instances
Update10 f => TestEquality (Field10 f :: k -> Type) Source # | |
Defined in Data.Ten.Field | |
Update10 f => GEq (Field10 f :: k -> Type) Source # | |
(Traversable10 f, Applicative10 f, Update10 f) => GCompare (Field10 f :: k -> Type) Source # | |
(Constrained10 c f, Applicative10 f) => Entails (Field10 f :: k -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.Ten.Field Methods entailment :: forall (a :: k0). Field10 f a -> Dict1 c a Source # | |
(Traversable10 f, Applicative10 f) => Eq (Field10 f a) Source # | |
(Traversable10 f, Applicative10 f) => Ord (Field10 f a) Source # | |
Defined in Data.Ten.Field | |
FieldPaths10 f => Show (Field10 f a) Source # | |
(Traversable10 f, Applicative10 f) => Hashable (Field10 f a) Source # | |
Defined in Data.Ten.Field | |
FieldPaths10 f => Portray (Field10 f a) Source # | |
Defined in Data.Ten.Field | |
(Traversable10 f, Applicative10 f, FieldPaths10 f) => Diff (Field10 f a) Source # | |
class FieldPaths10 (rec :: (k -> Type) -> Type) where Source #
Provides a path of field selectors / lenses identifying each "field".
Methods
fieldPaths10 :: rec (Const [PathComponent]) Source #
Instances
FieldPaths10 (Ap10 a :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods fieldPaths10 :: Ap10 a (Const [PathComponent]) Source # | |
(Generic1 rec, GFieldPaths10 (Rep1 rec)) => FieldPaths10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) rec :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods fieldPaths10 :: Wrapped1 Generic1 rec (Const [PathComponent]) Source # |
class GFieldPaths10 (rec :: (k -> Type) -> Type) where Source #
Generic1
implementation of FieldPaths10
.
Methods
gfieldPaths10 :: (forall a. [PathComponent] -> r a) -> rec r Source #
Instances
GFieldPaths10 (U1 :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> U1 r Source # | |
(Functor10 rec, FieldPaths10 rec) => GFieldPaths10 (Rec1 rec :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> Rec1 rec r Source # | |
(GFieldPaths10 f, GFieldPaths10 g) => GFieldPaths10 (f :*: g :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> (f :*: g) r Source # | |
(Functor f, FieldPaths f, GFieldPaths10 g) => GFieldPaths10 (f :.: g :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> (f :.: g) r Source # | |
(KnownSymbol sym, GFieldPaths10 rec) => GFieldPaths10 (M1 S ('MetaSel ('Just sym) b c d) rec :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> M1 S ('MetaSel ('Just sym) b c d) rec r Source # | |
GFieldPaths10 rec => GFieldPaths10 (M1 D ('MetaData n m p 'True) (M1 C i (M1 S j rec)) :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field | |
GFieldPaths10 rec => GFieldPaths10 (M1 D ('MetaData n m p 'False) rec :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> M1 D ('MetaData n m p 'False) rec r Source # | |
GFieldPaths10 rec => GFieldPaths10 (M1 C i rec :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Field Methods gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> M1 C i rec r Source # |
class Constrained10 (c :: k -> Constraint) (f :: (k -> Type) -> Type) where Source #
Constrained10 c f
means that in f m
, all applications of m
are to types x
that satisfy constraint c
.
Methods
constrained10 :: f (Dict1 c) Source #
Recover instances of c
to accompany each m
element in f
.