| Copyright | (C) 2012-14 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | non-portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell98 | 
Control.Lens.Review
Contents
Description
- type Review s t a b = forall p f. (Choice p, Bifunctor p, Settable f) => Optic p f s t a b
- type Review' t b = Review t t b b
- type AReview s t a b = Optic Tagged Identity s t a b
- type AReview' t b = AReview t t b b
- unto :: (Profunctor p, Bifunctor p, Functor f) => (b -> t) -> Optic p f s t a b
- un :: (Profunctor p, Bifunctor p, Functor f) => Getting a s a -> Optic' p f a s
- 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 Bifunctor p where- bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
 
- retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b
- class (Profunctor p, Bifunctor p) => Reviewable p
Reviewing
re :: AReview s t a b -> Getter b t Source
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 t Source
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 r Source
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 t Source
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 r Source
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 -> t infixr 8 Source
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
class Bifunctor p where
Minimal definition either bimap or first and second
Formally, the class Bifunctor represents a bifunctor
 from Hask -> Hask.
Intuitively it is a bifunctor where both the first and second arguments are covariant.
You can define a Bifunctor by either defining bimap or by defining both
 first and second.
If you supply bimap, you should ensure that:
bimapidid≡id
If you supply first and second, ensure:
firstid≡idsecondid≡id
If you supply both, you should also ensure:
bimapf g ≡firstf.secondg
These ensure by parametricity:
bimap(f.g) (h.i) ≡bimapf h.bimapg ifirst(f.g) ≡firstf.firstgsecond(f.g) ≡secondf.secondg
Minimal complete definition
Nothing
Methods
bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b Source
This is a profunctor used internally to implement Review
It plays a role similar to that of Accessor
 or Const do for Control.Lens.Getter
class (Profunctor p, Bifunctor p) => Reviewable p Source
This class is provided mostly for backwards compatibility with lens 3.8, but it can also shorten type signatures.
Instances
| (Profunctor p, Bifunctor p) => Reviewable p |