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

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Optic.Cotraversal

Contents

Synopsis

Cotraversal & Cxtraversal

type Cotraversal s t a b = forall p. (Choice p, Closed p, Coapplicative (Corep p), Corepresentable p) => Optic p s t a b Source #

type Cotraversal' t b = Cotraversal t t b b Source #

cotraversing :: Distributive g => (((s -> a) -> b) -> t) -> Cotraversal (g s) (g t) a b Source #

Obtain a Cotraversal by embedding a continuation into a Distributive functor.

 withGrate o cotraversingcotraversed . o

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

  • sabt ($ s) ≡ s
  • sabt (k -> f (k . sabt)) ≡ sabt (k -> f ($ k))

retraversing :: Distributive g => (b -> t) -> (b -> s -> a) -> Cotraversal (g s) (g t) a b Source #

Obtain a Cotraversal by embedding a reversed lens getter and setter into a Distributive functor.

 withLens (re o) cotraversingcotraversed . o

cotraversalVl :: (forall f. Coapplicative f => (f a -> b) -> f s -> t) -> Cotraversal s t a b Source #

Obtain a profunctor Cotraversal from a Van Laarhoven Cotraversal.

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

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

See Property.

Optics

cotraversed :: Distributive f => Cotraversal (f a) (f b) a b Source #

TODO: Document

Operators

withCotraversal :: Coapplicative f => ACotraversal f s t a b -> (f a -> b) -> f s -> t Source #

withCotraversal $ grate (flip cotraverse id) ≡ cotraverse

The cotraversal laws can be restated in terms of withCotraversal:

  • withCotraversal o (f . runIdentity) ≡  fmap f . runIdentity
  • withCotraversal o f . fmap (withCotraversal o g) == withCotraversal o (f . fmap g . getCompose) . Compose

See also https://www.cs.ox.ac.uk/jeremy.gibbons/publications/iterator.pdf

distributes :: Coapplicative f => ACotraversal f s t a (f a) -> f s -> t Source #

TODO: Document

>>> distributes left' (1, Left "foo")
Left (1,"foo")
>>> distributes left' (1, Right "foo")
Right "foo"