| Copyright | (C) 2012-2016 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Control.Lens.Internal.Context
Description
- class IndexedFunctor w where- ifmap :: (s -> t) -> w a b s -> w a b t
 
- class IndexedFunctor w => IndexedComonad w where- iextract :: w a a t -> t
- iduplicate :: w a c t -> w a b (w b c t)
- iextend :: (w b c t -> r) -> w a c t -> w a b r
 
- class IndexedComonad w => IndexedComonadStore w where
- class Corepresentable p => Sellable p w | w -> p where- sell :: p a (w a b b)
 
- data Context a b t = Context (b -> t) a
- type Context' a = Context a a
- newtype Pretext p a b t = Pretext {- runPretext :: forall f. Functor f => p a (f b) -> f t
 
- type Pretext' p a = Pretext p a a
- newtype PretextT p g a b t = PretextT {- runPretextT :: forall f. Functor f => p a (f b) -> f t
 
- type PretextT' p g a = PretextT p g a a
Documentation
class IndexedFunctor w where Source
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.
Instances
| IndexedFunctor Context Source | |
| IndexedFunctor Mafic Source | |
| IndexedFunctor (Pretext p) Source | |
| IndexedFunctor (Bazaar1 p) Source | |
| IndexedFunctor (Bazaar p) Source | |
| IndexedFunctor (Molten i) Source | |
| IndexedFunctor (PretextT p g) Source | |
| IndexedFunctor (BazaarT1 p g) Source | |
| IndexedFunctor (BazaarT p g) Source | |
| IndexedFunctor (TakingWhile p f) Source | |
class IndexedFunctor w => IndexedComonad w where Source
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.
Minimal complete definition
Methods
iextract :: w a a t -> t Source
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 r Source
extend a indexed comonadic computation splitting the index.
Instances
| IndexedComonad Context Source | |
| Conjoined p => IndexedComonad (Pretext p) Source | |
| Conjoined p => IndexedComonad (Bazaar1 p) Source | |
| Conjoined p => IndexedComonad (Bazaar p) Source | |
| IndexedComonad (Molten i) Source | |
| Conjoined p => IndexedComonad (PretextT p g) Source | |
| Conjoined p => IndexedComonad (BazaarT1 p g) Source | |
| Conjoined p => IndexedComonad (BazaarT p g) Source | |
class IndexedComonad w => IndexedComonadStore w where Source
This is an indexed analogue to ComonadStore for when you are working with an
 IndexedComonad.
Methods
This is the generalization of pos to an indexed comonad store.
ipeek :: c -> w a c t -> t Source
This is the generalization of peek to an indexed comonad store.
ipeeks :: (a -> c) -> w a c t -> t Source
This is the generalization of peeks to an indexed comonad store.
iseek :: b -> w a c t -> w b c t Source
This is the generalization of seek to an indexed comonad store.
iseeks :: (a -> b) -> w a c t -> w b c t Source
This is the generalization of seeks to an indexed comonad store.
iexperiment :: Functor f => (b -> f c) -> w b c t -> f t Source
This is the generalization of experiment to an indexed comonad store.
context :: w a b t -> Context a b t Source
We can always forget the rest of the structure of w and obtain a simpler
 indexed comonad store model called Context.
Instances
| IndexedComonadStore Context Source | |
| Conjoined p => IndexedComonadStore (Pretext p) Source | |
| Conjoined p => IndexedComonadStore (PretextT p g) Source | |
class Corepresentable p => Sellable p w | w -> p where Source
Instances
| Sellable (->) Context Source | |
| Sellable (->) Mafic Source | |
| Corepresentable p => Sellable p (Pretext p) Source | |
| Corepresentable p => Sellable p (Bazaar1 p) Source | |
| Corepresentable p => Sellable p (Bazaar p) Source | |
| Corepresentable p => Sellable p (PretextT p g) Source | |
| Corepresentable p => Sellable p (BazaarT1 p g) Source | |
| Corepresentable p => Sellable p (BazaarT p g) Source | |
| Sellable (Indexed i) (Molten i) Source | |
The indexed store can be used to characterize a Lens
 and is used by clone.
Context a b tnewtype ,
 and to Context a b t = Context { runContext :: forall f. Functor f => (a -> f b) -> f t }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 | 
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 
 | |
Instances
| Corepresentable p => Sellable p (Pretext p) Source | |
| ((~) * a b, Conjoined p) => ComonadStore a (Pretext p a b) Source | |
| Conjoined p => IndexedComonadStore (Pretext p) Source | |
| Conjoined p => IndexedComonad (Pretext p) Source | |
| IndexedFunctor (Pretext p) Source | |
| Functor (Pretext p a b) Source | |
| ((~) * a b, Conjoined p) => Comonad (Pretext p a b) Source | |
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
 Getter-compatibility under limited circumstances.
 This is used internally to permit a number of combinators to gracefully
 degrade when applied to a Fold or
 Getter.
Constructors
| PretextT | |
| Fields 
 | |
Instances
| Corepresentable p => Sellable p (PretextT p g) Source | |
| ((~) * a b, Conjoined p) => ComonadStore a (PretextT p g a b) Source | |
| Conjoined p => IndexedComonadStore (PretextT p g) Source | |
| Conjoined p => IndexedComonad (PretextT p g) Source | |
| IndexedFunctor (PretextT p g) Source | |
| Functor (PretextT p g a b) Source | |
| (Profunctor p, Contravariant g) => Contravariant (PretextT p g a b) Source | |
| ((~) * a b, Conjoined p) => Comonad (PretextT p g a b) Source | |