| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Lens.Family2.Stock
Description
This module contains lenses and traversals for common structures in Haskell. It also contains the combinators for lenses and traversals.
- choosing :: Functor f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (Either a b) (Either a' b') c c'
- alongside :: Functor f => LensLike (AlongsideLeft f b2') a1 a1' b1 b1' -> LensLike (AlongsideRight f a1') a2 a2' b2 b2' -> LensLike f (a1, a2) (a1', a2') (b1, b2) (b1', b2')
- beside :: Applicative f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (a, b) (a', b') c c'
- _1 :: Lens (a, b) (a', b) a a'
- _2 :: Lens (a, b) (a, b') b b'
- chosen :: Lens (Either a a) (Either b b) a b
- ix :: Eq k => k -> Lens' (k -> v) v
- at :: Ord k => k -> Lens' (Map k v) (Maybe v)
- intAt :: Int -> Lens' (IntMap v) (Maybe v)
- at' :: Ord k => k -> Lens' (Map k v) (Maybe v)
- intAt' :: Int -> Lens' (IntMap v) (Maybe v)
- contains :: Ord k => k -> Lens' (Set k) Bool
- intContains :: Int -> Lens' IntSet Bool
- both :: Traversal (a, a) (b, b) a b
- _Left :: Traversal (Either a b) (Either a' b) a a'
- _Right :: Traversal (Either a b) (Either a b') b b'
- _Just :: Traversal (Maybe a) (Maybe a') a a'
- _Nothing :: Traversal' (Maybe a) ()
- ignored :: Traversal a a b b'
- mapped :: Functor f => Setter (f a) (f a') a a'
- data AlongsideLeft f b a :: (* -> *) -> * -> * -> *
- data AlongsideRight f a b :: (* -> *) -> * -> * -> *
- 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 LensLike f a a' b b' = (b -> f b') -> a -> f a'
- type LensLike' f a b = (b -> f b) -> a -> f a
- class Functor f => Applicative f
- class Applicative f => Identical f
Lens Combinators
choosing :: Functor f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (Either a b) (Either a' b') c c' #
choosing :: Lens a a' c c' -> Lens b b' c c' -> Lens (Either a b) (Either a' b') c c'
choosing :: Traversal a a' c c' -> Traversal b b' c c' -> Traversal (Either a b) (Either a' b') c c'
choosing :: Getter a a' c c' -> Getter b b' c c' -> Getter (Either a b) (Either a' b') c c'
choosing :: Fold a a' c c' -> Fold b b' c c' -> Fold (Either a b) (Either a' b') c c'
choosing :: Setter a a' c c' -> Setter b b' c c' -> Setter (Either a b) (Either a' b') c c'
Given two lens/traversal/getter/fold/setter families with the same substructure, make a new lens/traversal/getter/fold/setter on Either.
alongside :: Functor f => LensLike (AlongsideLeft f b2') a1 a1' b1 b1' -> LensLike (AlongsideRight f a1') a2 a2' b2 b2' -> LensLike f (a1, a2) (a1', a2') (b1, b2) (b1', b2') #
alongside :: Lens a1 a1' b1 b1' -> Lens a2 a2' b2 b2' -> Lens (a1, a2) (a1', a2') (b1, b2) (b1', b2')
alongside :: Getter a1 a1' b1 b1' -> Getter a2 a2' b2 b2' -> Getter (a1, a2) (a1', a2') (b1, b2) (b1', b2')
Given two lens/getter families, make a new lens/getter on their product.
beside :: Applicative f => LensLike f a a' c c' -> LensLike f b b' c c' -> LensLike f (a, b) (a', b') c c' #
beside :: Traversal a a' c c' -> Traversal b' b' c c' -> Traversal (a,b) (a',b') c c'
beside :: Fold a a' c c' -> Fold b' b' c c' -> Fold (a,b) (a',b') c c'
beside :: Setter a a' c c' -> Setter b' b' c c' -> Setter (a,b) (a',b') c c'
Given two traversals/folds/setters referencing a type c, create a traversal/fold/setter on the pair referencing c.
Stock Lenses
chosen :: Lens (Either a a) (Either b b) a b Source #
Lens on the Left or Right element of an (Either a a).
at' :: Ord k => k -> Lens' (Map k v) (Maybe v) Source #
Lens providing strict access to a given point of a Map.
intAt' :: Int -> Lens' (IntMap v) (Maybe v) Source #
Lens providing strict access to a given point of a IntMap.
Stock Traversals
Stock SECs
mapped :: Functor f => Setter (f a) (f a') a a' Source #
An SEC referencing the parameter of a functor.
Types
data AlongsideLeft f b a :: (* -> *) -> * -> * -> * #
Instances
| Functor f => Functor (AlongsideLeft f a) | |
| Phantom f => Phantom (AlongsideLeft f a) | |
data AlongsideRight f a b :: (* -> *) -> * -> * -> * #
Instances
| Functor f => Functor (AlongsideRight f a) | |
| Phantom f => Phantom (AlongsideRight f a) | |
Re-exports
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 #
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
- puref- <*>- purex =- pure(f x)
- interchange
- u - <*>- purey =- 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).
Instances