|
Generics.Pointless.Lenses.Reader.RecursionPatterns | Portability | non-portable | Stability | experimental | Maintainer | hpacheco@di.uminho.pt |
|
|
|
Description |
Pointless Lenses:
bidirectional lenses with point-free programming
This module provides catamorphism and anamorphism bidirectional combinators for the definition of recursive lenses.
The implementations use a monad reader so that each lens combinator permits a more flexible environment.
|
|
Synopsis |
|
fmap_lns' :: Fctrable f => Fix f -> ((a, Rep f c) -> c) -> Lens c a -> Lens (Rep f c) (Rep f a) | | fzip' :: Fctr f -> ((a, e) -> c) -> (Rep f a, Rep f c) -> e -> Rep f (a, c) | | fcre' :: Fctr f -> ((a, e) -> c) -> Rep f a -> e -> Rep f (a, c) | | ana_lns' :: (Mu b, Fctrable (PF b)) => ((b, a) -> a) -> Lens a (F b a) -> Lens a b | | cata_lns' :: (Mu a, Fctrable (PF a)) => ((b, a) -> a) -> Lens (F a b) b -> Lens a b | | nat_lns' :: (Mu a, Mu b, Fctrable (PF b)) => ((b, a) -> a) -> NatLens (PF a) (PF b) -> Lens a b | | bmap_lns' :: Bifctrable f => x -> BFix f -> ((a, Rep (BRep f c) x) -> c) -> Lens c a -> Lens (Rep (BRep f c) x) (Rep (BRep f a) x) | | bzip' :: x -> Bifctr f -> ((a, e) -> c) -> (Rep (BRep f a) x, Rep (BRep f c) x) -> e -> Rep (BRep f (a, c)) x | | bcre' :: x -> Bifctr f -> ((a, e) -> c) -> Rep (BRep f a) x -> e -> Rep (BRep f (a, c)) x | | gmap_lns' :: (Mu (d a), Mu (d c), Fctrable (PF (d c)), Fctrable (PF (d a)), Bifctrable (BF d), F (d a) (d c) ~ B d a (d c), F (d c) (d c) ~ B d c (d c), F (d a) (d a) ~ B d a (d a), F (d c) (d a) ~ B d c (d a)) => ((a, d c) -> c) -> ((d a, d c) -> d c) -> Lens c a -> Lens (d c) (d a) |
|
|
Documentation |
|
|
The functor mapping function fmap as a more relaxed lens.
The extra function allows user-defined behavior when creating default concrete F-values.
|
|
|
The polytypic functor zipping combinator.
Gives preference to the abstract (first) F-structure.
|
|
|
The polytypic auxiliary function for fzip'.
Similar to fmap (id / create) but using a monad reader for the concrete reconstruction function.
|
|
|
The ana recursion pattern as a more relaxed lens.
For ana_lns' to be a well-behaved lens, we MUST prove termination of |get| for each instance.
|
|
|
The cata recursion pattern as a more relaxed lens.
For cata_lns' to be a well-behaved lens, we MUST prove termination of |put| and |create| for each instance.
|
|
|
A more relaxed version of the recursion pattern for recursive functions that can be expressed both as anamorphisms and catamorphisms.
Proofs of termination are dismissed.
|
|
|
A more relaxed version of the bifunctor mapping function bmap as a lens.
Cannot employ NatLens because the extra function depends on the polymorphic type argument.
|
|
|
A more relaxed version of the the polytypic bifunctor zipping combinator.
|
|
|
|
gmap_lns' :: (Mu (d a), Mu (d c), Fctrable (PF (d c)), Fctrable (PF (d a)), Bifctrable (BF d), F (d a) (d c) ~ B d a (d c), F (d c) (d c) ~ B d c (d c), F (d a) (d a) ~ B d a (d a), F (d c) (d a) ~ B d c (d a)) => ((a, d c) -> c) -> ((d a, d c) -> d c) -> Lens c a -> Lens (d c) (d a) | Source |
|
A more relaxed version of the generic mapping lens for parametric types with one polymorphic parameter.
We do not define gmap_lns' as a recursion pattern lens because we want to provide more control in the auxiliary functions.
Using bmap_lns' we would not get (a,d c) -> c but instead (a,B d c (d a)) -> c.
|
|
Produced by Haddock version 2.7.2 |