Safe Haskell | Trustworthy |
---|
- 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 aSource
Create a Store using an accessor function and a stored value
The Store comonad transformer
StoreT (w (s -> a)) s |
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) | |
(Typeable s, Typeable1 w) => Typeable1 (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 s, Typeable1 w, Typeable a) => Typeable (StoreT s w a) |
Operations
seek :: s -> StoreT s w a -> StoreT s w aSource
Set the stored value
pos . seek (3,7) $ store fst (1,5) (3,7)
Seek satisfies the law
seek s = peek s . duplicate
peek :: Comonad w => s -> StoreT s w a -> aSource
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 -> aSource
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 aSource
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