Copyright | (C) 2012-16 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | Rank2Types |
Safe Haskell | Safe |
Language | Haskell98 |
A
is just any function Getter
s a(s -> a)
, which we've flipped
into continuation passing style, (a -> r) -> s -> r
and decorated
with Const
to obtain:
typeGetting
r s a = (a ->Const
r a) -> s ->Const
r s
If we restrict access to knowledge about the type r
, we could get:
typeGetter
s a = forall r.Getting
r s a
However, for Getter
(but not for Getting
) we actually permit any
functor f
which is an instance of both Functor
and Contravariant
:
typeGetter
s a = forall f. (Contravariant
f,Functor
f) => (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.
A common question is whether you can combine multiple Getter
s to
retrieve multiple values. Recall that all Getter
s are Fold
s and that
we have a
instance to play
with. Knowing this, we can use Monoid
m => Applicative
(Const
m)
to glue <>
Fold
s
together:
>>>
import Data.Monoid
>>>
(1, 2, 3, 4, 5) ^.. (_2 <> _3 <> _5)
[2,3,5]
- 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, Functor f) => a -> Optic' p f s a
- ilike :: (Indexable i p, Contravariant f, Functor 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 :: MonadReader s m => LensLike' (Const r) s a -> (a -> r) -> m r
- use :: MonadState s m => Getting a s a -> m a
- uses :: MonadState s m => LensLike' (Const r) s a -> (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
- getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f) => Optical p q f s t a b -> Optical' p q f s a
- newtype Const k a (b :: k) :: forall k. * -> k -> * = 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
, then when 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)) ->IndexedGetter
i s a
like :: (Profunctor p, Contravariant f, Functor f) => a -> Optic' p f s a Source #
ilike :: (Indexable i p, Contravariant f, Functor f) => i -> a -> Over' p f s a Source #
ilike
:: i -> a ->IndexedGetter
i 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)^._2
b
>>>
("hello","world")^._2
"world"
>>>
import Data.Complex
>>>
((0, 1 :+ 2), 3)^._1._2.to magnitude
2.23606797749979
(^.
) :: s ->Getter
s a -> a (^.
) ::Monoid
m => s ->Fold
s m -> m (^.
) :: s ->Iso'
s a -> a (^.
) :: s ->Lens'
s a -> a (^.
) ::Monoid
m => 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) a
f a
>>>
view _2 (1,"hello")
"hello"
>>>
view (to succ) 5
6
>>>
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
::Getter
s a -> s -> aview
::Monoid
m =>Fold
s m -> s -> mview
::Iso'
s a -> s -> aview
::Lens'
s a -> s -> aview
::Monoid
m =>Traversal'
s m -> s -> m
In a more general setting, such as when working with a Monad
transformer stack you can use:
view
::MonadReader
s m =>Getter
s a -> m aview
:: (MonadReader
s m,Monoid
a) =>Fold
s a -> m aview
::MonadReader
s m =>Iso'
s a -> m aview
::MonadReader
s m =>Lens'
s a -> m aview
:: (MonadReader
s m,Monoid
a) =>Traversal'
s a -> m a
views :: MonadReader s m => LensLike' (Const r) s a -> (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
.
views
l f ≡view
(l.
to
f)
>>>
views (to f) g a
g (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
::Getter
s a -> (a -> r) -> s -> rviews
::Monoid
m =>Fold
s a -> (a -> m) -> s -> mviews
::Iso'
s a -> (a -> r) -> s -> rviews
::Lens'
s a -> (a -> r) -> s -> rviews
::Monoid
m =>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
::MonadReader
s m =>Getter
s a -> (a -> r) -> m rviews
:: (MonadReader
s m,Monoid
r) =>Fold
s a -> (a -> r) -> m rviews
::MonadReader
s m =>Iso'
s a -> (a -> r) -> m rviews
::MonadReader
s m =>Lens'
s a -> (a -> r) -> m rviews
:: (MonadReader
s m,Monoid
r) =>Traversal'
s a -> (a -> r) -> m r
views
::MonadReader
s m =>Getting
r 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
::MonadState
s m =>Getter
s a -> m ause
:: (MonadState
s m,Monoid
r) =>Fold
s r -> m ruse
::MonadState
s m =>Iso'
s a -> m ause
::MonadState
s m =>Lens'
s a -> m ause
:: (MonadState
s m,Monoid
r) =>Traversal'
s r -> m r
uses :: MonadState s m => LensLike' (Const r) s a -> (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
::MonadState
s m =>Getter
s a -> (a -> r) -> m ruses
:: (MonadState
s m,Monoid
r) =>Fold
s a -> (a -> r) -> m ruses
::MonadState
s m =>Lens'
s a -> (a -> r) -> m ruses
::MonadState
s m =>Iso'
s a -> (a -> r) -> m ruses
:: (MonadState
s m,Monoid
r) =>Traversal'
s a -> (a -> r) -> m r
uses
::MonadState
s m =>Getting
r 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
::MonadWriter
w m =>Getter
w u -> m a -> m (a, u)listening
::MonadWriter
w m =>Lens'
w u -> m a -> m (a, u)listening
::MonadWriter
w m =>Iso'
w u -> m a -> m (a, u)listening
:: (MonadWriter
w m,Monoid
u) =>Fold
w u -> m a -> m (a, u)listening
:: (MonadWriter
w m,Monoid
u) =>Traversal'
w u -> m a -> m (a, u)listening
:: (MonadWriter
w m,Monoid
u) =>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
::MonadWriter
w m =>Getter
w u -> (u -> v) -> m a -> m (a, v)listenings
::MonadWriter
w m =>Lens'
w u -> (u -> v) -> m a -> m (a, v)listenings
::MonadWriter
w m =>Iso'
w u -> (u -> v) -> m a -> m (a, v)listenings
:: (MonadWriter
w m,Monoid
v) =>Fold
w u -> (u -> v) -> m a -> m (a, v)listenings
:: (MonadWriter
w m,Monoid
v) =>Traversal'
w u -> (u -> v) -> m a -> m (a, v)listenings
:: (MonadWriter
w m,Monoid
v) =>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 ->IndexedGetter
i 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
::MonadWriter
w m =>IndexedGetter
i w u -> m a -> m (a, (i, u))ilistening
::MonadWriter
w m =>IndexedLens'
i w u -> m a -> m (a, (i, u))ilistening
:: (MonadWriter
w m,Monoid
u) =>IndexedFold
i w u -> m a -> m (a, (i, u))ilistening
:: (MonadWriter
w m,Monoid
u) =>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
::MonadWriter
w m =>IndexedGetter
w u -> (i -> u -> v) -> m a -> m (a, v)ilistenings
::MonadWriter
w m =>IndexedLens'
w u -> (i -> u -> v) -> m a -> m (a, v)ilistenings
:: (MonadWriter
w m,Monoid
v) =>IndexedFold
w u -> (i -> u -> v) -> m a -> m (a, v)ilistenings
:: (MonadWriter
w m,Monoid
v) =>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.
getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f) => Optical p q f s t a b -> Optical' p q f s a Source #
Coerce a Getter
-compatible Optical
to an Optical'
. This
is useful when using a Traversal
that is not simple as a Getter
or a
Fold
.
getting
::Traversal
s t a b ->Fold
s agetting
::Lens
s t a b ->Getter
s agetting
::IndexedTraversal
i s t a b ->IndexedFold
i s agetting
::IndexedLens
i s t a b ->IndexedGetter
i s a
newtype Const k a (b :: k) :: forall k. * -> k -> * #
The Const
functor.
Generic1 k (Const k a) | |
Bitraversable (Const *) | Since: 4.10.0.0 |
Bifoldable (Const *) | Since: 4.10.0.0 |
Bifunctor (Const *) | Since: 4.8.0.0 |
Eq2 (Const *) | Since: 4.9.0.0 |
Ord2 (Const *) | Since: 4.9.0.0 |
Read2 (Const *) | Since: 4.9.0.0 |
Show2 (Const *) | Since: 4.9.0.0 |
Biapplicative (Const *) | |
Hashable2 (Const *) | |
Bitraversable1 (Const *) | |
Bifoldable1 (Const *) | |
Biapply (Const *) | |
Semigroupoid * (Const *) | |
Sieve (Forget r) (Const * r) | |
Functor (Const * m) | Since: 2.1 |
Monoid m => Applicative (Const * m) | Since: 2.0.1 |
Foldable (Const * m) | Since: 4.7.0.0 |
Traversable (Const * m) | Since: 4.7.0.0 |
Contravariant (Const * a) | |
Eq a => Eq1 (Const * a) | Since: 4.9.0.0 |
Ord a => Ord1 (Const * a) | Since: 4.9.0.0 |
Read a => Read1 (Const * a) | Since: 4.9.0.0 |
Show a => Show1 (Const * a) | Since: 4.9.0.0 |
Hashable a => Hashable1 (Const * a) | |
Semigroup m => Apply (Const * m) | |
Bounded a => Bounded (Const k a b) | |
Enum a => Enum (Const k a b) | |
Eq a => Eq (Const k a b) | |
Floating a => Floating (Const k a b) | |
Fractional a => Fractional (Const k a b) | |
Integral a => Integral (Const k a b) | |
(Typeable * k3, Data a, Typeable k3 b) => Data (Const k3 a b) | Since: 4.10.0.0 |
Num a => Num (Const k a b) | |
Ord a => Ord (Const k a b) | |
Read a => Read (Const k a b) | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
Real a => Real (Const k a b) | |
RealFloat a => RealFloat (Const k a b) | |
RealFrac a => RealFrac (Const k a b) | |
Show a => Show (Const k a b) | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
Ix a => Ix (Const k a b) | |
Generic (Const k a b) | |
Semigroup a => Semigroup (Const k a b) | Since: 4.9.0.0 |
Monoid a => Monoid (Const k a b) | |
Storable a => Storable (Const k a b) | |
Bits a => Bits (Const k a b) | |
FiniteBits a => FiniteBits (Const k a b) | |
Hashable a => Hashable (Const k a b) | |
Wrapped (Const k a x) Source # | |
(~) * t (Const k2 a' x') => Rewrapped (Const k1 a x) t Source # | |
type Rep1 k (Const k a) | |
type Rep (Const k a b) | |
type Unwrapped (Const k a x) Source # | |