| Portability | Rank2Types | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Safe-Infered | 
Control.Lens.Getter
Description
A Getter a c(a -> c), which we've flipped
 into continuation passing style, (c -> r) -> a -> r and decorated
 with Accessor to obtain:
typeGettingr a c = (c ->Accessorr c) -> a ->Accessorr a
If we restrict access to knowledge about the type r and can work for
 any d and b, we could get:
typeGettera c = forall r.Gettingr a c
But we actually hide the use of Accessor behind a class Gettable
 to error messages from type class resolution rather than at unification
 time, where they are much uglier.
typeGettera c = forall f.Gettablef => (c -> f c) -> a -> f a
Everything you can do with a function, you can do with a Getter, but
 note that because of the continuation passing style (.) composes them
 in the opposite order.
Since it is only a function, every Getter obviously only retrieves a
 single value for a given input.
- type Getter a c = forall f. Gettable f => (c -> f c) -> a -> f a
- type Getting r a c = (c -> Accessor r c) -> a -> Accessor r a
- class Functor f => Gettable f  where- coerce :: f a -> f b
 
- newtype  Accessor r a = Accessor {- runAccessor :: r
 
- to :: (a -> c) -> Getter a c
- (^.) :: a -> Getting c a c -> c
- (^$) :: Getting c a c -> a -> c
- view :: Getting c a c -> a -> c
- views :: Getting m a c -> (c -> m) -> a -> m
- use :: MonadState a m => Getting c a c -> m c
- uses :: MonadState a m => Getting e a c -> (c -> e) -> m e
- query :: MonadReader a m => Getting c a c -> m c
- queries :: MonadReader a m => Getting e a c -> (c -> e) -> m e
- class (MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m where
Getters
type Getter a c = forall f. Gettable f => (c -> f c) -> a -> f aSource
A Getter describes how to retrieve a single value in a way that can be
 composed with other lens-like constructions.
Unlike a Lens a Getter is read-only. Since a Getter
 cannot be used to write back there are no lens laws that can be applied to
 it. In fact, it is isomorphic to an arbitrary function from (a -> c).
Moreover, a Getter can be used directly as a Fold,
 since it just ignores the Applicative.
type Getting r a c = (c -> Accessor r c) -> a -> Accessor r aSource
Most Getter combinators are able to be used with both a Getter or a
 Fold in limited situations, to do so, they need to be
 monomorphic in what we are going to extract with Const. To be compatible
 with Lens, Traversal and
 Iso we also restricted choices of the irrelevant b and
 d parameters.
If a function accepts a Getting r a cr is a Monoid, then
 you can pass a Fold (or
 Traversal), otherwise you can only pass this a
 Getter or Lens.
Used instead of Const to report
No instance of (SettableAccessor)
when the user attempts to misuse a Setter as a
 Getter, rather than a monolithic unification error.
Constructors
| Accessor | |
| Fields 
 | |
Building Getters
Combinators for Getters and Folds
(^.) :: a -> Getting c a c -> cSource
View the value pointed to by a Getter or Lens or the
 result of folding over all the results of a Fold or
 Traversal that points at a monoidal values.
This is the same operation as view with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
 performed with (.)
>>>:m + Data.Complex Control.Lens>>>((0, 1 :+ 2), 3)^._1._2.to magnitude2.23606797749979
(^.) :: a ->Gettera c -> c (^.) ::Monoidm => a ->Folda m -> m (^.) :: a ->SimpleIsoa c -> c (^.) :: a ->SimpleLensa c -> c (^.) ::Monoidm => a ->SimpleTraversala m -> m
(^$) :: Getting c a c -> a -> cSource
View the value pointed to by a Getter, Iso or
 Lens or the result of folding over all the results of a
 Fold or Traversal that points
 at a monoidal values.
This is the same operation as view, only infix.
>>>import Control.Lens>>>_2 ^$ (1, "hello")"hello"
(^$) ::Gettera c -> a -> c (^$) ::Monoidm =>Folda m -> a -> m (^$) ::SimpleIsoa c -> a -> c (^$) ::SimpleLensa c -> a -> c (^$) ::Monoidm =>SimpleTraversala m -> a -> m
view :: Getting c a c -> a -> cSource
View the value pointed to by a Getter, Iso or
 Lens or the result of folding over all the results of a
 Fold or Traversal that points
 at a monoidal values.
view.to=id
>>>import Control.Lens>>>view _2 (1,"hello")"hello"
It may be useful to think of view as having these more restrictive
 signatures:
view ::Gettera c -> a -> c view ::Monoidm =>Folda m -> a -> m view ::SimpleIsoa c -> a -> c view ::SimpleLensa c -> a -> c view ::Monoidm =>SimpleTraversala m -> a -> m
views :: Getting m a c -> (c -> m) -> a -> mSource
View the value of a Getter, Iso,
 Lens or the result of folding over the result of mapping
 the targets of a Fold or
 Traversal.
It may be useful to think of views as having these more restrictive
 signatures:
>>>import Control.Lens>>>views _2 length (1,"hello")5
views ::Gettera c -> (c -> d) -> a -> d views ::Monoidm =>Folda c -> (c -> m) -> a -> m views ::SimpleIsoa c -> (c -> d) -> a -> d views ::SimpleLensa c -> (c -> d) -> a -> d views ::Monoidm =>SimpleTraversala c -> (c -> m) -> a -> m
use :: MonadState a m => Getting c a c -> m cSource
Use the target of a Lens, Iso, or
 Getter in the current state, or use a summary of a
 Fold or Traversal that points
 to a monoidal value.
use ::MonadStatea m =>Gettera c -> m c use :: (MonadStatea m,Monoidr) =>Folda r -> m r use ::MonadStatea m =>SimpleIsoa c -> m c use ::MonadStatea m =>SimpleLensa c -> m c use :: (MonadStatea m,Monoidr) =>SimpleTraversala r -> m r
uses :: MonadState a m => Getting e a c -> (c -> e) -> m eSource
Use the target of a Lens, Iso or
 Getter in the current state, or use a summary of a
 Fold or Traversal that
 points to a monoidal value.
uses ::MonadStatea m =>Gettera c -> (c -> e) -> m e uses :: (MonadStatea m,Monoidr) =>Folda c -> (c -> r) -> m r uses ::MonadStatea m =>SimpleLensa c -> (c -> e) -> m e uses ::MonadStatea m =>SimpleIsoa c -> (c -> e) -> m e uses :: (MonadStatea m,Monoidr) =>SimpleTraversala c -> (c -> r) -> m r
query :: MonadReader a m => Getting c a c -> m cSource
Query the target of a Lens, Iso or
 Getter in the current state, or use a summary of a
 Fold or Traversal that points
 to a monoidal value.
query ::MonadReadera m =>Gettera c -> m c query :: (MonadReadera m,Monoidc) =>Folda c -> m c query ::MonadReadera m =>SimpleIsoa c -> m c query ::MonadReadera m =>SimpleLensa c -> m c query :: (MonadReadera m,Monoidc) =>SimpleTraversala c -> m c
queries :: MonadReader a m => Getting e a c -> (c -> e) -> m eSource
Use the target of a Lens, Iso or
 Getter in the current state, or use a summary of a
 Fold or Traversal that points
 to a monoidal value.
queries ::MonadReadera m =>Gettera c -> (c -> e) -> m e queries :: (MonadReadera m,Monoidc) =>Folda c -> (c -> e) -> m e queries ::MonadReadera m =>SimpleIsoa c -> (c -> e) -> m e queries ::MonadReadera m =>SimpleLensa c -> (c -> e) -> m e queries :: (MonadReadera m,Monoidc) =>SimpleTraversala c -> (c -> e) -> m e
class (MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m whereSource
This class allows us to use magnify part of the environment, changing the environment supplied by
 many different monad transformers. Unlike focus this can change the environment of a deeply nested monad transformer.
Also, unlike focus, this can be used with any valid Getter, but cannot be used with a Traversal or Fold.
Methods
magnify :: Getter a b -> m c -> n cSource
Run a monadic action in a larger environment than it was defined in, using a Getter.
This acts like local, but can in many cases change the type of the environment as well.
This is commonly used to lift actions in a simpler Reader monad into a monad with a larger environment type.
This can be used to edit pretty much any monad transformer stack with an environment in it:
magnify ::Gettera b -> (b -> c) -> a -> c magnify ::Gettera b -> RWS a w s c -> RWST b w s c magnify ::Gettera b -> ErrorT e (Reader b) c -> ErrorT e (Reader a) c magnify ::Gettera b -> ListT (ReaderT b (StateT s)) c -> ListT (ReaderT a (StateT s)) c ...
Instances
| Magnify ((->) b) ((->) a) b a | |
| Magnify m n b a => Magnify (ListT m) (ListT n) b a | |
| Magnify m n b a => Magnify (MaybeT m) (MaybeT n) b a | |
| Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a | |
| Magnify m m a a => Magnify (ContT r m) (ContT r m) a a | |
| (Error e, Magnify m n b a) => Magnify (ErrorT e m) (ErrorT e n) b a | |
| Monad m => Magnify (ReaderT b m) (ReaderT a m) b a | |
| Magnify m n b a => Magnify (StateT s m) (StateT s n) b a | |
| Magnify m n b a => Magnify (StateT s m) (StateT s n) b a | |
| (Monoid w, Magnify m n b a) => Magnify (WriterT w m) (WriterT w n) b a | |
| (Monoid w, Magnify m n b a) => Magnify (WriterT w m) (WriterT w n) b a | |
| (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a | |
| (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a |