pointless-lenses-0.0.5: Pointless Lenses librarySource codeContentsIndex
Generics.Pointless.Lenses.RecursionPatterns
Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@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.

Synopsis
inn_lns :: Mu a => Lens (F a a) a
out_lns :: Mu a => Lens a (F a a)
fmap_lns :: Fctrable f => Fix f -> Lens c a -> Lens (Rep f c) (Rep f a)
fzip :: Fctr f -> (a -> c) -> (Rep f a, Rep f c) -> Rep f (a, c)
hylo_lns :: (Mu b, Fctrable (PF b)) => b -> Lens (F b c) c -> Lens a (F b a) -> Lens a c
ana_lns :: (Mu b, Fctrable (PF b)) => b -> Lens a (F b a) -> Lens a b
cata_lns :: (Mu a, Fctrable (PF a)) => a -> Lens (F a b) b -> Lens a b
nat_lns :: (Mu a, Mu b, Fctrable (PF b)) => a -> NatLens (PF a) (PF b) -> Lens a b
binn_lns :: Bimu d => Lens (B d a (d a)) (d a)
bout_lns :: Bimu d => Lens (d a) (B d a (d a))
bmap_lns :: Bifctrable f => BFix f -> Lens c a -> NatLens (BRep f c) (BRep f a)
bzip :: x -> Bifctr f -> (a -> c) -> (Rep (BRep f a) x, Rep (BRep f c) x) -> Rep (BRep f (a, c)) x
gmap_lns :: (Mu (d c), Mu (d a), Fctrable (PF (d c)), Bifctrable (BF d), F (d a) (d a) ~ B d a (d a), F (d c) (d a) ~ B d c (d a)) => d a -> Lens c a -> Lens (d c) (d a)
Documentation
inn_lns :: Mu a => Lens (F a a) aSource
The inn point-free combinator.
out_lns :: Mu a => Lens a (F a a)Source
The out point-free combinator.
fmap_lns :: Fctrable f => Fix f -> Lens c a -> Lens (Rep f c) (Rep f a)Source
The functor mapping function fmap as a lens.
fzip :: Fctr f -> (a -> c) -> (Rep f a, Rep f c) -> Rep f (a, c)Source
The polytypic functor zipping combinator. Gives preference to the abstract (first) F-structure.
hylo_lns :: (Mu b, Fctrable (PF b)) => b -> Lens (F b c) c -> Lens a (F b a) -> Lens a cSource
The hylo recursion pattern as the composition of a lens catamorphism after a lens anamorphism .
ana_lns :: (Mu b, Fctrable (PF b)) => b -> Lens a (F b a) -> Lens a bSource
The ana recursion pattern as a lens. For ana_lns to be a well-behaved lens, we MUST prove termination of |get| for each instance.
cata_lns :: (Mu a, Fctrable (PF a)) => a -> Lens (F a b) b -> Lens a bSource
The cata recursion pattern as a lens. For cata_lns to be a well-behaved lens, we MUST prove termination of |put| and |create| for each instance.
nat_lns :: (Mu a, Mu b, Fctrable (PF b)) => a -> NatLens (PF a) (PF b) -> Lens a bSource
The recursion pattern for recursive functions that can be expressed both as anamorphisms and catamorphisms. Proofs of termination are dismissed.
binn_lns :: Bimu d => Lens (B d a (d a)) (d a)Source
bout_lns :: Bimu d => Lens (d a) (B d a (d a))Source
bmap_lns :: Bifctrable f => BFix f -> Lens c a -> NatLens (BRep f c) (BRep f a)Source
The bifunctor mapping function bmap as a lens.
bzip :: x -> Bifctr f -> (a -> c) -> (Rep (BRep f a) x, Rep (BRep f c) x) -> Rep (BRep f (a, c)) xSource
The polytypic bifunctor zipping combinator. Just maps over the polymorphic parameter. To map over the recursive parameter we can use fzip.
gmap_lns :: (Mu (d c), Mu (d a), Fctrable (PF (d c)), Bifctrable (BF d), F (d a) (d a) ~ B d a (d a), F (d c) (d a) ~ B d c (d a)) => d a -> Lens c a -> Lens (d c) (d a)Source
Generic mapping lens for parametric types with one polymorphic parameter. Cannot be defined using nat_lns because of the required equality constraints between functors and bifunctors. This could, however, be overcome by defining specific recursive combinators for bifunctors.
Produced by Haddock version 2.7.2