| Safe Haskell | Safe-Inferred |
|---|
Lens.Family.Clone
Contents
Description
This module is provided for Haskell 98 compatibility.
If you are able to use Rank2Types, I advise you to instead use the rank 2 aliases
-
Lens,Lens' -
Traversal,Traversal' -
Setter,Setter' -
Fold,Fold' -
Getter,Getter'
from the lens-family package instead.
cloneLens allows one to circumvent the need for rank 2 types by allowing one to take a universal monomorphic lens instance and rederive a polymorphic instance.
When you require a lens family parameter you use the type (or ALens a a' b b').
Then, inside a ALens' a bwhere clause, you use cloneLens to create a Lens type.
For example.
example :: ALens a a' b b' -> Example example l = ... x^.cl ... cl .~ y ... where cl x = cloneLens l x
Note: It is important to eta-expand the definition of cl to avoid the dreaded monomorphism restriction.
cloneTraversal, cloneGetter, cloneSetter, and cloneFold provides similar functionality for traversals, getters, setters, and folds respectively.
Note: Cloning is only need if you use a functional reference multiple times with different instances.
- cloneLens :: Functor f => ALens a a' b b' -> LensLike f a a' b b'
- cloneTraversal :: Applicative f => ATraversal a a' b b' -> LensLike f a a' b b'
- cloneSetter :: Identical f => ASetter a a' b b' -> LensLike f a a' b b'
- cloneGetter :: Phantom f => AGetter a a' b b' -> LensLike f a a' b b'
- cloneFold :: (Phantom f, Applicative f) => AFold a a' b b' -> LensLike f a a' b b'
- type ALens a a' b b' = LensLike (IStore b b') a a' b b'
- type ALens' a b = LensLike' (IStore b b) a b
- type ATraversal a a' b b' = LensLike (IKleeneStore b b') a a' b b'
- type ATraversal' a b = LensLike' (IKleeneStore b b) a b
- type AGetter a a' b b' = FoldLike b a a' b b'
- type AGetter' a b = FoldLike' b a b
- type AFold a a' b b' = FoldLike [b] a a' b b'
- type AFold' a b = FoldLike' [b] a b
- data IStore b b' a
- data IKleeneStore b b' a
- 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
- type ASetter a a' b b' = LensLike Identity a a' b b'
- class Functor f => Applicative f
- class Functor f => Phantom f
- class Applicative f => Identical f
Documentation
cloneLens :: Functor f => ALens a a' b b' -> LensLike f a a' b b'Source
Converts a universal lens instance back into a polymorphic lens.
cloneTraversal :: Applicative f => ATraversal a a' b b' -> LensLike f a a' b b'Source
Converts a universal traversal instance back into a polymorphic traversal.
cloneSetter :: Identical f => ASetter a a' b b' -> LensLike f a a' b b'Source
Converts a universal setter instance back into a polymorphic setter.
cloneGetter :: Phantom f => AGetter a a' b b' -> LensLike f a a' b b'Source
Converts a universal getter instance back into a polymorphic getter.
cloneFold :: (Phantom f, Applicative f) => AFold a a' b b' -> LensLike f a a' b b'Source
Converts a universal fold instance back into a polymorphic fold.
Types
type ALens a a' b b' = LensLike (IStore b b') a a' b b'Source
ALens a a' b b' is a universal Lens a a' b b' instance
type ATraversal a a' b b' = LensLike (IKleeneStore b b') a a' b b'Source
ATraversal a a' b b' is a universal Traversal a a' b b' instance
type ATraversal' a b = LensLike' (IKleeneStore b b) a bSource
ATraversal' a b is a universal Traversal' a b instance
type AGetter a a' b b' = FoldLike b a a' b b'Source
AGetter a a' b b' is a universal Fold a a' b b' instance
type AFold a a' b b' = FoldLike [b] a a' b b'Source
AFold a a' b b' is a universal Fold' a a' b b' instance
data IKleeneStore b b' a Source
Instances
| Functor (IKleeneStore b b') | |
| Applicative (IKleeneStore b b') |
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
-
pureid<*>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:
u *> v = pure (const id) <*> u <*> v
u <* v = pure const <*> u <*> v
As a consequence of these laws, the Functor instance for f will satisfy
fmap f x = pure f <*> x
If f is also a Monad, it should satisfy and
pure = return( (which implies that <*>) = appure and <*> satisfy the
applicative functor laws).
Instances
| Applicative [] | |
| Applicative IO | |
| Applicative ZipList | |
| Applicative STM | |
| Applicative ReadPrec | |
| Applicative ReadP | |
| Applicative Maybe | |
| Applicative Identity | |
| Applicative ((->) a) | |
| Applicative (Either e) | |
| Monoid a => Applicative ((,) a) | |
| Applicative (ST s) | |
| Monoid m => Applicative (Const m) | |
| Monad m => Applicative (WrappedMonad m) | |
| Applicative (ST s) | |
| Arrow a => Applicative (ArrowMonad a) | |
| Applicative f => Applicative (Backwards f) | Apply |
| Monoid a => Applicative (Constant a) | |
| Arrow a => Applicative (WrappedArrow a b) | |
| (Monoid w, Applicative m) => Applicative (WriterT w m) | |
| (Functor m, Monad m) => Applicative (StateT s m) | |
| (Functor m, Monad m) => Applicative (StateT s m) | |
| (Applicative f, Applicative g) => Applicative (Compose f g) | |
| (Monoid c, Monad m) => Applicative (Zooming m c) | |
| Applicative (IKleeneStore b b') |