pointless-lenses-0.0.7: Pointless Lenses library

Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@di.uminho.pt

Generics.Pointless.Lenses.Combinators

Contents

Description

Pointless Lenses: bidirectional lenses with point-free programming

This module lifts a standard set of point-free combinators into bidirectional lenses.

Synopsis

Point-free lens combinators

ap_lns :: Eq a => (b -> a) -> Lens (a -> b, a) bSource

Function application is a lens.

(?<) :: Eq a => Lens (a -> Bool, a) (Either a a)Source

Predicate application is a lens.

rexp_lns :: Lens b c -> Lens (a -> b) (a -> c)Source

The right exponentiation combinator as a lens. Applies a lens to the domain of a function.

curry_lns :: Lens ((a, b) -> c) (a -> b -> c)Source

uncurry_lns :: Lens (a -> b -> c) ((a, b) -> c)Source

(.<) :: Lens b a -> Lens c b -> Lens c aSource

The lens composition operator.

fst_lns :: (a -> b) -> Lens (a, b) aSource

The fst point-free combinator.

snd_lns :: (b -> a) -> Lens (a, b) bSource

The snd point-free combinator.

(><<) :: Lens c a -> Lens d b -> Lens (c, d) (a, b)Source

The >< point-free combinator.

(\/<) :: (c -> Either One One) -> Lens a c -> Lens b c -> Lens (Either a b) cSource

(.\/<) :: Lens a c -> Lens b c -> Lens (Either a b) cSource

The left-biased / point-free combinator. It chooses left values over right values in the create direction.

(\/.<) :: Lens a c -> Lens b c -> Lens (Either a b) cSource

The right-biased / point-free combinator. It chooses right values over left values in the create direction.

(-|-<) :: Lens c a -> Lens d b -> Lens (Either c d) (Either a b)Source

The -|- point-free combinator.

sum_lns :: ((a, d) -> c) -> ((b, c) -> d) -> Lens c a -> Lens d b -> Lens (Either c d) (Either a b)Source

The -|- point-free combinator with user-defined backward behavior.

(!<) :: (One -> c) -> Lens c OneSource

The pnt point-free combinator.

(!\/<) :: Eq a => a -> Lens b a -> c -> Lens (Either c b) aSource

The (a!) / f point-free expression, where a is a constant and f a function. The additional argument of type c is the default value when the view matches the constant of type a.

(\/!<) :: Eq a => a -> Lens c a -> b -> Lens (Either c b) aSource

The f / (a!) point-free expression, where a is a constant and f a function. The additional argument of type b is the default value when the view matches the constant of type a.

(#\/<) :: Lens a c -> Lens b (Either c d) -> Lens (Either a b) (Either c d)Source

The inl / f point-free expression, where f is a function.

(\/$<) :: Lens a (Either c d) -> Lens b d -> Lens (Either a b) (Either c d)Source

The f / inr point-free expression, where f is a function.

(!/\<) :: Lens c a -> Lens c (One, a)Source

The bang / f point-free expression, where f is a function.

(/\!<) :: Lens c a -> Lens c (a, One)Source

The f / bang point-free expression, where f is a function.

Point-free isomorphism combinators

id_lns :: Lens c cSource

The lens identity combinator.

subr_lns :: Lens (a, (b, c)) (b, (a, c))Source

The subr point-free combinator.

subl_lns :: Lens ((a, b), c) ((a, c), b)Source

The subl point-free combinator.

cosubr_lns :: Lens (Either a (Either b c)) (Either b (Either a c))Source

The cosubr point-free combinator.

cosubl_lns :: Lens (Either (Either a b) c) (Either (Either a c) b)Source

The cosubl point-free combinator.

distp_lns :: Lens ((c, d), (a, b)) ((c, a), (d, b))Source

The distp point-free combinator.

dists_lns :: Lens (Either a b, Either c d) (Either (Either (a, c) (a, d)) (Either (b, c) (b, d)))Source

The dists point-free combinator.

swap_lns :: Lens (a, b) (b, a)Source

The swap point-free combinator.

coswap_lns :: Lens (Either a b) (Either b a)Source

The coswap point-free combinator

distl_lns :: Lens (Either a b, c) (Either (a, c) (b, c))Source

The distl point-free combinator.

undistl_lns :: Lens (Either (a, c) (b, c)) (Either a b, c)Source

The undistl point-free combinator.

distr_lns :: Lens (c, Either a b) (Either (c, a) (c, b))Source

The distr point-free combinator.

undistr_lns :: Lens (Either (c, a) (c, b)) (c, Either a b)Source

The undistr point-free combinator.

assocl_lns :: Lens (a, (b, c)) ((a, b), c)Source

The assocl point-free combinator.

assocr_lns :: Lens ((a, b), c) (a, (b, c))Source

The assocr point-free combinator.

coassocl_lns :: Lens (Either a (Either b c)) (Either (Either a b) c)Source

The coassocl point-free combinator.

coassocr_lns :: Lens (Either (Either a b) c) (Either a (Either b c))Source

The coassocr point-free combinator.