ten-0.1.0.2: Typeclasses like Functor, etc. over arity-1 type constructors.
Safe HaskellNone
LanguageHaskell2010

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

Documentation

newtype Field10 f a Source #

A Rep10 type as a parametric accessor function.

Constructors

Field10 

Fields

Instances

Instances details
Update10 f => TestEquality (Field10 f :: k -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

testEquality :: forall (a :: k0) (b :: k0). Field10 f a -> Field10 f b -> Maybe (a :~: b) #

Update10 f => GEq (Field10 f :: k -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

geq :: forall (a :: k0) (b :: k0). Field10 f a -> Field10 f b -> Maybe (a :~: b) #

(Traversable10 f, Applicative10 f, Update10 f) => GCompare (Field10 f :: k -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

gcompare :: forall (a :: k0) (b :: k0). Field10 f a -> Field10 f b -> GOrdering a b #

(Constrained10 c f, Applicative10 f) => Entails (Field10 f :: k -> Type) (c :: k -> Constraint) Source # 
Instance details

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 # 
Instance details

Defined in Data.Ten.Field

Methods

(==) :: Field10 f a -> Field10 f a -> Bool #

(/=) :: Field10 f a -> Field10 f a -> Bool #

(Traversable10 f, Applicative10 f) => Ord (Field10 f a) Source # 
Instance details

Defined in Data.Ten.Field

Methods

compare :: Field10 f a -> Field10 f a -> Ordering #

(<) :: Field10 f a -> Field10 f a -> Bool #

(<=) :: Field10 f a -> Field10 f a -> Bool #

(>) :: Field10 f a -> Field10 f a -> Bool #

(>=) :: Field10 f a -> Field10 f a -> Bool #

max :: Field10 f a -> Field10 f a -> Field10 f a #

min :: Field10 f a -> Field10 f a -> Field10 f a #

FieldPaths10 f => Show (Field10 f a) Source # 
Instance details

Defined in Data.Ten.Field

Methods

showsPrec :: Int -> Field10 f a -> ShowS #

show :: Field10 f a -> String #

showList :: [Field10 f a] -> ShowS #

(Traversable10 f, Applicative10 f) => Hashable (Field10 f a) Source # 
Instance details

Defined in Data.Ten.Field

Methods

hashWithSalt :: Int -> Field10 f a -> Int #

hash :: Field10 f a -> Int #

FieldPaths10 f => Portray (Field10 f a) Source # 
Instance details

Defined in Data.Ten.Field

Methods

portray :: Field10 f a -> Portrayal #

portrayList :: [Field10 f a] -> Portrayal #

(Traversable10 f, Applicative10 f, FieldPaths10 f) => Diff (Field10 f a) Source # 
Instance details

Defined in Data.Ten.Field

Methods

diff :: Field10 f a -> Field10 f a -> Maybe Portrayal #

class FieldPaths10 (rec :: (k -> Type) -> Type) where Source #

Provides a path of field selectors / lenses identifying each "field".

Instances

Instances details
FieldPaths10 (Ap10 a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

(Generic1 rec, GFieldPaths10 (Rep1 rec)) => FieldPaths10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) rec :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

class GFieldPaths10 (rec :: (k -> Type) -> Type) where Source #

Generic1 implementation of FieldPaths10.

Methods

gfieldPaths10 :: (forall a. [PathComponent] -> r a) -> rec r Source #

Instances

Instances details
GFieldPaths10 (U1 :: (k -> Type) -> Type) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Data.Ten.Field

Methods

gfieldPaths10 :: (forall (a :: k0). [PathComponent] -> r a) -> M1 D ('MetaData n m p 'True) (M1 C i (M1 S j rec)) r Source #

GFieldPaths10 rec => GFieldPaths10 (M1 D ('MetaData n m p 'False) rec :: (k -> Type) -> Type) Source # 
Instance details

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 # 
Instance details

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.

Instances

Instances details
Constrained10 (c :: k -> Constraint) (U1 :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

constrained10 :: U1 (Dict1 c) Source #

c a => Constrained10 (c :: k -> Constraint) (Ap10 a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

constrained10 :: Ap10 a (Dict1 c) Source #

Constrained10 c f => Constrained10 (c :: k -> Constraint) (Rec1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

constrained10 :: Rec1 f (Dict1 c) Source #

(Constrained10 c f, Constrained10 c g) => Constrained10 (c :: k -> Constraint) (f :*: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

constrained10 :: (f :*: g) (Dict1 c) Source #

(Generic1 f, Constrained10 c (Rep1 f)) => Constrained10 (c :: k -> Constraint) (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

(Applicative f, Constrained10 c g) => Constrained10 (c :: k -> Constraint) (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

constrained10 :: (f :.: g) (Dict1 c) Source #

Constrained10 c f => Constrained10 (c :: k -> Constraint) (M1 i c1 f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Field

Methods

constrained10 :: M1 i c1 f (Dict1 c) Source #