lens-3.8.0.2: Lenses, Folds and Traversals

Portabilitynon-portable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.Review

Contents

Description

A Review is a type-restricted form of a Prism that can only be used for writing back via re, review, reuse.

Synopsis

Reviewing

type Review s t a b = forall p f. (Reviewable p, Settable f) => Overloaded p f s t a bSource

This is a limited form of a Prism that can only be used for re operations.

Like with a Getter, there are no laws to state for a Review.

You can generate a Review by using unto. You can also use any Prism or Iso directly as a Review.

type Review' t b = Review t t b bSource

type AReview s t a b = Overloaded Reviewed Identity s t a bSource

If you see this in a signature for a function, the function is expecting a Review (in practice, this usually means a Prism).

type AReview' t b = AReview t t b bSource

unto :: (Reviewable p, Functor f) => (b -> t) -> Overloaded p f s t a bSource

An analogue of to for review.

 unto :: (b -> t) -> Review' t b

re :: AReview s t a b -> Getter b tSource

Turn a Prism or Iso around to build a Getter.

If you have an Iso, from is a more powerful version of this function that will return an Iso instead of a mere Getter.

>>> 5 ^.re _Left
Left 5
 reviewview  . re
 reviewsviews . re
 reuseuse   . re
 reusesuses  . re
 re :: Prism s t a b -> Getter b t
 re :: Iso s t a b   -> Getter b t

review :: MonadReader b m => AReview s t a b -> m tSource

This can be used to turn an Iso or Prism around and view a value (or the current environment) through it the other way.

 reviewview . re
>>> review _Left "mustard"
Left "mustard"

Usually review is used in the (->) Monad with a Prism or Iso, in which case it may be useful to think of it as having one of these more restricted type signatures:

 review :: Iso' s a   -> a -> s
 review :: Prism' s a -> a -> s

However, when working with a Monad transformer stack, it is sometimes useful to be able to review the current environment, in which case one of these more slightly more liberal type signatures may be beneficial to think of it as having:

 review :: MonadReader a m => Iso' s a   -> m s
 review :: MonadReader a m => Prism' s a -> m s

reviews :: MonadReader b m => AReview s t a b -> (t -> r) -> m rSource

This can be used to turn an Iso or Prism around and view a value (or the current environment) through it the other way, applying a function.

 reviewsviews . re
>>> reviews _Left isRight "mustard"
False

Usually this function is used in the (->) Monad with a Prism or Iso, in which case it may be useful to think of it as having one of these more restricted type signatures:

 reviews :: Iso' s a   -> (s -> r) -> a -> r
 reviews :: Prism' s a -> (s -> r) -> a -> r

However, when working with a Monad transformer stack, it is sometimes useful to be able to review the current environment, in which case one of these more slightly more liberal type signatures may be beneficial to think of it as having:

 reviews :: MonadReader a m => Iso' s a   -> (s -> r) -> m r
 reviews :: MonadReader a m => Prism' s a -> (s -> r) -> m r

reuse :: MonadState b m => AReview s t a b -> m tSource

This can be used to turn an Iso or Prism around and use a value (or the current environment) through it the other way.

reuseuse . re
>>> evalState (reuse _Left) 5
Left 5
 reuse :: MonadState a m => Prism' s a -> m s
 reuse :: MonadState a m => Iso' s a   -> m s

reuses :: MonadState b m => AReview s t a b -> (t -> r) -> m rSource

This can be used to turn an Iso or Prism around and use the current state through it the other way, applying a function.

reusesuses . re
>>> evalState (reuses _Left isLeft) (5 :: Int)
True
 reuses :: MonadState a m => Prism' s a -> (s -> r) -> m r
 reuses :: MonadState a m => Iso' s a   -> (s -> r) -> m r

Reviewable Profunctors

class Profunctor p => Reviewable p whereSource

This provides a dual notion to that of Gettable.

Methods

retagged :: p a b -> p s bSource