| Portability | Rank2Types |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | Safe-Infered |
Control.Lens.Internal
Contents
Description
These are some of the explicit Functor instances that leak into the type signatures of Control.Lens. You shouldn't need to import this module directly, unless you are coming up with a whole new kind of "Family" and need to add instances.
- data IndexedStore c d a = IndexedStore (d -> a) c
- newtype Focusing m c a = Focusing {
- unfocusing :: m (c, a)
- newtype FocusingWith w m c a = FocusingWith {
- unfocusingWith :: m (c, a, w)
- newtype FocusingPlus w k c a = FocusingPlus {
- unfocusingPlus :: k (c, w) a
- newtype FocusingOn f k c a = FocusingOn {
- unfocusingOn :: k (f c) a
- newtype FocusingErr e k c a = FocusingErr {
- unfocusingErr :: k (Err e c) a
- newtype Err e a = Err {}
- newtype FocusingMay k c a = FocusingMay {
- unfocusingMay :: k (May c) a
- newtype May a = May {}
- newtype Traversed f = Traversed {
- getTraversed :: f ()
- newtype Sequenced m = Sequenced {
- getSequenced :: m ()
- newtype AppliedState f a = AppliedState {
- runAppliedState :: Int -> (f a, Int)
- data Min a
- getMin :: Min a -> Maybe a
- data Max a
- getMax :: Max a -> Maybe a
- newtype ElementOf f a = ElementOf {
- getElementOf :: Int -> ElementOfResult f a
- data ElementOfResult f a
- data Kleene c d a
- kleene :: Applicative f => (c -> f d) -> Kleene c d b -> f b
- newtype Effect m r a = Effect {
- getEffect :: m r
- newtype EffectRWS w s m c a = EffectRWS {
- getEffectRWS :: s -> m (c, s, w)
- class Functor f => Gettable f where
- coerce :: f a -> f b
- newtype Accessor r a = Accessor {
- runAccessor :: r
- class (Monad m, Gettable f) => Effective m r f | f -> m r where
- effective :: Isomorphic k => k (m r) (f a)
- ineffective :: Effective m r f => Isomorphic k => k (f a) (m r)
- class Applicative f => Settable f where
- untainted :: f a -> a
- newtype Mutator a = Mutator {
- runMutator :: a
Implementation details
data IndexedStore c d a Source
Constructors
| IndexedStore (d -> a) c |
Instances
| Functor (IndexedStore c d) |
Constructors
| Focusing | |
Fields
| |
newtype FocusingWith w m c a Source
Constructors
| FocusingWith | |
Fields
| |
Instances
| Monad m => Functor (FocusingWith w m c) | |
| (Monad m, Monoid c, Monoid w) => Applicative (FocusingWith w m c) | |
| (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) (FocusingWith w z) s t | |
| (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) (FocusingWith w z) s t |
newtype FocusingPlus w k c a Source
Constructors
| FocusingPlus | |
Fields
| |
Instances
| (Monoid w, Zoom m n k s t) => Zoom (WriterT w m) (WriterT w n) (FocusingPlus w k) s t | |
| (Monoid w, Zoom m n k s t) => Zoom (WriterT w m) (WriterT w n) (FocusingPlus w k) s t | |
| Functor (k (c, w)) => Functor (FocusingPlus w k c) | |
| (Monoid w, Applicative (k (c, w))) => Applicative (FocusingPlus w k c) |
newtype FocusingOn f k c a Source
Constructors
| FocusingOn | |
Fields
| |
Instances
| Zoom m n k s t => Zoom (ListT m) (ListT n) (FocusingOn [] k) s t | |
| Functor (k (f c)) => Functor (FocusingOn f k c) | |
| Applicative (k (f c)) => Applicative (FocusingOn f k c) |
newtype FocusingErr e k c a Source
Constructors
| FocusingErr | |
Fields
| |
Instances
| (Error e, Zoom m n k s t) => Zoom (ErrorT e m) (ErrorT e n) (FocusingErr e k) s t | |
| Functor (k (Err e c)) => Functor (FocusingErr e k c) | |
| Applicative (k (Err e c)) => Applicative (FocusingErr e k c) |
Make a monoid out of Either for error handling
newtype FocusingMay k c a Source
Constructors
| FocusingMay | |
Fields
| |
Instances
| Zoom m n k s t => Zoom (MaybeT m) (MaybeT n) (FocusingMay k) s t | |
| Functor (k (May c)) => Functor (FocusingMay k c) | |
| Applicative (k (May c)) => Applicative (FocusingMay k c) |
Make a monoid out of Maybe for error handling
Used internally by traverseOf_ and the like.
Constructors
| Traversed | |
Fields
| |
Instances
| Applicative f => Monoid (Traversed f) |
Used internally by mapM_ and the like.
Constructors
| Sequenced | |
Fields
| |
newtype AppliedState f a Source
Applicative composition of with a State IntFunctor, used
by elementOf, elementsOf, traverseElement, traverseElementsOf
Constructors
| AppliedState | |
Fields
| |
Instances
| Functor f => Functor (AppliedState f) | |
| Applicative f => Applicative (AppliedState f) |
Constructors
| ElementOf | |
Fields
| |
data ElementOfResult f a Source
Instances
| Functor f => Functor (ElementOfResult f) |
The Indexed Kleene Store comonad, aka the 'indexed cartesian store comonad' or an indexed FunList.
This is used to characterize a Traversal.
Instances
| Functor (Kleene c d) | |
| Applicative (Kleene c d) |
kleene :: Applicative f => (c -> f d) -> Kleene c d b -> f bSource
Given an action to run for each matched pair, traverse a store.
Wrap a monadic effect with a phantom type argument.
newtype EffectRWS w s m c a Source
Wrap a monadic effect with a phantom type argument. Used when magnifying RWST.
Constructors
| EffectRWS | |
Fields
| |
Used instead of Const to report
No instance of (SettableAccessor)
when the user attempts to misuse a Setter as a
Getter, rather than a monolithic unification error.
Constructors
| Accessor | |
Fields
| |
class (Monad m, Gettable f) => Effective m r f | f -> m r whereSource
An Effective Functor ignores its argument and is isomorphic to a monad wrapped around a value.
That said, the monad is possibly rather unrelated to any Applicative structure.
Methods
effective :: Isomorphic k => k (m r) (f a)Source
ineffective :: Effective m r f => Isomorphic k => k (f a) (m r)Source
A convenient antonym that is used internally.
class Applicative f => Settable f whereSource
Mutator is just a renamed Identity functor to give better error
messages when someone attempts to use a getter as a setter.
Most user code will never need to see this type.
Constructors
| Mutator | |
Fields
| |