| Portability | non-portable |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | Trustworthy |
Control.Lens.Review
Contents
Description
- type Review s t a b = forall p f. (Reviewable p, Settable f) => Overloaded p f s t a b
- type Review' t b = Review t t b b
- type AReview s t a b = Overloaded Reviewed Identity s t a b
- type AReview' t b = AReview t t b b
- unto :: (Reviewable p, Functor f) => (b -> t) -> Overloaded p f s t a b
- re :: AReview s t a b -> Getter b t
- review :: MonadReader b m => AReview s t a b -> m t
- reviews :: MonadReader b m => AReview s t a b -> (t -> r) -> m r
- reuse :: MonadState b m => AReview s t a b -> m t
- reuses :: MonadState b m => AReview s t a b -> (t -> r) -> m r
- (#) :: AReview s t a b -> b -> t
- class Profunctor p => Reviewable p where
- retagged :: p a b -> p s b
Reviewing
type Review s t a b = forall p f. (Reviewable p, Settable f) => Overloaded p f s t a bSource
type AReview s t a b = Overloaded Reviewed Identity s t a bSource
unto :: (Reviewable p, Functor f) => (b -> t) -> Overloaded p f s t a bSource
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 _LeftLeft 5
>>>6 ^.re (_Left.unto succ)Left 7
review≡view.rereviews≡views.rereuse≡use.rereuses≡uses.re
re::Prisms t a b ->Getterb tre::Isos t a b ->Getterb 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.
review≡view.rereview.unto≡id
>>>review _Left "mustard"Left "mustard"
>>>review (unto succ) 56
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 -> sreview::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::MonadReadera m =>Iso's a -> m sreview::MonadReadera 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.
reviews≡views.rereviews(untof) g ≡ g.f
>>>reviews _Left isRight "mustard"False
>>>reviews (unto succ) (*2) 38
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 -> rreviews::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::MonadReadera m =>Iso's a -> (s -> r) -> m rreviews::MonadReadera 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.
reuse≡use.rereuse.unto≡gets
>>>evalState (reuse _Left) 5Left 5
>>>evalState (reuse (unto succ)) 56
reuse::MonadStatea m =>Prism's a -> m sreuse::MonadStatea 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.
reuses≡uses.rereuses(untof) g ≡gets(g.f)
>>>evalState (reuses _Left isLeft) (5 :: Int)True
reuses::MonadStatea m =>Prism's a -> (s -> r) -> m rreuses::MonadStatea m =>Iso's a -> (s -> r) -> m r
(#) :: AReview s t a b -> b -> tSource
An infix alias for review.
untof # x ≡ f x l # x ≡ x^.rel
This is commonly used when using a Prism as a smart constructor.
>>>_Left # 4Left 4
But it can be used for any Prism
>>>base 16 # 123"7b"
(#) ::Iso's a -> a -> s (#) ::Prism's a -> a -> s (#) ::Review's a -> a -> s (#) ::Equality's a -> a -> s
Reviewable Profunctors
class Profunctor p => Reviewable p whereSource
This provides a dual notion to that of Gettable.
Instances