Copyright | (c) Edward Kmett & Sjoerd Visscher 2011 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell98 |
This is a generalized Store
Comonad
, parameterized by a Representable
Functor
.
The representation of that Functor
serves as the index of the store.
This can be useful if the representable functor serves to memoize its contents and will be inspected often.
- type Store g = StoreT g Identity
- store :: Representable g => (Rep g -> a) -> Rep g -> Store g a
- runStore :: Representable g => Store g a -> (Rep g -> a, Rep g)
- data StoreT g w a = StoreT (w (g a)) (Rep g)
- storeT :: (Functor w, Representable g) => w (Rep g -> a) -> Rep g -> StoreT g w a
- runStoreT :: (Functor w, Representable g) => StoreT g w a -> (w (Rep g -> a), Rep g)
- class Comonad w => ComonadStore s w | w -> s where
Documentation
type Store g = StoreT g Identity Source
A memoized store comonad parameterized by a representable functor g
, where
the representatation of g
, Rep g
is the index of the store.
:: Representable g | |
=> (Rep g -> a) | computation |
-> Rep g | index |
-> Store g a |
Construct a store comonad computation from a function and a current index.
(The inverse of runStore
.)
:: Representable g | |
=> Store g a | a store to access |
-> (Rep g -> a, Rep g) | initial state |
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 indexRep g
w
- The inner comonad.
(ComonadTraced m w, Representable g) => ComonadTraced m (StoreT g w) | |
(Comonad w, Representable g, (~) * (Rep g) s) => ComonadStore s (StoreT g w) | |
(ComonadEnv m w, Representable g) => ComonadEnv m (StoreT g w) | |
(Representable g, ComonadCofree f w) => ComonadCofree f (StoreT g w) | |
ComonadHoist (StoreT g) | |
Representable g => ComonadTrans (StoreT g) | |
(Functor w, Functor g) => Functor (StoreT g w) | |
(Applicative w, Semigroup (Rep g), Monoid (Rep g), Representable g) => Applicative (StoreT g w) | |
(Comonad w, Representable g) => Comonad (StoreT g w) | |
(ComonadApply w, Semigroup (Rep g), Representable g) => ComonadApply (StoreT g w) | |
(Apply w, Semigroup (Rep g), Representable g) => Apply (StoreT g w) | |
(Extend w, Representable g) => Extend (StoreT g w) |
class Comonad w => ComonadStore s w | w -> s where
pos :: w a -> s
peek :: s -> w a -> a
peeks :: (s -> s) -> w a -> a
seek :: s -> w a -> w a
seeks :: (s -> s) -> w a -> w a
experiment :: Functor f => (s -> f s) -> w a -> f a
ComonadStore s w => ComonadStore s (IdentityT w) | |
ComonadStore s w => ComonadStore s (Cofree w) | |
(Comonad w, Representable g, (~) * (Rep g) s) => ComonadStore s (StoreT g w) | |
(ComonadStore s w, Monoid m) => ComonadStore s (TracedT m w) | |
Comonad w => ComonadStore s (StoreT s w) | |
ComonadStore s w => ComonadStore s (EnvT e w) |