focus-1.0.1.2: A general abstraction for manipulating elements of container data structures

Safe HaskellNone
LanguageHaskell2010

Focus

Contents

Synopsis

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

Constructors

Focus (m (result, Change element)) (element -> m (result, Change element)) 
Instances
MonadTrans (Focus element) Source # 
Instance details

Defined in Focus

Methods

lift :: Monad m => m a -> Focus element m a #

Monad m => Monad (Focus element m) Source # 
Instance details

Defined in Focus

Methods

(>>=) :: Focus element m a -> (a -> Focus element m b) -> Focus element m b #

(>>) :: Focus element m a -> Focus element m b -> Focus element m b #

return :: a -> Focus element m a #

fail :: String -> Focus element m a #

Functor m => Functor (Focus element m) Source # 
Instance details

Defined in Focus

Methods

fmap :: (a -> b) -> Focus element m a -> Focus element m b #

(<$) :: a -> Focus element m b -> Focus element m a #

Monad m => Applicative (Focus element m) Source # 
Instance details

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 #

data Change a Source #

What to do with the focused value.

The interpretation of the commands is up to the context APIs.

Constructors

Leave

Produce no changes

Remove

Delete it

Set a

Set its value to the provided one

Instances
Functor Change Source # 
Instance details

Defined in Focus

Methods

fmap :: (a -> b) -> Change a -> Change b #

(<$) :: a -> Change b -> Change a #

Eq a => Eq (Change a) Source # 
Instance details

Defined in Focus

Methods

(==) :: Change a -> Change a -> Bool #

(/=) :: Change a -> Change a -> Bool #

Ord a => Ord (Change a) Source # 
Instance details

Defined in Focus

Methods

compare :: Change a -> Change a -> Ordering #

(<) :: Change a -> Change a -> Bool #

(<=) :: Change a -> Change a -> Bool #

(>) :: Change a -> Change a -> Bool #

(>=) :: Change a -> Change a -> Bool #

max :: Change a -> Change a -> Change a #

min :: Change a -> Change a -> Change a #

Show a => Show (Change a) Source # 
Instance details

Defined in Focus

Methods

showsPrec :: Int -> Change a -> ShowS #

show :: Change a -> String #

showList :: [Change a] -> ShowS #

Pure functions

Reading functions

member :: Monad m => Focus a m Bool Source #

Reproduces the behaviour of Data.Map.lookup.

lookup :: Monad m => Focus a m (Maybe a) Source #

Reproduces the behaviour of Data.Map.lookup.

lookupWithDefault :: Monad m => a -> Focus a m a Source #

Reproduces the behaviour of Data.Map.findWithDefault with a better name.

Modifying functions

delete :: Monad m => Focus a m () Source #

Reproduces the behaviour of Data.Map.delete.

lookupAndDelete :: Monad m => Focus a m (Maybe a) Source #

Lookup an element and delete it if it exists.

Same as lookup <* delete.

insert :: Monad m => a -> Focus a m () Source #

Reproduces the behaviour of Data.Map.insert.

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.

adjust :: Monad m => (a -> a) -> Focus a m () Source #

Reproduces the behaviour of Data.Map.adjust.

update :: Monad m => (a -> Maybe a) -> Focus a m () Source #

Reproduces the behaviour of Data.Map.update.

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

insertM :: Monad m => m a -> Focus a m () Source #

A monadic version of insert.

insertOrMergeM :: Monad m => (a -> a -> m a) -> m a -> Focus a m () Source #

A monadic version of insertOrMerge.

alterM :: Monad m => (Maybe a -> m (Maybe a)) -> Focus a m () Source #

A monadic version of alter.

adjustM :: Monad m => (a -> m a) -> Focus a m () Source #

A monadic version of adjust.

updateM :: Monad m => (a -> m (Maybe a)) -> Focus a m () Source #

A monadic version of update.

Construction utils

casesM :: Monad m => 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.

testingSizeChange Source #

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.

STM

onTVarValue :: Focus a STM b -> Focus (TVar a) STM b Source #

Focus on the contents of a TVar.