lens-family-core-1.2.1: Haskell 98 Lens Families

Safe HaskellSafe
LanguageHaskell98

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 ALens a a' b b' (or ALens' a b). Then, inside a where 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.

Synopsis

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 ALens' a b = LensLike' (IStore b b) a b Source #

ALens' a b is a universal Lens' a 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 b Source #

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 AGetter' a b = FoldLike' b a b Source #

AGetter' a b is a universal Fold' a 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

type AFold' a b = FoldLike' [b] a b Source #

AFold' a b is a universal Fold' a b instance

data IStore b b' a Source #

Instances

Functor (IStore b b') Source # 

Methods

fmap :: (a -> b) -> IStore b b' a -> IStore b b' b #

(<$) :: a -> IStore b b' b -> IStore b b' a #

data IKleeneStore b b' a Source #

Instances

Functor (IKleeneStore b b') Source # 

Methods

fmap :: (a -> b) -> IKleeneStore b b' a -> IKleeneStore b b' b #

(<$) :: a -> IKleeneStore b b' b -> IKleeneStore b b' a #

Applicative (IKleeneStore b b') Source # 

Methods

pure :: a -> IKleeneStore b b' a #

(<*>) :: IKleeneStore b b' (a -> b) -> IKleeneStore b b' a -> IKleeneStore b b' b #

(*>) :: IKleeneStore b b' a -> IKleeneStore b b' b -> IKleeneStore b b' b #

(<*) :: IKleeneStore b b' a -> IKleeneStore b b' b -> IKleeneStore b b' a #

Re-exports

type LensLike f a a' b b' = (b -> f b') -> a -> f a' Source #

type LensLike' f a b = (b -> f b) -> a -> f a Source #

type FoldLike r a a' b b' = LensLike (Constant r) a a' b b' Source #

type FoldLike' r a b = LensLike' (Constant r) a b Source #

type ASetter a a' b b' = LensLike Identity a a' b b' Source #

class Functor f => Applicative f #

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

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
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = 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).

Minimal complete definition

pure, (<*>)

Instances

Applicative [] 

Methods

pure :: a -> [a] #

(<*>) :: [a -> b] -> [a] -> [b] #

(*>) :: [a] -> [b] -> [b] #

(<*) :: [a] -> [b] -> [a] #

Applicative Maybe 

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Applicative IO 

Methods

pure :: a -> IO a #

(<*>) :: IO (a -> b) -> IO a -> IO b #

(*>) :: IO a -> IO b -> IO b #

(<*) :: IO a -> IO b -> IO a #

Applicative U1 

Methods

pure :: a -> U1 a #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b #

(*>) :: U1 a -> U1 b -> U1 b #

(<*) :: U1 a -> U1 b -> U1 a #

Applicative Par1 

Methods

pure :: a -> Par1 a #

(<*>) :: Par1 (a -> b) -> Par1 a -> Par1 b #

(*>) :: Par1 a -> Par1 b -> Par1 b #

(<*) :: Par1 a -> Par1 b -> Par1 a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Applicative Min 

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Applicative Max 

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative Option 

Methods

pure :: a -> Option a #

(<*>) :: Option (a -> b) -> Option a -> Option b #

(*>) :: Option a -> Option b -> Option b #

(<*) :: Option a -> Option b -> Option a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Applicative Complex 

Methods

pure :: a -> Complex a #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b #

(*>) :: Complex a -> Complex b -> Complex b #

(<*) :: Complex a -> Complex b -> Complex a #

Applicative ZipList 

Methods

pure :: a -> ZipList a #

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b #

(*>) :: ZipList a -> ZipList b -> ZipList b #

(<*) :: ZipList a -> ZipList b -> ZipList a #

Applicative Dual 

Methods

pure :: a -> Dual a #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b #

(*>) :: Dual a -> Dual b -> Dual b #

(<*) :: Dual a -> Dual b -> Dual a #

Applicative Sum 

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Applicative Product 

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative ((->) a) 

Methods

pure :: a -> a -> a #

(<*>) :: (a -> a -> b) -> (a -> a) -> a -> b #

(*>) :: (a -> a) -> (a -> b) -> a -> b #

(<*) :: (a -> a) -> (a -> b) -> a -> a #

Applicative (Either e) 

Methods

pure :: a -> Either e a #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b #

(*>) :: Either e a -> Either e b -> Either e b #

(<*) :: Either e a -> Either e b -> Either e a #

Applicative f => Applicative (Rec1 f) 

Methods

pure :: a -> Rec1 f a #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a #

Monoid a => Applicative ((,) a) 

Methods

pure :: a -> (a, a) #

(<*>) :: (a, a -> b) -> (a, a) -> (a, b) #

(*>) :: (a, a) -> (a, b) -> (a, b) #

(<*) :: (a, a) -> (a, b) -> (a, a) #

Monad m => Applicative (WrappedMonad m) 

Methods

pure :: a -> WrappedMonad m a #

(<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Applicative (ArrowMonad a) 

Methods

pure :: a -> ArrowMonad a a #

(<*>) :: ArrowMonad a (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(*>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

(<*) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

(Applicative f, Applicative g) => Applicative ((:*:) f g) 

Methods

pure :: a -> (f :*: g) a #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a #

(Applicative f, Applicative g) => Applicative ((:.:) f g) 

Methods

pure :: a -> (f :.: g) a #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a #

Arrow a => Applicative (WrappedArrow a b) 

Methods

pure :: a -> WrappedArrow a b a #

(<*>) :: WrappedArrow a b (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(*>) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b b #

(<*) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b a #

Monoid m => Applicative (Const * m) 

Methods

pure :: a -> Const * m a #

(<*>) :: Const * m (a -> b) -> Const * m a -> Const * m b #

(*>) :: Const * m a -> Const * m b -> Const * m b #

(<*) :: Const * m a -> Const * m b -> Const * m a #

Applicative f => Applicative (Alt * f) 

Methods

pure :: a -> Alt * f a #

(<*>) :: Alt * f (a -> b) -> Alt * f a -> Alt * f b #

(*>) :: Alt * f a -> Alt * f b -> Alt * f b #

(<*) :: Alt * f a -> Alt * f b -> Alt * f a #

Applicative f => Applicative (Backwards * f)

Apply f-actions in the reverse order.

Methods

pure :: a -> Backwards * f a #

(<*>) :: Backwards * f (a -> b) -> Backwards * f a -> Backwards * f b #

(*>) :: Backwards * f a -> Backwards * f b -> Backwards * f b #

(<*) :: Backwards * f a -> Backwards * f b -> Backwards * f a #

(Monoid w, Applicative m) => Applicative (WriterT w m) 

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

(Functor m, Monad m) => Applicative (StateT s m) 

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) 

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

Monoid a => Applicative (Constant * a) 

Methods

pure :: a -> Constant * a a #

(<*>) :: Constant * a (a -> b) -> Constant * a a -> Constant * a b #

(*>) :: Constant * a a -> Constant * a b -> Constant * a b #

(<*) :: Constant * a a -> Constant * a b -> Constant * a a #

(Monoid c, Monad m) => Applicative (Zooming m c) # 

Methods

pure :: a -> Zooming m c a #

(<*>) :: Zooming m c (a -> b) -> Zooming m c a -> Zooming m c b #

(*>) :: Zooming m c a -> Zooming m c b -> Zooming m c b #

(<*) :: Zooming m c a -> Zooming m c b -> Zooming m c a #

Applicative (IKleeneStore b b') # 

Methods

pure :: a -> IKleeneStore b b' a #

(<*>) :: IKleeneStore b b' (a -> b) -> IKleeneStore b b' a -> IKleeneStore b b' b #

(*>) :: IKleeneStore b b' a -> IKleeneStore b b' b -> IKleeneStore b b' b #

(<*) :: IKleeneStore b b' a -> IKleeneStore b b' b -> IKleeneStore b b' a #

Applicative f => Applicative (M1 i c f) 

Methods

pure :: a -> M1 i c f a #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a #

(Applicative f, Applicative g) => Applicative (Compose * * f g) 

Methods

pure :: a -> Compose * * f g a #

(<*>) :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b #

(*>) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g b #

(<*) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g a #

class Functor f => Phantom f Source #

Minimal complete definition

coerce

Instances

Phantom (Const * a) Source # 

Methods

coerce :: Const * a a -> Const * a b

Phantom f => Phantom (Backwards * f) Source # 

Methods

coerce :: Backwards * f a -> Backwards * f b

Phantom (Constant * a) Source # 

Methods

coerce :: Constant * a a -> Constant * a b

Phantom f => Phantom (AlongsideRight f a) Source # 

Methods

coerce :: AlongsideRight f a a -> AlongsideRight f a b

Phantom f => Phantom (AlongsideLeft f a) Source # 

Methods

coerce :: AlongsideLeft f a a -> AlongsideLeft f a b

(Phantom f, Functor g) => Phantom (Compose * * f g) Source # 

Methods

coerce :: Compose * * f g a -> Compose * * f g b

class Applicative f => Identical f Source #

Minimal complete definition

extract

Instances

Identical Identity Source # 

Methods

extract :: Identity a -> a

Identical f => Identical (Backwards * f) Source # 

Methods

extract :: Backwards * f a -> a

(Identical f, Identical g) => Identical (Compose * * f g) Source # 

Methods

extract :: Compose * * f g a -> a