Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This is the main module for end-users of lens-families. If you are not building your own lenses or traversals, but just using functional references made by others, this is the only module you need.
- to :: (a -> b) -> Getter a a' b b'
- view :: FoldLike b a a' b b' -> a -> b
- (^.) :: a -> FoldLike b a a' b b' -> b
- folding :: Foldable f => (a -> f b) -> Fold a a' b b'
- views :: FoldLike r a a' b b' -> (b -> r) -> a -> r
- (^..) :: a -> Fold a a' b b' -> [b]
- (^?) :: a -> Fold a a' b b' -> Maybe b
- toListOf :: Fold a a' b b' -> a -> [b]
- allOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool
- anyOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool
- firstOf :: Fold a a' b b' -> a -> Maybe b
- lastOf :: Fold a a' b b' -> a -> Maybe b
- sumOf :: Num b => Fold a a' b b' -> a -> b
- productOf :: Num b => Fold a a' b b' -> a -> b
- lengthOf :: Num r => Fold a a' b b' -> a -> r
- nullOf :: Fold a a' b b' -> a -> Bool
- backwards :: LensLike (Backwards * f) a a' b b' -> LensLike f a a' b b'
- over :: Setter a a' b b' -> (b -> b') -> a -> a'
- (%~) :: Setter a a' b b' -> (b -> b') -> a -> a'
- set :: Setter a a' b b' -> b' -> a -> a'
- (.~) :: Setter a a' b b' -> b' -> a -> a'
- (&) :: a -> (a -> b) -> b
- (+~) :: Num b => Setter' a b -> b -> a -> a
- (*~) :: Num b => Setter' a b -> b -> a -> a
- (-~) :: Num b => Setter' a b -> b -> a -> a
- (//~) :: Fractional b => Setter' a b -> b -> a -> a
- (&&~) :: Setter' a Bool -> Bool -> a -> a
- (||~) :: Setter' a Bool -> Bool -> a -> a
- (<>~) :: Monoid o => Setter' a o -> o -> a -> a
- type Lens a a' b b' = forall f. Functor f => LensLike f a a' b b'
- type Lens' a b = forall f. Functor f => LensLike' f a b
- type Traversal a a' b b' = forall f. Applicative f => LensLike f a a' b b'
- type Traversal' a b = forall f. Applicative f => LensLike' f a b
- type Setter a a' b b' = forall f. Identical f => LensLike f a a' b b'
- type Setter' a b = forall f. Identical f => LensLike' f a b
- type Getter a a' b b' = forall f. Phantom f => LensLike f a a' b b'
- type Getter' a b = forall f. Phantom f => LensLike' f a b
- type Fold a a' b b' = forall f. (Phantom f, Applicative f) => LensLike f a a' b b'
- type Fold' a b = forall f. (Phantom f, Applicative f) => LensLike' f a b
- type LensLike f a a' b b' = (b -> f b') -> a -> f a'
- type LensLike' f a b = (b -> f b) -> a -> f a
- type FoldLike r a a' b b' = LensLike (Constant * r) a a' b b'
- type FoldLike' r a b = LensLike' (Constant * r) a b
- data Constant k a b :: forall k. * -> k -> *
- class Functor f => Phantom f
- class Applicative f => Identical f
- class Functor f => Applicative f
- class Foldable t
- class Monoid a
- data Backwards k f a :: forall k. (k -> *) -> k -> *
Lenses
This module provides ^.
for accessing fields and .~
and %~
for setting and modifying fields.
Lenses are composed with .
from the Prelude
and id
is the identity lens.
Lens composition in this library enjoys the following identities.
x^.l1.l2 === x^.l1^.l2
l1.l2 %~ f === l1 %~ l2 %~ f
The identity lens behaves as follows.
x^.id === x
id %~ f === f
The &
operator, allows for a convenient way to sequence record updating:
record & l1 .~ value1 & l2 .~ value2
Lenses are implemented in van Laarhoven style.
Lenses have type
and lens families have type Functor
f => (b -> f b) -> a -> f a
.Functor
f => (b i -> f (b j)) -> a i -> f (a j)
Keep in mind that lenses and lens families can be used directly for functorial updates.
For example, _2 id
gives you strength.
_2 id :: Functor f => (a, f b) -> f (a, b)
Here is an example of code that uses the Maybe
functor to preserves sharing during update when possible.
-- | 'sharedUpdate' returns the *identical* object if the update doesn't change anything. -- This is useful for preserving sharing. sharedUpdate :: Eq b => LensLike' Maybe a b -> (b -> b) -> a -> a sharedUpdate l f a = fromMaybe a (l f' a) where f' b | fb == b = Nothing | otherwise = Just fb where fb = f b
Traversals
^.
can be used with traversals to access monoidal fields.
The result will be a mconcat
of all the fields referenced.
The various fooOf
functions can be used to access different monoidal summaries of some kinds of values.
^?
can be used to access the first value of a traversal.
Nothing
is returned when the traversal has no references.
^..
can be used with a traversals and will return a list of all fields referenced.
When .~
is used with a traversal, all referenced fields will be set to the same value, and when %~
is used with a traversal, all referenced fields will be modified with the same function.
Like lenses, traversals can be composed with .
, and because every lens is automatically a traversal, lenses and traversals can be composed with .
yielding a traversal.
Traversals are implemented in van Laarhoven style.
Traversals have type
and traversal families have type Applicative
f => (b -> f b) -> a -> f a
.Applicative
f => (b i -> f (b j)) -> a i -> f (a j)
For stock lenses and traversals, see Lens.Family2.Stock.
To build your own lenses and traversals, see Lens.Family2.Unchecked.
References:
Documentation
to :: (a -> b) -> Getter a a' b b' Source #
to
promotes a projection function to a read-only lens called a getter.
To demote a lens to a projection function, use the section (^.l)
or view l
.
>>>
(3 :+ 4, "example")^._1.to(abs)
5.0 :+ 0.0
view :: FoldLike b a a' b b' -> a -> b #
view :: Getter a a' b b' -> a -> b
Demote a lens or getter to a projection function.
view :: Monoid b => Fold a a' b b' -> a -> b
Returns the monoidal summary of a traversal or a fold.
(^.) :: a -> FoldLike b a a' b b' -> b infixl 8 #
(^.) :: a -> Getter a a' b b' -> b
Access the value referenced by a getter or lens.
(^.) :: Monoid b => a -> Fold a a' b b' -> b
Access the monoidal summary referenced by a getter or lens.
folding :: Foldable f => (a -> f b) -> Fold a a' b b' Source #
folding
promotes a "toList" function to a read-only traversal called a fold.
To demote a traversal or fold to a "toList" function use the section (^..l)
or toListOf l
.
views :: FoldLike r a a' b b' -> (b -> r) -> a -> r #
views :: Monoid r => Fold a a' b b' -> (b -> r) -> a -> r
Given a fold or traversal, return the foldMap
of all the values using the given function.
views :: Getter a a' b b' -> (b -> r) -> a -> r
views
is not particularly useful for getters or lenses, but given a getter or lens, it returns the referenced value passed through the given function.
views l f a = f (view l a)
(^..) :: a -> Fold a a' b b' -> [b] infixl 8 Source #
Returns a list of all of the referenced values in order.
toListOf :: Fold a a' b b' -> a -> [b] Source #
Returns a list of all of the referenced values in order.
allOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool Source #
Returns true if all of the referenced values satisfy the given predicate.
anyOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool Source #
Returns true if any of the referenced values satisfy the given predicate.
productOf :: Num b => Fold a a' b b' -> a -> b Source #
Returns the product of all the referenced values.
lengthOf :: Num r => Fold a a' b b' -> a -> r Source #
Counts the number of references in a traversal or fold for the input.
nullOf :: Fold a a' b b' -> a -> Bool Source #
Returns true if the number of references in the input is zero.
backwards :: LensLike (Backwards * f) a a' b b' -> LensLike f a a' b b' #
backwards :: Traversal a a' b b' -> Traversal a a' b b' backwards :: Fold a a' b b' -> Fold a a' b b'
Given a traversal or fold, reverse the order that elements are traversed.
backwards :: Lens a a' b b' -> Lens a a' b b' backwards :: Getter a a' b b' -> Getter a a' b b' backwards :: Setter a a' b b' -> Setter a a' b b'
No effect on lenses, getters or setters.
over :: Setter a a' b b' -> (b -> b') -> a -> a' Source #
Demote a setter to a semantic editor combinator.
(.~) :: Setter a a' b b' -> b' -> a -> a' infixr 4 Source #
Set all referenced fields to the given value.
Pseudo-imperatives
(//~) :: Fractional b => Setter' a b -> b -> a -> a infixr 4 Source #
(<>~) :: Monoid o => Setter' a o -> o -> a -> a infixr 4 Source #
Monoidally append a value to all referenced fields.
Types
type Traversal a a' b b' = forall f. Applicative f => LensLike f a a' b b' Source #
type Traversal' a b = forall f. Applicative f => LensLike' f a b Source #
data Constant k a b :: forall k. * -> k -> * #
Constant functor.
Eq2 (Constant *) | |
Ord2 (Constant *) | |
Read2 (Constant *) | |
Show2 (Constant *) | |
Bifunctor (Constant *) | |
Functor (Constant * a) | |
Monoid a => Applicative (Constant * a) | |
Foldable (Constant * a) | |
Traversable (Constant * a) | |
Eq a => Eq1 (Constant * a) | |
Ord a => Ord1 (Constant * a) | |
Read a => Read1 (Constant * a) | |
Show a => Show1 (Constant * a) | |
Phantom (Constant * a) | |
Eq a => Eq (Constant k a b) | |
Ord a => Ord (Constant k a b) | |
Read a => Read (Constant k a b) | |
Show a => Show (Constant k a b) | |
Monoid a => Monoid (Constant k a b) | |
class Applicative f => Identical f #
extract
Re-exports
class Functor f => Applicative f #
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying the following laws:
- identity
pure
id
<*>
v = v- composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- homomorphism
pure
f<*>
pure
x =pure
(f x)- interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Data structures that can be folded.
For example, given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Foldable Tree where foldMap f Empty = mempty foldMap f (Leaf x) = f x foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
This is suitable even for abstract types, as the monoid is assumed
to satisfy the monoid laws. Alternatively, one could define foldr
:
instance Foldable Tree where foldr f z Empty = z foldr f z (Leaf x) = f x z foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
Foldable
instances are expected to satisfy the following laws:
foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id
sum
, product
, maximum
, and minimum
should all be essentially
equivalent to foldMap
forms, such as
sum = getSum . foldMap Sum
but may be less defined.
If the type is also a Functor
instance, it should satisfy
foldMap f = fold . fmap f
which implies that
foldMap f . fmap g = foldMap (f . g)
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat =
foldr
mappend mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
Monoid Ordering | |
Monoid () | |
Monoid All | |
Monoid Any | |
Monoid IntSet | |
Monoid [a] | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
Monoid a => Monoid (IO a) | |
Ord a => Monoid (Max a) | |
Ord a => Monoid (Min a) | |
Monoid a => Monoid (Identity a) | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Sum a) | |
Num a => Monoid (Product a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid (IntMap a) | |
Ord a => Monoid (Set a) | |
Monoid b => Monoid (a -> b) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
Monoid (Proxy k s) | |
Ord k => Monoid (Map k v) | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
Monoid a => Monoid (Const k a b) | |
Alternative f => Monoid (Alt * f a) | |
Monoid a => Monoid (Constant k a b) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | |
data Backwards k f a :: forall k. (k -> *) -> k -> * #
The same functor, but with an Applicative
instance that performs
actions in the reverse order.
Functor f => Functor (Backwards * f) | Derived instance. |
Applicative f => Applicative (Backwards * f) | Apply |
Foldable f => Foldable (Backwards * f) | Derived instance. |
Traversable f => Traversable (Backwards * f) | Derived instance. |
Eq1 f => Eq1 (Backwards * f) | |
Ord1 f => Ord1 (Backwards * f) | |
Read1 f => Read1 (Backwards * f) | |
Show1 f => Show1 (Backwards * f) | |
Alternative f => Alternative (Backwards * f) | Try alternatives in the same order as |
Identical f => Identical (Backwards * f) | |
Phantom f => Phantom (Backwards * f) | |
(Eq1 f, Eq a) => Eq (Backwards * f a) | |
(Ord1 f, Ord a) => Ord (Backwards * f a) | |
(Read1 f, Read a) => Read (Backwards * f a) | |
(Show1 f, Show a) => Show (Backwards * f a) | |