adjunctions-4.1.0.1: Adjunctions and representable functors

Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

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 IdentitySource

A memoized store comonad parameterized by a representable functor g, where the representatation of g, Rep g is the index of the store.

storeSource

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

runStoreSource

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) 

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

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

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 (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)