adjunctions-4.4: Adjunctions and representable functors

Copyright(c) Edward Kmett & Sjoerd Visscher 2011
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell98

Control.Comonad.Representable.Store

Description

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.

Synopsis

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.

store Source #

Arguments

:: 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.)

runStore Source #

Arguments

:: 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.)

data StoreT g w a Source #

A store transformer comonad parameterized by:

  • g - A representable functor used to memoize results for an index Rep g
  • w - The inner comonad.

Constructors

StoreT (w (g a)) (Rep g) 

Instances

(ComonadEnv m w, Representable g) => ComonadEnv m (StoreT g w) Source # 

Methods

ask :: StoreT g w a -> m #

(Comonad w, Representable g, (~) * (Rep g) s) => ComonadStore s (StoreT g w) Source # 

Methods

pos :: StoreT g w a -> s #

peek :: s -> StoreT g w a -> a #

peeks :: (s -> s) -> StoreT g w a -> a #

seek :: s -> StoreT g w a -> StoreT g w a #

seeks :: (s -> s) -> StoreT g w a -> StoreT g w a #

experiment :: Functor f => (s -> f s) -> StoreT g w a -> f a #

(ComonadTraced m w, Representable g) => ComonadTraced m (StoreT g w) Source # 

Methods

trace :: m -> StoreT g w a -> a #

(Representable g, ComonadCofree f w) => ComonadCofree f (StoreT g w) Source # 

Methods

unwrap :: StoreT g w a -> f (StoreT g w a) #

Representable g => ComonadTrans (StoreT g) Source # 

Methods

lower :: Comonad w => StoreT g w a -> w a #

ComonadHoist (StoreT g) Source # 

Methods

cohoist :: (Comonad w, Comonad v) => (forall x. w x -> v x) -> StoreT g w a -> StoreT g v a #

(Functor w, Functor g) => Functor (StoreT g w) Source # 

Methods

fmap :: (a -> b) -> StoreT g w a -> StoreT g w b #

(<$) :: a -> StoreT g w b -> StoreT g w a #

(Applicative w, Monoid (Rep g), Representable g) => Applicative (StoreT g w) Source # 

Methods

pure :: a -> StoreT g w a #

(<*>) :: StoreT g w (a -> b) -> StoreT g w a -> StoreT g w b #

liftA2 :: (a -> b -> c) -> StoreT g w a -> StoreT g w b -> StoreT g w c #

(*>) :: StoreT g w a -> StoreT g w b -> StoreT g w b #

(<*) :: StoreT g w a -> StoreT g w b -> StoreT g w a #

(Comonad w, Representable g) => Comonad (StoreT g w) Source # 

Methods

extract :: StoreT g w a -> a #

duplicate :: StoreT g w a -> StoreT g w (StoreT g w a) #

extend :: (StoreT g w a -> b) -> StoreT g w a -> StoreT g w b #

(ComonadApply w, Semigroup (Rep g), Representable g) => ComonadApply (StoreT g w) Source # 

Methods

(<@>) :: StoreT g w (a -> b) -> StoreT g w a -> StoreT g w b #

(@>) :: StoreT g w a -> StoreT g w b -> StoreT g w b #

(<@) :: StoreT g w a -> StoreT g w b -> StoreT g w a #

(Apply w, Semigroup (Rep g), Representable g) => Apply (StoreT g w) Source # 

Methods

(<.>) :: StoreT g w (a -> b) -> StoreT g w a -> StoreT g w b #

(.>) :: StoreT g w a -> StoreT g w b -> StoreT g w b #

(<.) :: StoreT g w a -> StoreT g w b -> StoreT g w a #

liftF2 :: (a -> b -> c) -> StoreT g w a -> StoreT g w b -> StoreT g w c #

(Extend w, Representable g) => Extend (StoreT g w) Source # 

Methods

duplicated :: StoreT g w a -> StoreT g w (StoreT g w a) #

extended :: (StoreT g w a -> b) -> StoreT g w a -> StoreT g w b #

storeT :: (Functor w, Representable g) => w (Rep g -> a) -> Rep g -> StoreT g w a Source #

runStoreT :: (Functor w, Representable g) => StoreT g w a -> (w (Rep g -> a), Rep g) Source #

class Comonad w => ComonadStore s (w :: * -> *) | w -> s where #

Minimal complete definition

pos, peek

Methods

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 #

Instances

ComonadStore s w => ComonadStore s (Cofree w) 

Methods

pos :: Cofree w a -> s #

peek :: s -> Cofree w a -> a #

peeks :: (s -> s) -> Cofree w a -> a #

seek :: s -> Cofree w a -> Cofree w a #

seeks :: (s -> s) -> Cofree w a -> Cofree w a #

experiment :: Functor f => (s -> f s) -> Cofree w a -> f a #

(Comonad w, Representable g, (~) * (Rep g) s) => ComonadStore s (StoreT g w) # 

Methods

pos :: StoreT g w a -> s #

peek :: s -> StoreT g w a -> a #

peeks :: (s -> s) -> StoreT g w a -> a #

seek :: s -> StoreT g w a -> StoreT g w a #

seeks :: (s -> s) -> StoreT g w a -> StoreT g w a #

experiment :: Functor f => (s -> f s) -> StoreT g w a -> f a #

(ComonadStore s w, Monoid m) => ComonadStore s (TracedT m w) 

Methods

pos :: TracedT m w a -> s #

peek :: s -> TracedT m w a -> a #

peeks :: (s -> s) -> TracedT m w a -> a #

seek :: s -> TracedT m w a -> TracedT m w a #

seeks :: (s -> s) -> TracedT m w a -> TracedT m w a #

experiment :: Functor f => (s -> f s) -> TracedT m w a -> f a #

Comonad w => ComonadStore s (StoreT s w) 

Methods

pos :: StoreT s w a -> s #

peek :: s -> StoreT s w a -> a #

peeks :: (s -> s) -> StoreT s w a -> a #

seek :: s -> StoreT s w a -> StoreT s w a #

seeks :: (s -> s) -> StoreT s w a -> StoreT s w a #

experiment :: Functor f => (s -> f s) -> StoreT s w a -> f a #

ComonadStore s w => ComonadStore s (IdentityT * w) 

Methods

pos :: IdentityT * w a -> s #

peek :: s -> IdentityT * w a -> a #

peeks :: (s -> s) -> IdentityT * w a -> a #

seek :: s -> IdentityT * w a -> IdentityT * w a #

seeks :: (s -> s) -> IdentityT * w a -> IdentityT * w a #

experiment :: Functor f => (s -> f s) -> IdentityT * w a -> f a #

ComonadStore s w => ComonadStore s (EnvT e w) 

Methods

pos :: EnvT e w a -> s #

peek :: s -> EnvT e w a -> a #

peeks :: (s -> s) -> EnvT e w a -> a #

seek :: s -> EnvT e w a -> EnvT e w a #

seeks :: (s -> s) -> EnvT e w a -> EnvT e w a #

experiment :: Functor f => (s -> f s) -> EnvT e w a -> f a #