selections-0.1.0.0: Combinators for operating with selections over an underlying functor

Safe HaskellNone
LanguageHaskell2010

Data.Functor.Selection

Contents

Synopsis

SelectionT

newtype SelectionT f b a Source #

A monad transformer for performing actions over selected values. Combinators are provided to select specific values within the underlying Functor. This transformer is isomorphic to EitherT, but interprets semantics differently, thus providing a different understanding and different combinators.

Constructors

SelectionT 

Fields

  • runSelectionT :: f (Either b a)

    Expose the underlying representation of a selection, this is isomorphic to EitherT.

Instances

Functor f => Bifunctor (SelectionT f) Source #

Bifunctor over unselected (first) and selected (second) values

Methods

bimap :: (a -> b) -> (c -> d) -> SelectionT f a c -> SelectionT f b d #

first :: (a -> b) -> SelectionT f a c -> SelectionT f b c #

second :: (b -> c) -> SelectionT f a b -> SelectionT f a c #

Traversable f => Bitraversable (SelectionT f) Source #

Bitraversable over unselected and selected values respectively

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> SelectionT f a b -> f (SelectionT f c d) #

Foldable f => Bifoldable (SelectionT f) Source #

Bifoldable over unselected and selected values respectively

Methods

bifold :: Monoid m => SelectionT f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> SelectionT f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> SelectionT f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> SelectionT f a b -> c #

Monad f => Monad (SelectionT f b) Source #

SelectionT is a monad over selected items when the underlying m is a Monad

Methods

(>>=) :: SelectionT f b a -> (a -> SelectionT f b b) -> SelectionT f b b #

(>>) :: SelectionT f b a -> SelectionT f b b -> SelectionT f b b #

return :: a -> SelectionT f b a #

fail :: String -> SelectionT f b a #

Functor f => Functor (SelectionT f b) Source # 

Methods

fmap :: (a -> b) -> SelectionT f b a -> SelectionT f b b #

(<$) :: a -> SelectionT f b b -> SelectionT f b a #

Applicative f => Applicative (SelectionT f b) Source # 

Methods

pure :: a -> SelectionT f b a #

(<*>) :: SelectionT f b (a -> b) -> SelectionT f b a -> SelectionT f b b #

(*>) :: SelectionT f b a -> SelectionT f b b -> SelectionT f b b #

(<*) :: SelectionT f b a -> SelectionT f b b -> SelectionT f b a #

Foldable f => Foldable (SelectionT f b) Source # 

Methods

fold :: Monoid m => SelectionT f b m -> m #

foldMap :: Monoid m => (a -> m) -> SelectionT f b a -> m #

foldr :: (a -> b -> b) -> b -> SelectionT f b a -> b #

foldr' :: (a -> b -> b) -> b -> SelectionT f b a -> b #

foldl :: (b -> a -> b) -> b -> SelectionT f b a -> b #

foldl' :: (b -> a -> b) -> b -> SelectionT f b a -> b #

foldr1 :: (a -> a -> a) -> SelectionT f b a -> a #

foldl1 :: (a -> a -> a) -> SelectionT f b a -> a #

toList :: SelectionT f b a -> [a] #

null :: SelectionT f b a -> Bool #

length :: SelectionT f b a -> Int #

elem :: Eq a => a -> SelectionT f b a -> Bool #

maximum :: Ord a => SelectionT f b a -> a #

minimum :: Ord a => SelectionT f b a -> a #

sum :: Num a => SelectionT f b a -> a #

product :: Num a => SelectionT f b a -> a #

Eq (f (Either b a)) => Eq (SelectionT f b a) Source # 

Methods

(==) :: SelectionT f b a -> SelectionT f b a -> Bool #

(/=) :: SelectionT f b a -> SelectionT f b a -> Bool #

Show (f (Either b a)) => Show (SelectionT f b a) Source # 

Methods

showsPrec :: Int -> SelectionT f b a -> ShowS #

show :: SelectionT f b a -> String #

showList :: [SelectionT f b a] -> ShowS #

Selecting/Deselecting

Most selection combinators require that both the selected and unselected types be equal (i.e. SelectionT f a a); this is necessary since items will switch their selection status. Your selected and unselected types may diverge, but you'll need to unify them in order to extract your underlying functor.

newSelection :: Functor f => f a -> SelectionT f () a Source #

Create a selection from a functor by selecting all values

forgetSelection :: Functor f => SelectionT f a a -> f a Source #

Drops selection from your functor returning all values (selected or not).

forgetSelection . newSelection = id

select :: Functor f => (a -> Bool) -> SelectionT f a a -> SelectionT f a a Source #

Clear the selection then select only items which match a predicate.

select f = include f . deselectAll

include :: Functor f => (a -> Bool) -> SelectionT f a a -> SelectionT f a a Source #

Add items which match a predicate to the current selection

include f . select g = select (a -> f a || g a)

exclude :: Functor f => (a -> Bool) -> SelectionT f a a -> SelectionT f a a Source #

Remove items which match a predicate to the current selection

exclude f . select g = select (a -> f a && not (g a))

selectAll :: Functor f => SelectionT f a a -> SelectionT f a a Source #

Select all items in the container

selectAll = include (const True)

deselectAll :: Functor f => SelectionT f a a -> SelectionT f a a Source #

Deselect all items in the container

deselectAll = exclude (const True)

invertSelection :: Functor f => SelectionT f b a -> SelectionT f a b Source #

Flip the selection, all selected are now unselected and vice versa.

onSelected :: Functor f => (a -> c) -> SelectionT f b a -> SelectionT f b c Source #

Map over selected values

onSelected = fmap

onUnselected :: Functor f => (b -> c) -> SelectionT f b a -> SelectionT f c a Source #

Map over unselected values

onSelected = first

getSelected :: Foldable f => SelectionT f b a -> [a] Source #

Collect all selected values into a list. For more complex operations use foldMap.

getSelected = foldMap (:[])

getUnselected :: (Functor f, Foldable f) => SelectionT f b a -> [b] Source #

Collect all unselected values into a list. For more complex operations use operations from Bifoldable.

getUnselected = foldMap (:[]) . invertSelection

Comonad Combinators

selectWithContext :: Comonad w => (w a -> Bool) -> SelectionT w a a -> SelectionT w a a Source #

Select values based on their context within a comonad. This combinator makes its selection by running the predicate using extend.