| Copyright | (C) 2008-2013 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Control.Comonad.Trans.Store
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 added34
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
- type Store s = StoreT s Identity
- store :: (s -> a) -> s -> Store s a
- runStore :: Store s a -> (s -> a, s)
- data StoreT s w a = StoreT (w (s -> a)) s
- runStoreT :: StoreT s w a -> (w (s -> a), s)
- pos :: StoreT s w a -> s
- seek :: s -> StoreT s w a -> StoreT s w a
- seeks :: (s -> s) -> StoreT s w a -> StoreT s w a
- peek :: Comonad w => s -> StoreT s w a -> a
- peeks :: Comonad w => (s -> s) -> StoreT s w a -> a
- experiment :: (Comonad w, Functor f) => (s -> f s) -> StoreT s w a -> f a
The Store comonad
store :: (s -> a) -> s -> Store s a Source #
Create a Store using an accessor function and a stored value
The Store comonad transformer
Constructors
| StoreT (w (s -> a)) s | 
Instances
| ComonadTraced m w => ComonadTraced m (StoreT s w) Source # | |
| Defined in Control.Comonad.Traced.Class | |
| Comonad w => ComonadStore s (StoreT s w) Source # | |
| Defined in Control.Comonad.Store.Class Methods pos :: StoreT s w a -> s Source # peek :: s -> StoreT s w a -> a Source # peeks :: (s -> s) -> StoreT s w a -> a Source # seek :: s -> StoreT s w a -> StoreT s w a Source # seeks :: (s -> s) -> StoreT s w a -> StoreT s w a Source # experiment :: Functor f => (s -> f s) -> StoreT s w a -> f a Source # | |
| ComonadEnv e w => ComonadEnv e (StoreT t w) Source # | |
| Defined in Control.Comonad.Env.Class | |
| ComonadHoist (StoreT s) Source # | |
| ComonadTrans (StoreT s) Source # | |
| Functor w => Functor (StoreT s w) Source # | |
| (Applicative w, Monoid s) => Applicative (StoreT s w) Source # | |
| Defined in Control.Comonad.Trans.Store | |
| (ComonadApply w, Semigroup s) => ComonadApply (StoreT s w) Source # | |
| Comonad w => Comonad (StoreT s w) Source # | |
Operations
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) 2Just 5>>>experiment f $ store (+1) (-2)Nothing