Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
A
is a purely functional reference.
Lens
s t a b
While a Traversal
could be used for
Getting
like a valid Fold
,
it wasn't a valid Getter
as Applicative
wasn't a superclass of
Gettable
.
Functor
, however is the superclass of both.
typeLens
s t a b = forall f.Functor
f => (a -> f b) -> s -> f t
Every Lens
can be used for Getting
like a
Fold
that doesn't use the Applicative
or
Gettable
.
Every Lens
is a valid Traversal
that only uses
the Functor
part of the Applicative
it is supplied.
Every Lens
can be used for Getting
like a valid
Getter
, since Functor
is a superclass of Gettable
Since every Lens
can be used for Getting
like a
valid Getter
it follows that it must view exactly one element in the
structure.
The lens laws follow from this property and the desire for it to act like
a Traversable
when used as a
Traversal
.
In the examples below, getter
and setter
are supplied as example getters
and setters, and are not actual functions supplied by this package.
- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
- type Simple f s a = f s s a a
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- (%%~) :: LensLike f s t a b -> (a -> f b) -> s -> f t
- (%%=) :: MonadState s m => LensLike ((,) r) s s a b -> (a -> (r, b)) -> m r
- choosing :: Functor f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (Either s s') (Either t t') a b
- chosen :: Lens (Either a a) (Either b b) a b
- alongside :: LensLike (Context a b) s t a b -> LensLike (Context a' b') s' t' a' b' -> Lens (s, s') (t, t') (a, a') (b, b')
- inside :: LensLike (Context a b) s t a b -> Lens (e -> s) (e -> t) (e -> a) (e -> b)
- (<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t)
- (<+~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<-~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<*~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<//~) :: Fractional a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<^~) :: (Num a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)
- (<^^~) :: (Fractional a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)
- (<**~) :: Floating a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<||~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t)
- (<&&~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t)
- (<<>~) :: Monoid m => LensLike ((,) m) s t m m -> m -> s -> (m, t)
- (<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t)
- (<<.~) :: LensLike ((,) a) s t a b -> b -> s -> (a, t)
- (<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m b
- (<+=) :: (MonadState s m, Num a) => SimpleLensLike ((,) a) s a -> a -> m a
- (<-=) :: (MonadState s m, Num a) => SimpleLensLike ((,) a) s a -> a -> m a
- (<*=) :: (MonadState s m, Num a) => SimpleLensLike ((,) a) s a -> a -> m a
- (<//=) :: (MonadState s m, Fractional a) => SimpleLensLike ((,) a) s a -> a -> m a
- (<^=) :: (MonadState s m, Num a, Integral e) => SimpleLensLike ((,) a) s a -> e -> m a
- (<^^=) :: (MonadState s m, Fractional a, Integral e) => SimpleLensLike ((,) a) s a -> e -> m a
- (<**=) :: (MonadState s m, Floating a) => SimpleLensLike ((,) a) s a -> a -> m a
- (<||=) :: MonadState s m => SimpleLensLike ((,) Bool) s Bool -> Bool -> m Bool
- (<&&=) :: MonadState s m => SimpleLensLike ((,) Bool) s Bool -> Bool -> m Bool
- (<<>=) :: (MonadState s m, Monoid r) => SimpleLensLike ((,) r) s r -> r -> m r
- (<<%=) :: MonadState s m => LensLike ((,) a) s s a b -> (a -> b) -> m a
- (<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a
- (<<~) :: MonadState s m => LensLike (Context a b) s s a b -> m b -> m b
- cloneLens :: Functor f => LensLike (Context a b) s t a b -> (a -> f b) -> s -> f t
- newtype ReifiedLens s t a b = ReifyLens {
- reflectLens :: Lens s t a b
- data Context a b t = Context (b -> t) a
- locus :: ComonadStore s w => Simple Lens (w a) s
- type LensLike f s t a b = (a -> f b) -> s -> f t
- type Overloaded k f s t a b = k (a -> f b) (s -> f t)
- type SimpleLens s a = Lens s s a a
- type SimpleLensLike f s a = LensLike f s s a a
- type SimpleOverloaded k f s a = Overloaded k f s s a a
- type SimpleReifiedLens s a = ReifiedLens s s a a
Lenses
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f tSource
A Lens
is actually a lens family as described in
http://comonad.com/reader/2012/mirrored-lenses/.
With great power comes great responsibility and a Lens
is subject to the
three common sense lens laws:
1) You get back what you put in:
view
l (set
l b a) ≡ b
2) Putting back what you got doesn't change anything:
set
l (view
l a) a ≡ a
3) Setting twice is the same as setting once:
set
l c (set
l b a) ≡set
l c a
These laws are strong enough that the 4 type parameters of a Lens
cannot
vary fully independently. For more on how they interact, read the "Why is
it a Lens Family?" section of
http://comonad.com/reader/2012/mirrored-lenses/.
Every Lens
can be used directly as a Setter
or
Traversal
.
You can also use a Lens
for Getting
as if it were a
Fold
or Getter
.
Since every lens is a valid Traversal
, the
traversal laws are required of any lenses you create:
lpure
≡pure
fmap
(l f).
l g ≡getCompose
.
l (Compose
.
fmap
f.
g)
typeLens
s t a b = forall f.Functor
f =>LensLike
f s t a b
type Simple f s a = f s s a aSource
A Simple
Lens
, Simple
Traversal
, ... can
be used instead of a Lens
,Traversal
, ...
whenever the type variables don't change upon setting a value.
imaginary
::Simple
Lens
(Complex
a) atraverseHead
::Simple
Traversal
[a] a
Note: To use this alias in your own code with
or
LensLike
fSetter
, you may have to turn on LiberalTypeSynonyms
.
(%%~) :: LensLike f s t a b -> (a -> f b) -> s -> f tSource
(%%~
) can be used in one of two scenarios:
When applied to a Lens
, it can edit the target of the Lens
in a
structure, extracting a functorial result.
When applied to a Traversal
, it can edit the
targets of the Traversals
, extracting an applicative summary of its
actions.
For all that the definition of this combinator is just:
(%%~
) ≡id
(%%~
) ::Functor
f =>Iso
s t a b -> (a -> f b) -> s -> f t (%%~
) ::Functor
f =>Lens
s t a b -> (a -> f b) -> s -> f t (%%~
) ::Applicative
f =>Traversal
s t a b -> (a -> f b) -> s -> f t
It may be beneficial to think about it as if it had these even more restrictive types, however:
When applied to a Traversal
, it can edit the
targets of the Traversals
, extracting a supplemental monoidal summary
of its actions, by choosing f = ((,) m)
(%%~
) ::Iso
s t a b -> (a -> (r, b)) -> s -> (r, t) (%%~
) ::Lens
s t a b -> (a -> (r, b)) -> s -> (r, t) (%%~
) ::Monoid
m =>Traversal
s t a b -> (a -> (m, b)) -> s -> (m, t)
(%%=) :: MonadState s m => LensLike ((,) r) s s a b -> (a -> (r, b)) -> m rSource
Modify the target of a Lens
in the current state returning some extra
information of type r
or modify all targets of a
Traversal
in the current state, extracting extra
information of type r
and return a monoidal summary of the changes.
>>>
runState (_1 %%= \x -> (f x, g x)) (a,b)
(f a,(g a,b))
(%%=
) ≡ (state
.
)
It may be useful to think of (%%=
), instead, as having either of the
following more restricted type signatures:
(%%=
) ::MonadState
s m =>Iso
s s a b -> (a -> (r, b)) -> m r (%%=
) ::MonadState
s m =>Lens
s s a b -> (a -> (r, b)) -> m r (%%=
) :: (MonadState
s m,Monoid
r) =>Traversal
s s a b -> (a -> (r, b)) -> m r
Lateral Composition
choosing :: Functor f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (Either s s') (Either t t') a bSource
Merge two lenses, getters, setters, folds or traversals.
chosen
≡choosing
id
id
choosing
::Getter
s a ->Getter
s' a ->Getter
(Either
s s') achoosing
::Fold
s a ->Fold
s' a ->Fold
(Either
s s') achoosing
::Simple
Lens
s a ->Simple
Lens
s' a ->Simple
Lens
(Either
s s') achoosing
::Simple
Traversal
s a ->Simple
Traversal
s' a ->Simple
Traversal
(Either
s s') achoosing
::Simple
Setter
s a ->Simple
Setter
s' a ->Simple
Setter
(Either
s s') a
alongside :: LensLike (Context a b) s t a b -> LensLike (Context a' b') s' t' a' b' -> Lens (s, s') (t, t') (a, a') (b, b')Source
inside :: LensLike (Context a b) s t a b -> Lens (e -> s) (e -> t) (e -> a) (e -> b)Source
Lift a Lens
so it can run under a function.
Setting Functionally with Passthrough
(<//~) :: Fractional a => LensLike ((,) a) s t a a -> a -> s -> (a, t)Source
Divide the target of a fractionally valued Lens
and return the result.
When you do not need the result of the division, (//~
) is more flexible.
(<//~
) ::Fractional
b =>Simple
Lens
s a -> a -> a -> (s, a) (<//~
) ::Fractional
b =>Simple
Iso
s a -> a -> a -> (s, a))
(<^~) :: (Num a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)Source
Raise the target of a numerically valued Lens
to a non-negative
Integral
power and return the result
When you do not need the result of the division, (^~
) is more flexible.
(<^~
) :: (Num
b,Integral
e) =>Simple
Lens
s a -> e -> a -> (a, s) (<^~
) :: (Num
b,Integral
e) =>Simple
Iso
s a -> e -> a -> (a, s)
(<^^~) :: (Fractional a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)Source
Raise the target of a fractionally valued Lens
to an Integral
power
and return the result.
When you do not need the result of the division, (^^~
) is more flexible.
(<^^~
) :: (Fractional
b,Integral
e) =>Simple
Lens
s a -> e -> a -> (a, s) (<^^~
) :: (Fractional
b,Integral
e) =>Simple
Iso
s a -> e -> a -> (a, s)
Setting State with Passthrough
(<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m bSource
Modify the target of a Lens
into your monad's state by a user supplied
function and return the result.
When applied to a Traversal
, it this will return a monoidal summary of all of the intermediate
results.
When you do not need the result of the operation, (%=
) is more flexible.
(<%=
) ::MonadState
s m =>Simple
Lens
s a -> (a -> a) -> m a (<%=
) ::MonadState
s m =>Simple
Iso
s a -> (a -> a) -> m a (<%=
) :: (MonadState
s m,Monoid
a) =>Simple
Traversal
s a -> (a -> a) -> m a
(<+=) :: (MonadState s m, Num a) => SimpleLensLike ((,) a) s a -> a -> m aSource
(<-=) :: (MonadState s m, Num a) => SimpleLensLike ((,) a) s a -> a -> m aSource
Subtract from the target of a numerically valued Lens
into your monad's
state and return the result.
When you do not need the result of the subtraction, (-=
) is more
flexible.
(<-=
) :: (MonadState
s m,Num
a) =>Simple
Lens
s a -> a -> m a (<-=
) :: (MonadState
s m,Num
a) =>Simple
Iso
s a -> a -> m a
(<*=) :: (MonadState s m, Num a) => SimpleLensLike ((,) a) s a -> a -> m aSource
Multiply the target of a numerically valued Lens
into your monad's
state and return the result.
When you do not need the result of the multiplication, (*=
) is more
flexible.
(<*=
) :: (MonadState
s m,Num
a) =>Simple
Lens
s a -> a -> m a (<*=
) :: (MonadState
s m,Num
a) =>Simple
Iso
s a -> a -> m a
(<//=) :: (MonadState s m, Fractional a) => SimpleLensLike ((,) a) s a -> a -> m aSource
Divide the target of a fractionally valued Lens
into your monad's state
and return the result.
When you do not need the result of the division, (//=
) is more flexible.
(<//=
) :: (MonadState
s m,Fractional
a) =>Simple
Lens
s a -> a -> m a (<//=
) :: (MonadState
s m,Fractional
a) =>Simple
Iso
s a -> a -> m a
(<^=) :: (MonadState s m, Num a, Integral e) => SimpleLensLike ((,) a) s a -> e -> m aSource
Raise the target of a numerically valued Lens
into your monad's state
to a non-negative Integral
power and return the result.
When you do not need the result of the operation, (**=
) is more flexible.
(<^=
) :: (MonadState
s m,Num
a,Integral
e) =>Simple
Lens
s a -> e -> m a (<^=
) :: (MonadState
s m,Num
a,Integral
e) =>Simple
Iso
s a -> e -> m a
(<^^=) :: (MonadState s m, Fractional a, Integral e) => SimpleLensLike ((,) a) s a -> e -> m aSource
Raise the target of a fractionally valued Lens
into your monad's state
to an Integral
power and return the result.
When you do not need the result of the operation, (^^=
) is more flexible.
(<^^=
) :: (MonadState
s m,Fractional
b,Integral
e) =>Simple
Lens
s a -> e -> m a (<^^=
) :: (MonadState
s m,Fractional
b,Integral
e) =>Simple
Iso
s a -> e -> m a
(<**=) :: (MonadState s m, Floating a) => SimpleLensLike ((,) a) s a -> a -> m aSource
Raise the target of a floating-point valued Lens
into your monad's
state to an arbitrary power and return the result.
When you do not need the result of the operation, (**=
) is more flexible.
(<**=
) :: (MonadState
s m,Floating
a) =>Simple
Lens
s a -> a -> m a (<**=
) :: (MonadState
s m,Floating
a) =>Simple
Iso
s a -> a -> m a
(<||=) :: MonadState s m => SimpleLensLike ((,) Bool) s Bool -> Bool -> m BoolSource
(<&&=) :: MonadState s m => SimpleLensLike ((,) Bool) s Bool -> Bool -> m BoolSource
(<<>=) :: (MonadState s m, Monoid r) => SimpleLensLike ((,) r) s r -> r -> m rSource
(<<%=) :: MonadState s m => LensLike ((,) a) s s a b -> (a -> b) -> m aSource
Modify the target of a Lens
into your monad's state by a user supplied
function and return the old value that was replaced.
When applied to a Traversal
, it this will return a monoidal summary of all of the old values
present.
When you do not need the result of the operation, (%=
) is more flexible.
(<<%=
) ::MonadState
s m =>Simple
Lens
s a -> (a -> a) -> m a (<<%=
) ::MonadState
s m =>Simple
Iso
s a -> (a -> a) -> m a (<<%=
) :: (MonadState
s m,Monoid
b) =>Simple
Traversal
s a -> (a -> a) -> m a
(<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m aSource
Modify the target of a Lens
into your monad's state by a user supplied
function and return the old value that was replaced.
When applied to a Traversal
, it this will return a monoidal summary of all of the old values
present.
When you do not need the result of the operation, (%=
) is more flexible.
(<<%=
) ::MonadState
s m =>Simple
Lens
s a -> (a -> a) -> m a (<<%=
) ::MonadState
s m =>Simple
Iso
s a -> (a -> a) -> m a (<<%=
) :: (MonadState
s m,Monoid
t) =>Simple
Traversal
s a -> (a -> a) -> m a
(<<~) :: MonadState s m => LensLike (Context a b) s s a b -> m b -> m bSource
Run a monadic action, and set the target of Lens
to its result.
(<<~
) ::MonadState
s m =>Iso
s s a b -> m b -> m b (<<~
) ::MonadState
s m =>Lens
s s a b -> m b -> m b
NB: This is limited to taking an actual Lens
than admitting a Traversal
because
there are potential loss of state issues otherwise.
Cloning Lenses
cloneLens :: Functor f => LensLike (Context a b) s t a b -> (a -> f b) -> s -> f tSource
Cloning a Lens
is one way to make sure you aren't given
something weaker, such as a Traversal
and can be
used as a way to pass around lenses that have to be monomorphic in f
.
Note: This only accepts a proper Lens
.
>>>
let example l x = set (cloneLens l) (x^.cloneLens l + 1) x in example _2 ("hello",1,"you")
("hello",2,"you")
newtype ReifiedLens s t a b Source
Useful for storing lenses in containers.
ReifyLens | |
|
Context
The indexed store can be used to characterize a Lens
and is used by clone
is isomorphic to
Context
a b tnewtype Context a b t = Context { runContext :: forall f. Functor f => (a -> f b) -> f t }
,
and to exists s. (s,
.
Lens
s t a b)
A Context
is like a Lens
that has already been applied to a some structure.
Context (b -> t) a |
locus :: ComonadStore s w => Simple Lens (w a) sSource
Simplified and In-Progress
type LensLike f s t a b = (a -> f b) -> s -> f tSource
Many combinators that accept a Lens
can also accept a
Traversal
in limited situations.
They do so by specializing the type of Functor
that they require of the
caller.
If a function accepts a
for some LensLike
f s t a bFunctor
f
,
then they may be passed a Lens
.
Further, if f
is an Applicative
, they may also be passed a
Traversal
.
type Overloaded k f s t a b = k (a -> f b) (s -> f t)Source
typeLensLike
f s t a b =Overloaded
(->) f s t a b
type SimpleLens s a = Lens s s a aSource
typeSimpleLens
=Simple
Lens
type SimpleLensLike f s a = LensLike f s s a aSource
typeSimpleLensLike
f =Simple
(LensLike
f)
type SimpleOverloaded k f s a = Overloaded k f s s a aSource
typeSimpleOverloaded
k f s a =Simple
(Overloaded
k f) s a
type SimpleReifiedLens s a = ReifiedLens s s a aSource
typeSimpleReifiedLens
=Simple
ReifiedLens