Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- 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 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.
IndexedFunctor Context | |
IndexedFunctor Mafic | |
IndexedFunctor (Pretext p) | |
IndexedFunctor (Bazaar p) | |
IndexedFunctor (Molten i) | |
IndexedFunctor (PretextT p g) | |
IndexedFunctor (BazaarT p g) | |
IndexedFunctor (TakingWhile p f) |
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.
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.
IndexedComonad Context | |
(IndexedFunctor (Pretext p), Conjoined p) => IndexedComonad (Pretext p) | |
(IndexedFunctor (Bazaar p), Conjoined p) => IndexedComonad (Bazaar p) | |
IndexedFunctor (Molten i) => IndexedComonad (Molten i) | |
(IndexedFunctor (PretextT p g), Conjoined p) => IndexedComonad (PretextT p g) | |
(IndexedFunctor (BazaarT p g), Conjoined p) => IndexedComonad (BazaarT p g) |
class IndexedComonad w => IndexedComonadStore w whereSource
This is an indexed analogue to ComonadStore
for when you are working with an
IndexedComonad
.
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
.
IndexedComonadStore Context | |
(IndexedComonad (Pretext p), Conjoined p) => IndexedComonadStore (Pretext p) | |
(IndexedComonad (PretextT p g), Conjoined p) => IndexedComonadStore (PretextT p g) |
class Corepresentable p => Sellable p w | w -> p whereSource
Sellable (->) Context | |
Sellable (->) Mafic | |
Corepresentable p => Sellable p (Pretext p) | |
Corepresentable p => Sellable p (Bazaar p) | |
Corepresentable p => Sellable p (PretextT p g) | |
Corepresentable p => Sellable p (BazaarT p g) | |
Corepresentable (Indexed i) => Sellable (Indexed i) (Molten i) |
The indexed store can be used to characterize a Lens
and is used by clone
.
is isomorphic to
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.
Context (b -> t) a |
IndexedComonadStore Context | |
IndexedComonad Context | |
IndexedFunctor Context | |
Sellable (->) Context | |
(Comonad (Context a b), ~ * a b) => ComonadStore a (Context a b) | |
Functor (Context a b) | |
(Functor (Context a b), ~ * a b) => Comonad (Context a b) |
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
Pretext | |
|
Corepresentable p => Sellable p (Pretext p) | |
(Comonad (Pretext p a b), ~ * a b, Conjoined p) => ComonadStore a (Pretext p a b) | |
(IndexedComonad (Pretext p), Conjoined p) => IndexedComonadStore (Pretext p) | |
(IndexedFunctor (Pretext p), Conjoined p) => IndexedComonad (Pretext p) | |
IndexedFunctor (Pretext p) | |
Functor (Pretext p a b) | |
(Functor (Pretext p a b), ~ * a b, Conjoined p) => Comonad (Pretext p a b) |
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
.
PretextT | |
|
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) |