| Portability | Rank2Types |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | None |
Control.Lens.Type
Contents
Description
A is a purely functional reference.
Lens a b c d
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.
typeLensa b c d = forall f.Functorf => (c -> f d) -> a -> f b
Every Lens is a valid Setter, choosing f =
Mutator.
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.
- type Lens a b c d = forall f. Functor f => (c -> f d) -> a -> f b
- type Simple f a b = f a a b b
- lens :: (a -> c) -> (a -> d -> b) -> Lens a b c d
- (%%~) :: LensLike f a b c d -> (c -> f d) -> a -> f b
- (%%=) :: MonadState a m => LensLike ((,) e) a a c d -> (c -> (e, d)) -> m e
- resultAt :: Eq e => e -> Simple Lens (e -> a) a
- merged :: Functor f => LensLike f a b c c -> LensLike f a' b' c c -> LensLike f (Either a a') (Either b b') c c
- alongside :: Lens a b c d -> Lens a' b' c' d' -> Lens (a, a') (b, b') (c, c') (d, d')
- (<%~) :: LensLike ((,) d) a b c d -> (c -> d) -> a -> (d, b)
- (<+~) :: Num c => LensLike ((,) c) a b c c -> c -> a -> (c, b)
- (<-~) :: Num c => LensLike ((,) c) a b c c -> c -> a -> (c, b)
- (<*~) :: Num c => LensLike ((,) c) a b c c -> c -> a -> (c, b)
- (<//~) :: Fractional c => LensLike ((,) c) a b c c -> c -> a -> (c, b)
- (<^~) :: (Num c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b)
- (<^^~) :: (Fractional c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b)
- (<**~) :: Floating c => LensLike ((,) c) a b c c -> c -> a -> (c, b)
- (<||~) :: LensLike ((,) Bool) a b Bool Bool -> Bool -> a -> (Bool, b)
- (<&&~) :: LensLike ((,) Bool) a b Bool Bool -> Bool -> a -> (Bool, b)
- (<%=) :: MonadState a m => LensLike ((,) d) a a c d -> (c -> d) -> m d
- (<+=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m b
- (<-=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m b
- (<*=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m b
- (<//=) :: (MonadState a m, Fractional b) => SimpleLensLike ((,) b) a b -> b -> m b
- (<^=) :: (MonadState a m, Num b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m b
- (<^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m b
- (<**=) :: (MonadState a m, Floating b) => SimpleLensLike ((,) b) a b -> b -> m b
- (<||=) :: MonadState a m => SimpleLensLike ((,) Bool) a Bool -> Bool -> m Bool
- (<&&=) :: MonadState a m => SimpleLensLike ((,) Bool) a Bool -> Bool -> m Bool
- cloneLens :: Functor f => LensLike (Context c d) a b c d -> (c -> f d) -> a -> f b
- newtype ReifiedLens a b c d = ReifyLens {
- reflectLens :: Lens a b c d
- type LensLike f a b c d = (c -> f d) -> a -> f b
- type Overloaded k f a b c d = k (c -> f d) (a -> f b)
- type SimpleLens a b = Lens a a b b
- type SimpleLensLike f a b = LensLike f a a b b
- type SimpleOverloaded k f a b = Overloaded k f a a b b
- type SimpleReifiedLens a b = ReifiedLens a a b b
Lenses
type Lens a b c d = forall f. Functor f => (c -> f d) -> a -> f bSource
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 Lensis subject to the
three common sense lens laws:
1) You get back what you put in:
viewl (setl b a) ≡ b
2) Putting back what you got doesn't change anything:
setl (viewl a) a ≡ a
3) Setting twice is the same as setting once:
setl c (setl b a) ≡setl 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≡purefmap(l f).l g ≡getCompose.l (Compose.fmapf.g)
typeLensa b c d = forall f.Functorf =>LensLikef a b c d
type Simple f a b = f a a b bSource
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::SimpleLens(Complexa) atraverseHead::SimpleTraversal[a] a
Note: To use this alias in your own code with or
LensLike fSetter, you may have to turn on LiberalTypeSynonyms.
(%%~) :: LensLike f a b c d -> (c -> f d) -> a -> f bSource
(%%~) 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
(%%~) ::Functorf =>Isoa b c d -> (c -> f d) -> a -> f b (%%~) ::Functorf =>Lensa b c d -> (c -> f d) -> a -> f b (%%~) ::Applicativef =>Traversala b c d -> (c -> f d) -> a -> f b
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)
(%%~) ::Isoa b c d -> (c -> (e, d)) -> a -> (e, b) (%%~) ::Lensa b c d -> (c -> (e, d)) -> a -> (e, b) (%%~) ::Monoidm =>Traversala b c d -> (c -> (m, d)) -> a -> (m, b)
(%%=) :: MonadState a m => LensLike ((,) e) a a c d -> (c -> (e, d)) -> m eSource
Modify the target of a Lens in the current state returning some extra
information of c or modify all targets of a
Traversal in the current state, extracting extra
information of type c and return a monoidal summary of the changes.
(%%=) ≡ (state.)
It may be useful to think of (%%=), instead, as having either of the
following more restricted type signatures:
(%%=) ::MonadStatea m =>Isoa a c d -> (c -> (e, d) -> m e (%%=) ::MonadStatea m =>Lensa a c d -> (c -> (e, d) -> m e (%%=) :: (MonadStatea m,Monoide) =>Traversala a c d -> (c -> (e, d) -> m e
resultAt :: Eq e => e -> Simple Lens (e -> a) aSource
This lens can be used to change the result of a function but only where the arguments match the key given.
Lateral Composition
merged :: Functor f => LensLike f a b c c -> LensLike f a' b' c c -> LensLike f (Either a a') (Either b b') c cSource
Merge two lenses, getters, setters, folds or traversals.
Setting Functionally with Passthrough
(<//~) :: Fractional c => LensLike ((,) c) a b c c -> c -> a -> (c, b)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.
(<//~) ::Fractionalb =>SimpleLensa b -> b -> a -> (b, a) (<//~) ::Fractionalb =>SimpleIsoa b -> b -> a -> (b, a)
(<^~) :: (Num c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b)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.
(<^~) :: (Numb,Integralc) =>SimpleLensa b -> c -> a -> (b, a) (<^~) :: (Numb,Integralc) =>SimpleIsoa b -> c -> a -> (b, a)
(<^^~) :: (Fractional c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b)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.
(<^^~) :: (Fractionalb,Integralc) =>SimpleLensa b -> c -> a -> (b, a) (<^^~) :: (Fractionalb,Integralc) =>SimpleIsoa b -> c -> a -> (b, a)
Setting State with Passthrough
(<%=) :: MonadState a m => LensLike ((,) d) a a c d -> (c -> d) -> m dSource
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.
(<%=) ::MonadStatea m =>SimpleLensa b -> (b -> b) -> m b (<%=) ::MonadStatea m =>SimpleIsoa b -> (b -> b) -> m b (<%=) :: (MonadStatea m,Monoidb) =>SimpleTraverala b -> (b -> b) -> m b
(<+=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m bSource
(<-=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m bSource
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 multiplication, (-=) is more
flexible.
(<-=) :: (MonadStatea m,Numb) =>SimpleLensa b -> b -> m b (<-=) :: (MonadStatea m,Numb) =>SimpleIsoa b -> b -> m b
(<*=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m bSource
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.
(<*=) :: (MonadStatea m,Numb) =>SimpleLensa b -> b -> m b (<*=) :: (MonadStatea m,Numb) =>SimpleIsoa b -> b -> m b
(<//=) :: (MonadState a m, Fractional b) => SimpleLensLike ((,) b) a b -> b -> m bSource
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.
(<//=) :: (MonadStatea m,Fractionalb) =>SimpleLensa b -> b -> m b (<//=) :: (MonadStatea m,Fractionalb) =>SimpleIsoa b -> b -> m b
(<^=) :: (MonadState a m, Num b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m bSource
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.
(<^=) :: (MonadStatea m,Numb,Integralc) =>SimpleLensa b -> c -> m b (<^=) :: (MonadStatea m,Numb,Integralc) =>SimpleIsoa b -> c -> m b
(<^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m bSource
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.
(<^^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleLensa b -> c -> m b (<^^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleIsoa b -> c -> m b
(<**=) :: (MonadState a m, Floating b) => SimpleLensLike ((,) b) a b -> b -> m bSource
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.
(<**=) :: (MonadStatea m,Floatingb) =>SimpleLensa b -> b -> m b (<**=) :: (MonadStatea m,Floatingb) =>SimpleIsoa b -> b -> m b
(<||=) :: MonadState a m => SimpleLensLike ((,) Bool) a Bool -> Bool -> m BoolSource
(<&&=) :: MonadState a m => SimpleLensLike ((,) Bool) a Bool -> Bool -> m BoolSource
Cloning Lenses
cloneLens :: Functor f => LensLike (Context c d) a b c d -> (c -> f d) -> a -> f bSource
Cloning a Lens is one way to make sure you arent 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.
\"Costate Comonad Coalgebra is equivalent of Java's member variable update technology for Haskell\" -- @PLT_Borat on Twitter
newtype ReifiedLens a b c d Source
Useful for storing lenses in containers.
Constructors
| ReifyLens | |
Fields
| |
Simplified and In-Progress
type LensLike f a b c d = (c -> f d) -> a -> f bSource
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 a b c dFunctor 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 a b c d = k (c -> f d) (a -> f b)Source
typeLensLikef a b c d =Overloaded(->) f a b c d
type SimpleLens a b = Lens a a b bSource
typeSimpleLens=SimpleLens
type SimpleLensLike f a b = LensLike f a a b bSource
typeSimpleLensLikef =Simple(LensLikef)
type SimpleOverloaded k f a b = Overloaded k f a a b bSource
typeSimpleOverloadedk f a b =Simple(Overloadedk f) a b
type SimpleReifiedLens a b = ReifiedLens a a b bSource
typeSimpleReifiedLens=SimpleReifiedLens