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

Safe HaskellSafe-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'
  • 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, and cloneFold provides similar functionality for traversals, getters and folds respectively. Setters are already monomorphic, so do not need to be cloned.

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.

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 = ALens a a b bSource

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 = ALens a a b 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 AGetter' a b = AGetter a a b bSource

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 = AFold a a b bSource

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

data IStore b b' a Source

Instances

Functor (IStore b b') 

data IKleeneStore b b' a Source

Instances

Re-exports

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

type FoldLike r a a' b b' = LensLike (Getting r) 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:

      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 pure = return and (<*>) = ap (which implies that pure and <*> satisfy the applicative functor laws).