comonad-4.2.6: Comonads

Copyright(C) 2008-2013 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Comonad.Trans.Store

Contents

Description

The store comonad holds a constant value along with a modifiable accessor function, which maps the stored value to the focus.

This module defines the strict store (aka state-in-context/costate) comonad transformer.

stored value = (1, 5), accessor = fst, resulting focus = 1:

>>> :{
 let
   storeTuple :: Store (Int, Int) Int
   storeTuple = store fst (1, 5)
:}

Add something to the focus:

>>> :{
 let
   addToFocus :: Int -> Store (Int, Int) Int -> Int
   addToFocus x wa = x + extract wa
:}
>>> :{
  let
    added3 :: Store (Int, Int) Int
    added3 = extend (addToFocus 3) storeTuple
:}

The focus of added3 is now 1 + 3 = 4. However, this action changed only the accessor function and therefore the focus but not the stored value:

>>> pos added3
(1,5)
>>> extract added3
4

The strict store (state-in-context/costate) comonad transformer is subject to the laws:

x = seek (pos x) x
y = pos (seek y x)
seek y x = seek y (seek z x)

Thanks go to Russell O'Connor and Daniel Peebles for their help formulating and proving the laws for this comonad transformer.

Synopsis

The Store comonad

store :: (s -> a) -> s -> Store s a Source

Create a Store using an accessor function and a stored value

runStore :: Store s a -> (s -> a, s) Source

The Store comonad transformer

data StoreT s w a Source

Constructors

StoreT (w (s -> a)) s 

Instances

ComonadEnv e w => ComonadEnv e (StoreT t w) 
Comonad w => ComonadStore s (StoreT s w) 
ComonadTraced m w => ComonadTraced m (StoreT s w) 
ComonadTrans (StoreT s) 
ComonadHoist (StoreT s) 
Functor w => Functor (StoreT s w) 
(Applicative w, Monoid s) => Applicative (StoreT s w) 
(ComonadApply w, Semigroup s) => ComonadApply (StoreT s w) 
Comonad w => Comonad (StoreT s w) 
Typeable (* -> (* -> *) -> * -> *) StoreT 

runStoreT :: StoreT s w a -> (w (s -> a), s) Source

Operations

pos :: StoreT s w a -> s Source

Read the stored value

>>> pos $ store fst (1,5)
(1,5)

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

Set the stored value

>>> pos . seek (3,7) $ store fst (1,5)
(3,7)

Seek satisfies the law

seek s = peek s . duplicate

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

Modify the stored value

>>> pos . seeks swap $ store fst (1,5)
(5,1)

Seeks satisfies the law

seeks f = peeks f . duplicate

peek :: Comonad w => s -> StoreT s w a -> a Source

Peek at what the current focus would be for a different stored value

Peek satisfies the law

peek x . extend (peek y) = peek y

peeks :: Comonad w => (s -> s) -> StoreT s w a -> a Source

Peek at what the current focus would be if the stored value was modified by some function

experiment :: (Comonad w, Functor f) => (s -> f s) -> StoreT s w a -> f a Source

Applies a functor-valued function to the stored value, and then uses the new accessor to read the resulting focus.

>>> let f x = if x > 0 then Just (x^2) else Nothing
>>> experiment f $ store (+1) 2
Just 5
>>> experiment f $ store (+1) (-2)
Nothing