| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Focus
Synopsis
- data Focus element m result = Focus (m (result, Change element)) (element -> m (result, Change element))
- data Change a
- member :: Monad m => Focus a m Bool
- lookup :: Monad m => Focus a m (Maybe a)
- lookupWithDefault :: Monad m => a -> Focus a m a
- delete :: Monad m => Focus a m ()
- lookupAndDelete :: Monad m => Focus a m (Maybe a)
- insert :: Monad m => a -> Focus a m ()
- insertOrMerge :: Monad m => (a -> a -> a) -> a -> Focus a m ()
- alter :: Monad m => (Maybe a -> Maybe a) -> Focus a m ()
- adjust :: Monad m => (a -> a) -> Focus a m ()
- update :: Monad m => (a -> Maybe a) -> Focus a m ()
- accessAndAdjust :: Monad m => (s -> a) -> (s -> s) -> Focus s m (Maybe a)
- liftState :: Monad m => State s a -> Focus s m (Maybe a)
- liftStateFn :: Monad m => (s -> (a, s)) -> Focus s m (Maybe a)
- cases :: Monad m => (b, Change a) -> (a -> (b, Change a)) -> Focus a m b
- unitCases :: Monad m => Change a -> (a -> Change a) -> Focus a m ()
- lookupWithDefaultM :: Monad m => m a -> Focus a m a
- insertM :: Monad m => m a -> Focus a m ()
- insertOrMergeM :: Monad m => (a -> a -> m a) -> m a -> Focus a m ()
- alterM :: Monad m => (Maybe a -> m (Maybe a)) -> Focus a m ()
- adjustM :: Monad m => (a -> m a) -> Focus a m ()
- updateM :: Monad m => (a -> m (Maybe a)) -> Focus a m ()
- casesM :: m (b, Change a) -> (a -> m (b, Change a)) -> Focus a m b
- unitCasesM :: Monad m => m (Change a) -> (a -> m (Change a)) -> Focus a m ()
- mappingInput :: Monad m => (a -> b) -> (b -> a) -> Focus a m x -> Focus b m x
- extractingInput :: Monad m => Focus a m b -> Focus a m (b, Maybe a)
- extractingChange :: Monad m => Focus a m b -> Focus a m (b, Change a)
- projectingChange :: Monad m => (Change a -> c) -> Focus a m b -> Focus a m (b, c)
- testingIfModifies :: Monad m => Focus a m b -> Focus a m (b, Bool)
- testingIfRemoves :: Monad m => Focus a m b -> Focus a m (b, Bool)
- testingIfInserts :: Monad m => Focus a m b -> Focus a m (b, Bool)
- testingSizeChange :: Monad m => sizeChange -> sizeChange -> sizeChange -> Focus a m b -> Focus a m (b, sizeChange)
- onTVarValue :: Focus a STM b -> Focus (TVar a) STM b
Documentation
data Focus element m result Source #
Abstraction over the modification of an element of a datastructure.
It is composable using the standard typeclasses, e.g.:
lookupAndDelete :: Monad m => Focus a m (Maybe a) lookupAndDelete = lookup <* delete
Instances
| MonadTrans (Focus element) Source # | |
| Monad m => Applicative (Focus element m) Source # | |
| Defined in Focus Methods pure :: a -> Focus element m a # (<*>) :: Focus element m (a -> b) -> Focus element m a -> Focus element m b # liftA2 :: (a -> b -> c) -> Focus element m a -> Focus element m b -> Focus element m c # (*>) :: Focus element m a -> Focus element m b -> Focus element m b # (<*) :: Focus element m a -> Focus element m b -> Focus element m a # | |
| Functor m => Functor (Focus element m) Source # | |
| Monad m => Monad (Focus element m) Source # | |
What to do with the focused value.
The interpretation of the commands is up to the context APIs.
Pure functions
Reading functions
lookupWithDefault :: Monad m => a -> Focus a m a Source #
Reproduces the behaviour of
 Data.Map.findWithDefault
 with a better name.
Modifying functions
insertOrMerge :: Monad m => (a -> a -> a) -> a -> Focus a m () Source #
Reproduces the behaviour of
 Data.Map.insertWith
 with a better name.
alter :: Monad m => (Maybe a -> Maybe a) -> Focus a m () Source #
Reproduces the behaviour of
 Data.Map.alter.
update :: Monad m => (a -> Maybe a) -> Focus a m () Source #
Reproduces the behaviour of
 Data.Map.update.
liftStateFn :: Monad m => (s -> (a, s)) -> Focus s m (Maybe a) Source #
Lift a pure state-monad-like function.
Construction utils
cases :: Monad m => (b, Change a) -> (a -> (b, Change a)) -> Focus a m b Source #
Lift pure functions which handle the cases of presence and absence of the element.
unitCases :: Monad m => Change a -> (a -> Change a) -> Focus a m () Source #
Lift pure functions which handle the cases of presence and absence of the element and produce no result.
Monadic functions
Reading functions
lookupWithDefaultM :: Monad m => m a -> Focus a m a Source #
A monadic version of lookupWithDefault.
Modifying functions
insertOrMergeM :: Monad m => (a -> a -> m a) -> m a -> Focus a m () Source #
A monadic version of insertOrMerge.
Construction utils
casesM :: m (b, Change a) -> (a -> m (b, Change a)) -> Focus a m b Source #
Lift monadic functions which handle the cases of presence and absence of the element.
unitCasesM :: Monad m => m (Change a) -> (a -> m (Change a)) -> Focus a m () Source #
Lift monadic functions which handle the cases of presence and absence of the element and produce no result.
Composition
mappingInput :: Monad m => (a -> b) -> (b -> a) -> Focus a m x -> Focus b m x Source #
Map the Focus input.
Change-inspecting functions
extractingInput :: Monad m => Focus a m b -> Focus a m (b, Maybe a) Source #
Extends the output with the input.
extractingChange :: Monad m => Focus a m b -> Focus a m (b, Change a) Source #
Extends the output with the change performed.
projectingChange :: Monad m => (Change a -> c) -> Focus a m b -> Focus a m (b, c) Source #
Extends the output with a projection on the change that was performed.
testingIfModifies :: Monad m => Focus a m b -> Focus a m (b, Bool) Source #
Extends the output with a flag,
 signaling whether a change, which is not Leave, has been introduced.
testingIfRemoves :: Monad m => Focus a m b -> Focus a m (b, Bool) Source #
Extends the output with a flag,
 signaling whether the Remove change has been introduced.
testingIfInserts :: Monad m => Focus a m b -> Focus a m (b, Bool) Source #
Extends the output with a flag,
 signaling whether an item will be inserted.
 That is, it didn't exist before and a Set change is introduced.
Arguments
| :: Monad m | |
| => sizeChange | Decreased | 
| -> sizeChange | Didn't change | 
| -> sizeChange | Increased | 
| -> Focus a m b | |
| -> Focus a m (b, sizeChange) | 
Extend the output with a flag, signaling how the size will be affected by the change.