lens-family-core-2.1.0: Haskell 2022 Lens Families

Safe HaskellSafe
LanguageHaskell98

Lens.Family.Clone

Contents

Description

This module is provided for "Haskell 2022" compatibility. If you are able to use Rank2Types, I advise you to instead use the rank 2 aliases

  • Adapter, Adapter'
  • Prism, Prism'
  • Lens, Lens'
  • Traversal, Traversal'
  • Setter, Setter'
  • Grate, Grate'
  • Resetter, Resetter'
  • Grid, Grid'
  • Fold, Fold'
  • Getter, Getter'
  • Reviewer, Reviewer'

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 s t a b (or ALens' s a). Then, inside a where clause, you use cloneLens to create a Lens type.

For example.

example :: ALens s t a 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.

cloneAdapter, cloneGrate, cloneTraversal, cloneSetter, cloneResetter, cloneGetter, and cloneFold provides similar functionality for adapters, grates, traversals, setters, resetters, getters, and folds respectively. Unfortunately, it is not yet known how to clone prisms and grids.

Note: Cloning is only need if you use a functional reference multiple times with different instances.

Synopsis

Documentation

cloneAdapter :: (Functor f, Functor g) => AnAdapter s t a b -> AdapterLike f g s t a b Source #

Converts a universal adapter instance back into a polymorphic adapter.

cloneLens :: Functor f => ALens s t a b -> LensLike f s t a b Source #

Converts a universal lens instance back into a polymorphic lens.

cloneGrate :: Functor g => AGrate s t a b -> GrateLike g s t a b Source #

Converts a universal grate instance back into a polymorphic grater.

cloneTraversal :: Applicative f => ATraversal s t a b -> LensLike f s t a b Source #

Converts a universal traversal instance back into a polymorphic traversal.

cloneSetter :: Identical f => ASetter s t a b -> LensLike f s t a b Source #

Converts a universal setter instance back into a polymorphic setter.

cloneResetter :: Identical f => AResetter s t a b -> GrateLike f s t a b Source #

Converts a universal resetter instance back into a polymorphic resetter.

cloneGetter :: Phantom f => AGetter s t a b -> LensLike f s t a b Source #

Converts a universal getter instance back into a polymorphic getter.

cloneFold :: (Phantom f, Applicative f) => AFold s t a b -> LensLike f s t a b Source #

Converts a universal fold instance back into a polymorphic fold.

Types

type AnAdapter s t a b = AdapterLike (PStore (s -> a) b) ((->) s) s t a b Source #

AnAdapter s t a b is a universal Adapter s t a b instance

type AnAdapter' s a = AdapterLike' (PStore (s -> a) a) ((->) s) s a Source #

AnAdapter' s a is a universal Adapter' s a instance

type ALens s t a b = LensLike (PStore a b) s t a b Source #

ALens s t a b is a universal Lens s t a b instance

type ALens' s a = LensLike' (PStore a a) s a Source #

ALens' s a is a universal Lens' s a instance

type ATraversal s t a b = LensLike (PKleeneStore a b) s t a b Source #

ATraversal s t a b is a universal Traversal s t a b instance

type ATraversal' s a = LensLike' (PKleeneStore a a) s a Source #

ATraversal' a b is a universal Traversal' a b instance

type AGetter s t a b = FoldLike a s t a b Source #

AGetter s t a b is a universal Getter s t a b instance

type AGetter' s a = FoldLike' a s a Source #

AGetter' s a is a universal Getter' s a instance

type AFold s t a b = FoldLike [a] s t a b Source #

AFold s t a b is a universal Fold s t a b instance

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

AFold' s a is a universal Fold' s a instance

data PStore i j a Source #

Instances
Functor (PStore i j) Source # 
Instance details

Defined in Lens.Family.Clone

Methods

fmap :: (a -> b) -> PStore i j a -> PStore i j b #

(<$) :: a -> PStore i j b -> PStore i j a #

data PKleeneStore i j a Source #

Instances
Functor (PKleeneStore i j) Source # 
Instance details

Defined in Lens.Family.Clone

Methods

fmap :: (a -> b) -> PKleeneStore i j a -> PKleeneStore i j b #

(<$) :: a -> PKleeneStore i j b -> PKleeneStore i j a #

Applicative (PKleeneStore i j) Source # 
Instance details

Defined in Lens.Family.Clone

Methods

pure :: a -> PKleeneStore i j a #

(<*>) :: PKleeneStore i j (a -> b) -> PKleeneStore i j a -> PKleeneStore i j b #

liftA2 :: (a -> b -> c) -> PKleeneStore i j a -> PKleeneStore i j b -> PKleeneStore i j c #

(*>) :: PKleeneStore i j a -> PKleeneStore i j b -> PKleeneStore i j b #

(<*) :: PKleeneStore i j a -> PKleeneStore i j b -> PKleeneStore i j a #

Re-exports

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

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

type GrateLike g s t a b = (g a -> b) -> g s -> t Source #

type GrateLike' g s a = (g a -> a) -> g s -> s Source #

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

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

type AGrate s t a b = GrateLike (PCont b a) s t a b Source #

type ASetter s t a b = LensLike Identity s t a b Source #

type AResetter s t a b = GrateLike Identity s t a b Source #

class Functor f => Phantom f Source #

Minimal complete definition

coerce

Instances
Phantom (Const a :: Type -> Type) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Const a a0 -> Const a b

Phantom (Constant a :: Type -> Type) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Phantom f => Phantom (Backwards f) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Backwards f a -> Backwards f b

Phantom g => Phantom (FromG e g) Source # 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: FromG e g a -> FromG e g b

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

Defined in Lens.Family.Stock

Methods

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

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

Defined in Lens.Family.Stock

Methods

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

Phantom g => Phantom (FromF i j g) Source # 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: FromF i j g a -> FromF i j g b

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

Defined in Lens.Family.Phantom

Methods

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

class (Traversable f, Applicative f) => Identical f Source #

Minimal complete definition

extract

Instances
Identical Identity Source # 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Identity a -> a

Identical f => Identical (Backwards f) Source # 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Backwards f a -> a

(Identical f, Identical g) => Identical (Compose f g) Source # 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Compose f g a -> a