lens-3.8.3: Lenses, Folds and Traversals

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.Internal.Context

Description

 

Synopsis

Documentation

class IndexedFunctor w whereSource

This is a Bob Atkey -style 2-argument indexed functor.

It exists as a superclass for IndexedComonad and expresses the functoriality of an IndexedComonad in its third argument.

Methods

ifmap :: (s -> t) -> w a b s -> w a b tSource

class IndexedFunctor w => IndexedComonad w whereSource

This is a Bob Atkey -style 2-argument indexed comonad.

It exists as a superclass for IndexedComonad and expresses the functoriality of an IndexedComonad in its third argument.

The notion of indexed monads is covered in more depth in Bob Atkey's Parameterized Notions of Computation http://bentnib.org/paramnotions-jfp.pdf and that construction is dualized here.

Methods

iextract :: w a a t -> tSource

extract from an indexed comonadic value when the indices match.

iduplicate :: w a c t -> w a b (w b c t)Source

duplicate an indexed comonadic value splitting the index.

iextend :: (w b c t -> r) -> w a c t -> w a b rSource

extend a indexed comonadic computation splitting the index.

class IndexedComonad w => IndexedComonadStore w whereSource

This is an indexed analogue to ComonadStore for when you are working with an IndexedComonad.

Methods

ipos :: w a c t -> aSource

This is the generalization of pos to an indexed comonad store.

ipeek :: c -> w a c t -> tSource

This is the generalization of peek to an indexed comonad store.

ipeeks :: (a -> c) -> w a c t -> tSource

This is the generalization of peeks to an indexed comonad store.

iseek :: b -> w a c t -> w b c tSource

This is the generalization of seek to an indexed comonad store.

iseeks :: (a -> b) -> w a c t -> w b c tSource

This is the generalization of seeks to an indexed comonad store.

iexperiment :: Functor f => (b -> f c) -> w b c t -> f tSource

This is the generalization of experiment to an indexed comonad store.

context :: w a b t -> Context a b tSource

We can always forget the rest of the structure of w and obtain a simpler indexed comonad store model called Context.

class Corepresentable p => Sellable p w | w -> p whereSource

This is used internally to construct a Bazaar, Context or Pretext from a singleton value.

Methods

sell :: p a (w a b b)Source

data Context a b t Source

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

Context a b t is isomorphic to newtype Context a b t = Context { runContext :: forall f. Functor f => (a -> f b) -> f t }, and to exists s. (s, Lens s t a b).

A Context is like a Lens that has already been applied to a some structure.

Constructors

Context (b -> t) a 

type Context' a = Context a aSource

type Context' a s = Context a a s

newtype Pretext p a b t Source

This is a generalized form of Context that can be repeatedly cloned with less impact on its performance, and which permits the use of an arbitrary Conjoined Profunctor

Constructors

Pretext 

Fields

runPretext :: forall f. Functor f => p a (f b) -> f t
 

type Pretext' p a = Pretext p a aSource

type Pretext' p a s = Pretext p a a s

newtype PretextT p g a b t Source

This is a generalized form of Context that can be repeatedly cloned with less impact on its performance, and which permits the use of an arbitrary Conjoined Profunctor.

The extra phantom Functor is used to let us lie and claim a Gettable instance under limited circumstances. This is used internally to permit a number of combinators to gracefully degrade when applied to a Fold, Getter or Action.

Constructors

PretextT 

Fields

runPretextT :: forall f. Functor f => p a (f b) -> f t
 

Instances

Corepresentable p => Sellable p (PretextT p g) 
(Comonad (PretextT p g a b), ~ * a b, Conjoined p) => ComonadStore a (PretextT p g a b) 
(IndexedComonad (PretextT p g), Conjoined p) => IndexedComonadStore (PretextT p g) 
(IndexedFunctor (PretextT p g), Conjoined p) => IndexedComonad (PretextT p g) 
IndexedFunctor (PretextT p g) 
Functor (PretextT p g a b) 
(Functor (PretextT p g a b), ~ * a b, Conjoined p) => Comonad (PretextT p g a b) 
(Functor (PretextT p g a b), Profunctor p, Gettable g) => Gettable (PretextT p g a b) 

type PretextT' p g a = PretextT p g a aSource

type PretextT' p g a s = PretextT p g a a s