Stability | experimental |
---|---|
Maintainer | ekmett@gmail.com |
Safe Haskell | Safe-Infered |
A generalized Store comonad, parameterized by a Representable functor. The representation of that functor serves as the index of the store.
- type Store g = StoreT g Identity
- store :: Representable g => (Key g -> a) -> Key g -> Store g a
- runStore :: Indexable g => Store g a -> (Key g -> a, Key g)
- data StoreT g w a = StoreT (w (g a)) (Key g)
- storeT :: (Functor w, Representable g) => w (Key g -> a) -> Key g -> StoreT g w a
- runStoreT :: (Functor w, Indexable g) => StoreT g w a -> (w (Key g -> a), Key g)
- pos :: ComonadStore s w => forall a. w a -> s
- peek :: ComonadStore s w => forall a. s -> w a -> a
- peeks :: ComonadStore s w => forall a. (s -> s) -> w a -> a
- seek :: ComonadStore s w => forall a. s -> w a -> w a
- seeks :: ComonadStore s w => forall a. (s -> s) -> w a -> w a
Documentation
type Store g = StoreT g IdentitySource
A memoized store comonad parameterized by a representable functor g
, where
the representatation of g
, Key g
is the index of the store.
:: Representable g | |
=> (Key g -> a) | computation |
-> Key g | index |
-> Store g a |
Construct a store comonad computation from a function and a current index.
(The inverse of runStore
.)
Unwrap a state monad computation as a function.
(The inverse of state
.)
A store transformer comonad parameterized by:
-
g
- A representable functor used to memoize results for an indexKey g
-
w
- The inner comonad.
(ComonadEnv m w, Representable g) => ComonadEnv m (StoreT g w) | |
(Comonad w, Representable g, ~ * (Key g) s) => ComonadStore s (StoreT g w) | |
(ComonadTraced m w, Representable g) => ComonadTraced m (StoreT g w) | |
(Representable g, ComonadCofree f w) => ComonadCofree f (StoreT g w) | |
ComonadHoist (StoreT g) | |
Indexable g => ComonadTrans (StoreT g) | |
(Functor w, Functor g) => Functor (StoreT g w) | |
(Applicative w, Semigroup (Key g), Monoid (Key g), Representable g) => Applicative (StoreT g w) | |
(Comonad w, Representable g) => Comonad (StoreT g w) | |
(Extend w, Representable g) => Extend (StoreT g w) | |
(Apply w, Semigroup (Key g), Representable g) => Apply (StoreT g w) |
pos :: ComonadStore s w => forall a. w a -> s
peek :: ComonadStore s w => forall a. s -> w a -> a
peeks :: ComonadStore s w => forall a. (s -> s) -> w a -> a
seek :: ComonadStore s w => forall a. s -> w a -> w a
seeks :: ComonadStore s w => forall a. (s -> s) -> w a -> w a