| Copyright | (C) 2012-15 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | Rank2Types | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Control.Lens.Getter
Contents
Description
A Getter s a(s -> a), which we've flipped
 into continuation passing style, (a -> r) -> s -> r and decorated
 with Const to obtain:
typeGettingr s a = (a ->Constr a) -> s ->Constr s
If we restrict access to knowledge about the type r, we could get:
typeGetters a = forall r.Gettingr s a
However, for Getter (but not for Getting) we actually permit any
 functor f which is an instance of both Functor and Contravariant:
typeGetters a = forall f. (Contravariantf,Functorf) => (a -> f a) -> s -> f s
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 s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
- type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s
- type Accessing p m s a = p a (Const m a) -> s -> Const m s
- to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
- ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a
- like :: (Profunctor p, Contravariant f) => a -> Optic' p f s a
- ilike :: (Indexable i p, Contravariant f) => i -> a -> Over' p f s a
- (^.) :: s -> Getting a s a -> a
- view :: MonadReader s m => Getting a s a -> m a
- views :: (Profunctor p, MonadReader s m) => Over' p (Const r) s a -> p a r -> m r
- use :: MonadState s m => Getting a s a -> m a
- uses :: (Profunctor p, MonadState s m) => Over' p (Const r) s a -> p a r -> m r
- listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u)
- listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v)
- (^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a)
- iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a)
- iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
- iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a)
- iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
- ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u))
- ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v)
- class Contravariant f where
- coerce :: (Contravariant f, Functor f) => f a -> f b
- coerced :: (Functor f, Contravariant f) => LensLike f s t a b -> LensLike' f s a
- newtype Const a b :: * -> * -> * = Const {- getConst :: a
 
Getters
type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s Source
A Getter describes how to retrieve a single value in a way that can be
 composed with other LensLike 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 (s -> a).
Moreover, a Getter can be used directly as a Fold,
 since it just ignores the Applicative.
type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s Source
Every IndexedGetter is a valid IndexedFold and can be used for Getting like a Getter.
type Getting r s a = (a -> Const r a) -> s -> Const r s Source
When you see this in a type signature it indicates that you can
 pass the function a Lens, Getter,
 Traversal, Fold,
 Prism, Iso, or one of
 the indexed variants, and it will just "do the right thing".
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 t and
 b parameters.
If a function accepts a Getting r s ar is a Monoid, then
 you can pass a Fold (or
 Traversal), otherwise you can only pass this a
 Getter or Lens.
type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s Source
Used to consume an IndexedFold.
type Accessing p m s a = p a (Const m a) -> s -> Const m s Source
This is a convenient alias used when consuming (indexed) getters and (indexed) folds in a highly general fashion.
Building Getters
to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a Source
ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a Source
ito:: (s -> (i, a)) ->IndexedGetteri s a
like :: (Profunctor p, Contravariant f) => a -> Optic' p f s a Source
ilike :: (Indexable i p, Contravariant f) => i -> a -> Over' p f s a Source
ilike:: i -> a ->IndexedGetteri s a
Combinators for Getters and Folds
(^.) :: s -> Getting a s a -> a infixl 8 Source
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 (.).
>>>(a,b)^._2b
>>>("hello","world")^._2"world"
>>>import Data.Complex>>>((0, 1 :+ 2), 3)^._1._2.to magnitude2.23606797749979
(^.) :: s ->Getters a -> a (^.) ::Monoidm => s ->Folds m -> m (^.) :: s ->Iso's a -> a (^.) :: s ->Lens's a -> a (^.) ::Monoidm => s ->Traversal's m -> m
view :: MonadReader s m => Getting a s a -> m a Source
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 value.
view.to≡id
>>>view (to f) af a
>>>view _2 (1,"hello")"hello"
>>>view (to succ) 56
>>>view (_2._1) ("hello",("world","!!!"))"world"
As view is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold,
 It may be useful to think of it as having one of these more restricted signatures:
view::Getters a -> s -> aview::Monoidm =>Folds m -> s -> mview::Iso's a -> s -> aview::Lens's a -> s -> aview::Monoidm =>Traversal's m -> s -> m
In a more general setting, such as when working with a Monad transformer stack you can use:
view::MonadReaders m =>Getters a -> m aview:: (MonadReaders m,Monoida) =>Folds a -> m aview::MonadReaders m =>Iso's a -> m aview::MonadReaders m =>Lens's a -> m aview:: (MonadReaders m,Monoida) =>Traversal's a -> m a
views :: (Profunctor p, MonadReader s m) => Over' p (Const r) s a -> p a r -> m r Source
View a function of the value pointed to by a Getter or Lens or the result of
 folding over the result of mapping the targets of a Fold or
 Traversal.
viewsl f ≡view(l.tof)
>>>views (to f) g ag (f a)
>>>views _2 length (1,"hello")5
As views is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold,
 It may be useful to think of it as having one of these more restricted signatures:
views::Getters a -> (a -> r) -> s -> rviews::Monoidm =>Folds a -> (a -> m) -> s -> mviews::Iso's a -> (a -> r) -> s -> rviews::Lens's a -> (a -> r) -> s -> rviews::Monoidm =>Traversal's a -> (a -> m) -> s -> m
In a more general setting, such as when working with a Monad transformer stack you can use:
views::MonadReaders m =>Getters a -> (a -> r) -> m rviews:: (MonadReaders m,Monoidr) =>Folds a -> (a -> r) -> m rviews::MonadReaders m =>Iso's a -> (a -> r) -> m rviews::MonadReaders m =>Lens's a -> (a -> r) -> m rviews:: (MonadReaders m,Monoidr) =>Traversal's a -> (a -> r) -> m r
views::MonadReaders m =>Gettingr s a -> (a -> r) -> m r
use :: MonadState s m => Getting a s a -> m a Source
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.
>>>evalState (use _1) (a,b)a
>>>evalState (use _1) ("hello","world")"hello"
use::MonadStates m =>Getters a -> m ause:: (MonadStates m,Monoidr) =>Folds r -> m ruse::MonadStates m =>Iso's a -> m ause::MonadStates m =>Lens's a -> m ause:: (MonadStates m,Monoidr) =>Traversal's r -> m r
uses :: (Profunctor p, MonadState s m) => Over' p (Const r) s a -> p a r -> m r Source
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.
>>>evalState (uses _1 length) ("hello","world")5
uses::MonadStates m =>Getters a -> (a -> r) -> m ruses:: (MonadStates m,Monoidr) =>Folds a -> (a -> r) -> m ruses::MonadStates m =>Lens's a -> (a -> r) -> m ruses::MonadStates m =>Iso's a -> (a -> r) -> m ruses:: (MonadStates m,Monoidr) =>Traversal's a -> (a -> r) -> m r
uses::MonadStates m =>Gettingr s t a b -> (a -> r) -> m r
listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u) Source
This is a generalized form of listen that only extracts the portion of
 the log that is focused on by a Getter. If given a Fold or a Traversal
 then a monoidal summary of the parts of the log that are visited will be
 returned.
listening::MonadWriterw m =>Getterw u -> m a -> m (a, u)listening::MonadWriterw m =>Lens'w u -> m a -> m (a, u)listening::MonadWriterw m =>Iso'w u -> m a -> m (a, u)listening:: (MonadWriterw m,Monoidu) =>Foldw u -> m a -> m (a, u)listening:: (MonadWriterw m,Monoidu) =>Traversal'w u -> m a -> m (a, u)listening:: (MonadWriterw m,Monoidu) =>Prism'w u -> m a -> m (a, u)
listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v) Source
This is a generalized form of listen that only extracts the portion of
 the log that is focused on by a Getter. If given a Fold or a Traversal
 then a monoidal summary of the parts of the log that are visited will be
 returned.
listenings::MonadWriterw m =>Getterw u -> (u -> v) -> m a -> m (a, v)listenings::MonadWriterw m =>Lens'w u -> (u -> v) -> m a -> m (a, v)listenings::MonadWriterw m =>Iso'w u -> (u -> v) -> m a -> m (a, v)listenings:: (MonadWriterw m,Monoidv) =>Foldw u -> (u -> v) -> m a -> m (a, v)listenings:: (MonadWriterw m,Monoidv) =>Traversal'w u -> (u -> v) -> m a -> m (a, v)listenings:: (MonadWriterw m,Monoidv) =>Prism'w u -> (u -> v) -> m a -> m (a, v)
Indexed Getters
Indexed Getter Combinators
(^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a) infixl 8 Source
View the index and value of an IndexedGetter or IndexedLens.
This is the same operation as iview with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
 performed with (.).
(^@.) :: s ->IndexedGetteri s a -> (i, a) (^@.) :: s ->IndexedLens'i s a -> (i, a)
The result probably doesn't have much meaning when applied to an IndexedFold.
iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a) Source
View the index and value of an IndexedGetter into the current environment as a pair.
When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of
 the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.
iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r Source
View a function of the index and value of an IndexedGetter into the current environment.
When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.
iviews≡ifoldMapOf
iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a) Source
Use the index and value of an IndexedGetter into the current state as a pair.
When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of
 the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.
iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r Source
Use a function of the index and value of an IndexedGetter into the current state.
When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.
ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u)) Source
This is a generalized form of listen that only extracts the portion of
 the log that is focused on by a Getter. If given a Fold or a Traversal
 then a monoidal summary of the parts of the log that are visited will be
 returned.
ilistening::MonadWriterw m =>IndexedGetteri w u -> m a -> m (a, (i, u))ilistening::MonadWriterw m =>IndexedLens'i w u -> m a -> m (a, (i, u))ilistening:: (MonadWriterw m,Monoidu) =>IndexedFoldi w u -> m a -> m (a, (i, u))ilistening:: (MonadWriterw m,Monoidu) =>IndexedTraversal'i w u -> m a -> m (a, (i, u))
ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v) Source
This is a generalized form of listen that only extracts the portion of
 the log that is focused on by a Getter. If given a Fold or a Traversal
 then a monoidal summary of the parts of the log that are visited will be
 returned.
ilistenings::MonadWriterw m =>IndexedGetterw u -> (i -> u -> v) -> m a -> m (a, v)ilistenings::MonadWriterw m =>IndexedLens'w u -> (i -> u -> v) -> m a -> m (a, v)ilistenings:: (MonadWriterw m,Monoidv) =>IndexedFoldw u -> (i -> u -> v) -> m a -> m (a, v)ilistenings:: (MonadWriterw m,Monoidv) =>IndexedTraversal'w u -> (i -> u -> v) -> m a -> m (a, v)
Implementation Details
class Contravariant f where
Any instance should be subject to the following laws:
contramap id = id contramap f . contramap g = contramap (g . f)
Note, that the second law follows from the free theorem of the type of
 contramap and the first law, so you need only check that the former
 condition holds.
Minimal complete definition
Instances
coerce :: (Contravariant f, Functor f) => f a -> f b Source
newtype Const a b :: * -> * -> *
Instances
| Bifunctor Const | |
| Biapplicative Const | |
| Bitraversable Const | |
| Bifoldable Const | |
| Bitraversable1 Const | |
| Biapply Const | |
| Bifoldable1 Const | |
| Functor (Const m) | |
| Monoid m => Applicative (Const m) | |
| Foldable (Const m) | |
| Traversable (Const m) | |
| Generic1 (Const a) | |
| Contravariant (Const a) | |
| Semigroup m => Apply (Const m) | |
| Sieve (Forget r) (Const r) | |
| Eq a => Eq (Const a b) | |
| Ord a => Ord (Const a b) | |
| Read a => Read (Const a b) | |
| Show a => Show (Const a b) | |
| Generic (Const a b) | |
| Monoid a => Monoid (Const a b) | |
| Semigroup a => Semigroup (Const a b) | |
| Wrapped (Const a x) Source | |
| (~) * t (Const a' x') => Rewrapped (Const a x) t Source | |
| type Rep1 (Const a) = D1 D1Const (C1 C1_0Const (S1 S1_0_0Const (Rec0 a))) | |
| type Rep (Const a b) = D1 D1Const (C1 C1_0Const (S1 S1_0_0Const (Rec0 a))) | |
| type Unwrapped (Const a x) = a Source | |