lens-2.4.0.2: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-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.

Synopsis

Implementation details

data IndexedStore c d a Source

The indexed store can be used to characterize a Lens and is used by clone

Constructors

IndexedStore (d -> a) c 

Instances

newtype Focusing m c a Source

Used by Zoom to zoom into StateT

Constructors

Focusing 

Fields

unfocusing :: m (c, a)
 

Instances

Monad m => Functor (Focusing m c) 
(Monad m, Monoid c) => Applicative (Focusing m c) 
Monad z => Zoom (StateT s z) (StateT t z) (Focusing z) s t 
Monad z => Zoom (StateT s z) (StateT t z) (Focusing z) s t 

newtype FocusingWith w m c a Source

Used by Zoom to zoom into RWST

Constructors

FocusingWith 

Fields

unfocusingWith :: m (c, a, w)
 

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

Used by Zoom to zoom into WriterT.

Constructors

FocusingPlus 

Fields

unfocusingPlus :: k (c, w) a
 

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

Used by Zoom to zoom into MaybeT or ListT

Constructors

FocusingOn 

Fields

unfocusingOn :: k (f c) a
 

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

Used by Zoom to zoom into ErrorT

Constructors

FocusingErr 

Fields

unfocusingErr :: k (Err e c) a
 

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) 

newtype Err e a Source

Make a monoid out of Either for error handling

Constructors

Err 

Fields

getErr :: Either e a
 

Instances

Monoid a => Monoid (Err e a) 

newtype FocusingMay k c a Source

Used by Zoom to zoom into ErrorT

Constructors

FocusingMay 

Fields

unfocusingMay :: k (May c) a
 

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) 

newtype May a Source

Make a monoid out of Maybe for error handling

Constructors

May 

Fields

getMay :: Maybe a
 

Instances

Monoid a => Monoid (May a) 

newtype Traversed f Source

Used internally by traverseOf_ and the like.

Constructors

Traversed 

Fields

getTraversed :: f ()
 

Instances

newtype Sequenced m Source

Used internally by mapM_ and the like.

Constructors

Sequenced 

Fields

getSequenced :: m ()
 

Instances

newtype AppliedState f a Source

Applicative composition of State Int with a Functor, used by elementOf, elementsOf, traverseElement, traverseElementsOf

Constructors

AppliedState 

Fields

runAppliedState :: Int -> (f a, Int)
 

data Min a Source

Used for minimumOf

Constructors

NoMin 
Min a 

Instances

Ord a => Monoid (Min a) 

getMin :: Min a -> Maybe aSource

Obtain the minimum.

data Max a Source

Used for maximumOf

Constructors

NoMax 
Max a 

Instances

Ord a => Monoid (Max a) 

getMax :: Max a -> Maybe aSource

Obtain the maximum

newtype ElementOf f a Source

Used to find the nth element of a Traversal.

Constructors

ElementOf 

Fields

getElementOf :: Int -> ElementOfResult f a
 

Instances

Functor f => Functor (ElementOf f) 
Functor f => Applicative (ElementOf f) 
Gettable f => Gettable (ElementOf f)

This instance is a lie, but it is a useful lie.

data ElementOfResult f a Source

The result of trying to find the nth element of a Traversal.

Constructors

Searching !Int a 
Found !Int (f a) 
NotFound String 

Instances

data Kleene c d a Source

The Indexed Kleene Store comonad, aka the 'indexed cartesian store comonad' or an indexed FunList.

This is used to characterize a Traversal.

http://twanvl.nl/blog/haskell/non-regular1

Constructors

Done a 
More (Kleene c d (d -> a)) c 

Instances

kleene :: Applicative f => (c -> f d) -> Kleene c d b -> f bSource

Given an action to run for each matched pair, traverse a store.

newtype Effect m r a Source

Wrap a monadic effect with a phantom type argument.

Constructors

Effect 

Fields

getEffect :: m r
 

Instances

Monad m => Effective m r (Effect m r) 
Functor (Effect m r) 
(Monad m, Monoid r) => Applicative (Effect m r) 
Gettable (Effect m r) 
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

getEffectRWS :: s -> m (c, s, w)
 

Instances

Functor (EffectRWS w s m c) 
(Monoid c, Monoid w, Monad m) => Applicative (EffectRWS w s m c) 
Gettable (EffectRWS w s m c) 
(Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) (EffectRWS w s m) b a 
(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 = fmap f = coerce

Methods

coerce :: f a -> f bSource

Replace the phantom type argument.

Instances

Gettable (Const r) 
Gettable f => Gettable (Backwards f) 
Gettable (Accessor r) 
Gettable f => Gettable (ElementOf f)

This instance is a lie, but it is a useful lie.

(Functor f, Gettable g) => Gettable (Compose f g) 
Gettable (Effect m r) 
Gettable (EffectRWS w s m c) 

newtype Accessor r a Source

Used instead of Const to report

No instance of (Settable Accessor)

when the user attempts to misuse a Setter as a Getter, rather than a monolithic unification error.

Constructors

Accessor 

Fields

runAccessor :: r
 

Instances

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

Instances

Effective Identity r (Accessor r) 
Monad m => Effective m r (Effect m r) 
Effective m r f => Effective m (Dual r) (Backwards f) 

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

Anything Settable must be isomorphic to the Identity Functor.

Methods

untainted :: f a -> aSource

Instances

Settable Identity

so you can pass our a Setter into combinators from other lens libraries

Settable Mutator 
Settable f => Settable (Backwards f)

backwards

(Settable f, Settable g) => Settable (Compose f g) 

newtype Mutator a Source

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

runMutator :: a