| Portability | Rank2Types |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | None |
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 Context c d a = Context (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 Indexing f a = Indexing {
- runIndexing :: Int -> IndexingResult f a
- data IndexingResult f a = IndexingResult (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
- newtype Bazaar c d a = Bazaar {
- _runBazaar :: forall f. Applicative f => (c -> f d) -> f a
- bazaar :: Applicative f => (c -> f d) -> Bazaar c d b -> f b
- duplicateBazaar :: Bazaar c e a -> Bazaar c d (Bazaar d e a)
- sell :: c -> Bazaar c d d
- 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)
- noEffect :: (Applicative f, Gettable f) => f a
- newtype Folding f a = Folding {
- getFolding :: f a
- class Applicative f => Settable f where
- untainted :: f a -> a
- newtype Mutator a = Mutator {
- runMutator :: a
Implementation details
Constructors
| Context (d -> a) c |
Constructors
| Focusing | |
Fields
| |
Instances
| Monad m => Functor (Focusing m c) | |
| (Functor (Focusing m c), Monad m, Monoid c) => Applicative (Focusing m c) | |
| (MonadState s (StateT s z), MonadState t (StateT t z), Monad z) => Zoom (StateT s z) (StateT t z) (Focusing z) s t | |
| (MonadState s (StateT s z), MonadState t (StateT t z), Monad z) => Zoom (StateT s z) (StateT t z) (Focusing z) s t |
newtype FocusingWith w m c a Source
Constructors
| FocusingWith | |
Fields
| |
Instances
| Monad m => Functor (FocusingWith w m c) | |
| (Functor (FocusingWith w m c), Monad m, Monoid c, Monoid w) => Applicative (FocusingWith w m c) | |
| (MonadState s (RWST r w s z), MonadState t (RWST r w t z), Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) (FocusingWith w z) s t | |
| (MonadState s (RWST r w s z), MonadState t (RWST r w t z), 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
| (MonadState s (WriterT w m), MonadState t (WriterT w n), Monoid w, Zoom m n k s t) => Zoom (WriterT w m) (WriterT w n) (FocusingPlus w k) s t | |
| (MonadState s (WriterT w m), MonadState t (WriterT w n), 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) | |
| (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
| (MonadState s (ListT m), MonadState t (ListT n), Zoom m n k s t) => Zoom (ListT m) (ListT n) (FocusingOn [] k) s t | |
| Functor (k (f c)) => Functor (FocusingOn f k 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
| (MonadState s (ErrorT e m), MonadState t (ErrorT e n), 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) | |
| (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
| (MonadState s (MaybeT m), MonadState t (MaybeT n), Zoom m n k s t) => Zoom (MaybeT m) (MaybeT n) (FocusingMay k) s t | |
| Functor (k (May c)) => Functor (FocusingMay k 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
| |
Constructors
| Indexing | |
Fields
| |
data IndexingResult f a Source
The result of Indexing
Constructors
| IndexingResult (f a) !Int |
Instances
| Functor f => Functor (IndexingResult f) |
Constructors
| ElementOf | |
Fields
| |
data ElementOfResult f a Source
Instances
| Functor f => Functor (ElementOfResult f) |
This is used to characterize a Traversal.
a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, or an indexed FunList.
http://twanvl.nl/blog/haskell/non-regular1
Mnemonically, a Bazaar holds many stores and you can easily add more.
This is a final encoding of Bazaar.
Constructors
| Bazaar | |
Fields
| |
bazaar :: Applicative f => (c -> f d) -> Bazaar c d b -> f bSource
Given an action to run for each matched pair, traverse a bazaar.
Wrap a monadic effect with a phantom type argument.
Instances
| (Gettable (Effect m r), Monad m) => Effective m r (Effect m r) | |
| Functor (Effect m r) | |
| (Functor (Effect m r), Monad m, Monoid r) => Applicative (Effect m r) | |
| Functor (Effect m r) => Gettable (Effect m r) | |
| (MonadReader b (ReaderT b m), MonadReader a (ReaderT a m), Monad m) => Magnify (ReaderT b m) (ReaderT a m) (Effect m) b a | |
| (Monad m, Monoid r) => Monoid (Effect m r a) |
newtype EffectRWS w s m c a Source
Wrap a monadic effect with a phantom type argument. Used when magnifying RWST.
Constructors
| EffectRWS | |
Fields
| |
Instances
| Functor (EffectRWS w s m c) | |
| (Functor (EffectRWS w s m c), Monoid c, Monoid w, Monad m) => Applicative (EffectRWS w s m c) | |
| Functor (EffectRWS w s m c) => Gettable (EffectRWS w s m c) | |
| (MonadReader b (RWST b w s m), MonadReader a (RWST a w s m), Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) (EffectRWS w s m) b a | |
| (MonadReader b (RWST b w s m), MonadReader a (RWST a w s m), Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) (EffectRWS w s m) b a |
class Functor f => Gettable f whereSource
Generalizing Const so we can apply simple Applicative
transformations to it and so we can get nicer error messages
A Gettable Functor ignores its argument, which it carries solely as a
phantom type parameter.
To ensure this, an instance of Gettable is required to satisfy:
id=fmapf =coerce
Instances
| Functor (Const r) => Gettable (Const r) | |
| (Functor (Backwards f), Gettable f) => Gettable (Backwards f) | |
| Functor (Accessor r) => Gettable (Accessor r) | |
| (Functor (ElementOf f), Gettable f) => Gettable (ElementOf f) | This instance is a lie, but it is a useful lie. |
| (Functor (Indexing f), Gettable f) => Gettable (Indexing f) | |
| (Functor (Compose f g), Functor f, Gettable g) => Gettable (Compose f g) | |
| Functor (Effect m r) => Gettable (Effect m r) | |
| Functor (EffectRWS w s m c) => Gettable (EffectRWS w s m c) |
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
| |
Instances
| (Monad Identity, Gettable (Accessor r)) => Effective Identity r (Accessor r) | |
| Functor (Accessor r) | |
| (Functor (Accessor r), Monoid r) => Applicative (Accessor r) | |
| Functor (Accessor r) => Gettable (Accessor r) | |
| (MonadReader b ((->) b), MonadReader a ((->) a)) => Magnify ((->) b) ((->) a) Accessor b a |
|
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.
noEffect :: (Applicative f, Gettable f) => f aSource
The mempty equivalent for a Gettable Applicative Functor.
A Monoid for a Gettable Applicative.
Constructors
| Folding | |
Fields
| |
Instances
| (Gettable f, Applicative f) => Monoid (Folding f a) |
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
| |