Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extends Representable10
with support for modifying elements.
Synopsis
- class Representable10 f => Update10 (f :: (k -> Type) -> Type) where
- updateRep10 :: Update10 f => Rep10 f a -> m a -> f m -> f m
- ixRep10 :: (Update10 f, Functor g) => Rep10 f a -> (m a -> g (m a)) -> f m -> g (f m)
- newtype FieldSetter10 f a = FS10 {
- runFS10 :: forall m. (m a -> m a) -> f m -> f m
- newtype EqualityTable f a = EqualityTable (f (Maybe :.: (:~:) a))
- equalityTable :: Update10 f => f (EqualityTable f)
- class GUpdate10 (rec :: (k -> Type) -> Type) where
- gsetters10 :: (forall a. (forall m. (m a -> m a) -> rec m -> rec m) -> r a) -> rec r
Documentation
class Representable10 f => Update10 (f :: (k -> Type) -> Type) where Source #
Extends Representable10
with support for modifying elements.
See also Update
.
updateRep10 :: Update10 f => Rep10 f a -> m a -> f m -> f m Source #
Update an f m
at a given index.
newtype FieldSetter10 f a Source #
A newtype wrapper to store field modifier functions in f
.
newtype EqualityTable f a Source #
A newtype wrapper to store tables of equality witnesses in f
.
EqualityTable (f (Maybe :.: (:~:) a)) |
equalityTable :: Update10 f => f (EqualityTable f) Source #
Implementation detail of
.TestEquality
(Field10
f)
This is a pre-populated table of
s, with Maybe
(a :~:
b)Just
s 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 #
gsetters10 :: (forall a. (forall m. (m a -> m a) -> rec m -> rec m) -> r a) -> rec r Source #
Instances
GUpdate10 (U1 :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Update | |
Update10 rec => GUpdate10 (Rec1 rec :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Update | |
(GUpdate10 f, GUpdate10 g) => GUpdate10 (f :*: g :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Update | |
(Update f, GUpdate10 g) => GUpdate10 (f :.: g :: (k -> Type) -> Type) Source # | |
Defined in Data.Ten.Update | |
GUpdate10 rec => GUpdate10 (M1 k2 i rec :: (k1 -> Type) -> Type) Source # | |
Defined in Data.Ten.Update |