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

Data.Ten.Update

Description

Extends Representable10 with support for modifying elements.

Synopsis

Documentation

class Representable10 f => Update10 (f :: (k -> Type) -> Type) where Source #

Extends Representable10 with support for modifying elements.

See also Update.

Methods

overRep10 :: Rep10 f a -> (m a -> m a) -> f m -> f m Source #

Modify an f m at a given index.

Instances

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

Defined in Data.Ten.Update

Methods

overRep10 :: forall (a0 :: k0) m. Rep10 (Ap10 a) a0 -> (m a0 -> m a0) -> Ap10 a m -> Ap10 a m Source #

(Generic1 f, Applicative10 (Rep1 f), GTabulate10 (Rep1 f), GUpdate10 (Rep1 f)) => Update10 (Wrapped1 (Generic1 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Update

Methods

overRep10 :: forall (a :: k0) m. Rep10 (Wrapped1 Generic1 f) a -> (m a -> m a) -> Wrapped1 Generic1 f m -> Wrapped1 Generic1 f m Source #

updateRep10 :: Update10 f => Rep10 f a -> m a -> f m -> f m Source #

Update an f m at a given index.

ixRep10 :: (Update10 f, Functor g) => Rep10 f a -> (m a -> g (m a)) -> f m -> g (f m) Source #

A Lens to the field identified by a given Rep10.

    ix10 :: Update10 f => Rep10 f a -> Lens' (f m) (m a)

newtype FieldSetter10 f a Source #

A newtype wrapper to store field modifier functions in f.

Constructors

FS10 

Fields

  • runFS10 :: forall m. (m a -> m a) -> f m -> f m
     

newtype EqualityTable f a Source #

A newtype wrapper to store tables of equality witnesses in f.

Constructors

EqualityTable (f (Maybe :.: (:~:) a)) 

equalityTable :: Update10 f => f (EqualityTable f) Source #

Implementation detail of TestEquality (Field10 f).

This is a pre-populated table of Maybe (a :~: b)s, with Justs in the elements where the inner position is the same as the outer position, i.e. along the "diagonal". Then we can test two forall m. f m -> m a functions for equality, by applying them in turn to the two layers of f, and see if we reach a Just or a Nothing.

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

Generic1 implementation of Update10.

Methods

gsetters10 :: (forall a. (forall m. (m a -> m a) -> rec m -> rec m) -> r a) -> rec r Source #

Instances

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

Defined in Data.Ten.Update

Methods

gsetters10 :: (forall (a :: k0). (forall (m :: k0 -> Type). (m a -> m a) -> U1 m -> U1 m) -> r a) -> U1 r Source #

Update10 rec => GUpdate10 (Rec1 rec :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Update

Methods

gsetters10 :: (forall (a :: k0). (forall (m :: k0 -> Type). (m a -> m a) -> Rec1 rec m -> Rec1 rec m) -> r a) -> Rec1 rec r Source #

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

Defined in Data.Ten.Update

Methods

gsetters10 :: (forall (a :: k0). (forall (m :: k0 -> Type). (m a -> m a) -> (f :*: g) m -> (f :*: g) m) -> r a) -> (f :*: g) r Source #

(Update f, GUpdate10 g) => GUpdate10 (f :.: g :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Update

Methods

gsetters10 :: (forall (a :: k0). (forall (m :: k0 -> Type). (m a -> m a) -> (f :.: g) m -> (f :.: g) m) -> r a) -> (f :.: g) r Source #

GUpdate10 rec => GUpdate10 (M1 k2 i rec :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.Update

Methods

gsetters10 :: (forall (a :: k). (forall (m :: k -> Type). (m a -> m a) -> M1 k2 i rec m -> M1 k2 i rec m) -> r a) -> M1 k2 i rec r Source #