profunctor-optics-0.0.0.1: An optics library compatible with the typeclasses in 'profunctors'.

Safe HaskellSafe
LanguageHaskell2010

Data.Profunctor.Optic.Repn

Synopsis

Documentation

representing :: (forall f. Functor f => (a -> f b) -> s -> f t) -> Repn s t a b Source #

Obtain a representable profunctor optic from a Van Laarhoven LensLike.

Caution: In order for the generated optic to be well-defined, you must ensure that the input satisfies the following properties:

  • abst pure ≡ pure
  • fmap (abst f) . abst g ≡ getCompose . abst (Compose . fmap f . g)

See Property.

ixrepresenting :: (forall f. Functor f => (i -> a -> f b) -> s -> f t) -> Ixrepn i s t a b Source #

TODO: Document

corepresenting :: (forall f. Functor f => (f a -> b) -> f s -> t) -> Corepn s t a b Source #

Obtain a corepresentable profunctor optic from a Van Laarhoven GrateLike.

cxrepresenting :: (forall f. Functor f => (k -> f a -> b) -> f s -> t) -> Cxrepn k s t a b Source #

TODO: Document

cloneRepn :: Optic (Star (Rep p)) s t a b -> RepnLike p s t a b Source #

TODO: Document

cloneCorepn :: Optic (Costar (Corep p)) s t a b -> CorepnLike p s t a b Source #

TODO: Document

repnOf :: Applicative f => ATraversal f s t a b -> (a -> f b) -> s -> f t Source #

The traversal laws can be stated in terms of repnOf:

Identity:

repnOf t (Identity . f) ≡  Identity (fmap f)

Composition:

Compose . fmap (repnOf t f) . repnOf t g ≡ repnOf t (Compose . fmap f . g)
repnOf :: Functor f => Lens s t a b -> (a -> f b) -> s -> f t
repnOf :: Applicative f => Traversal s t a b -> (a -> f b) -> s -> f t

corepnOf :: Functor f => Optic (Costar f) s t a b -> (f a -> b) -> f s -> t Source #

A more permissive variant of zipWithFOf.

corepnOf $ grate (flip cotraverse id) ≡ cotraverse

closed' :: Corepn (c -> a) (c -> b) a b Source #

A more permissive variant of closed.

distributed' :: Distributive f => Corepn (f a) (f b) a b Source #

A more permissive variant of distributed.