selections-0.3.0.0: Combinators for operating with selections over an underlying functor
Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Selection

Synopsis

Selection

newtype Selection f b a Source #

A selection wraps a Functor f and has an unselected type b and a selected type a

Constructors

Selection 

Fields

Instances

Instances details
Traversable f => Bitraversable (Selection f) Source #

Bitraversable over unselected and selected values respectively

Instance details

Defined in Data.Functor.Selection

Methods

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

Foldable f => Bifoldable (Selection f) Source #

Bifoldable over unselected and selected values respectively

Instance details

Defined in Data.Functor.Selection

Methods

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

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

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

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

Functor f => Bifunctor (Selection f) Source #

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

Instance details

Defined in Data.Functor.Selection

Methods

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

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

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

Monad m => Monad (Selection m b) Source #

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

Instance details

Defined in Data.Functor.Selection

Methods

(>>=) :: Selection m b a -> (a -> Selection m b b0) -> Selection m b b0 #

(>>) :: Selection m b a -> Selection m b b0 -> Selection m b b0 #

return :: a -> Selection m b a #

Functor f => Functor (Selection f b) Source # 
Instance details

Defined in Data.Functor.Selection

Methods

fmap :: (a -> b0) -> Selection f b a -> Selection f b b0 #

(<$) :: a -> Selection f b b0 -> Selection f b a #

Monad m => Applicative (Selection m b) Source # 
Instance details

Defined in Data.Functor.Selection

Methods

pure :: a -> Selection m b a #

(<*>) :: Selection m b (a -> b0) -> Selection m b a -> Selection m b b0 #

liftA2 :: (a -> b0 -> c) -> Selection m b a -> Selection m b b0 -> Selection m b c #

(*>) :: Selection m b a -> Selection m b b0 -> Selection m b b0 #

(<*) :: Selection m b a -> Selection m b b0 -> Selection m b a #

Foldable f => Foldable (Selection f b) Source # 
Instance details

Defined in Data.Functor.Selection

Methods

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

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

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

foldr :: (a -> b0 -> b0) -> b0 -> Selection f b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> Selection f b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> Selection f b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> Selection f b a -> b0 #

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

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

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

null :: Selection f b a -> Bool #

length :: Selection f b a -> Int #

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

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

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

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

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

Traversable f => Traversable (Selection f b) Source # 
Instance details

Defined in Data.Functor.Selection

Methods

traverse :: Applicative f0 => (a -> f0 b0) -> Selection f b a -> f0 (Selection f b b0) #

sequenceA :: Applicative f0 => Selection f b (f0 a) -> f0 (Selection f b a) #

mapM :: Monad m => (a -> m b0) -> Selection f b a -> m (Selection f b b0) #

sequence :: Monad m => Selection f b (m a) -> m (Selection f b a) #

Eq (f (Either b a)) => Eq (Selection f b a) Source # 
Instance details

Defined in Data.Functor.Selection

Methods

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

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

Show (f (Either b a)) => Show (Selection f b a) Source # 
Instance details

Defined in Data.Functor.Selection

Methods

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

show :: Selection f b a -> String #

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

type Selection' f a = Selection f a a Source #

A type alias for selections with the same unselected/selected types

withUnwrapped :: Functor f => (f (Either b a) -> g (Either d c)) -> Selection f b a -> Selection g d c Source #

Modify the underlying representation of a selection

A powerful and low-level way to transform your selection

Selecting/Deselecting

Most selection combinators require that both the selected and unselected types be equal (i.e. Selection 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 -> Selection f b a Source #

Create a selection from a functor by selecting all values

runSelection :: Functor f => Selection f a a -> f a Source #

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

forgetSelection . newSelection = id
forgetSelection = unify id id

select :: Functor f => (a -> Bool) -> Selection f a a -> Selection 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) -> Selection f a a -> Selection 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) -> Selection f a a -> Selection 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 => Selection f a a -> Selection f b a Source #

Select all items in the container

selectAll = include (const True)

deselectAll :: Functor f => Selection f b b -> Selection f b a Source #

Deselect all items in the container

deselectAll = exclude (const True)

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

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

mapSelected :: Functor f => (a -> c) -> Selection f b a -> Selection f b c Source #

Map over selected values

mapSelected = fmap

mapUnselected :: Functor f => (b -> c) -> Selection f b a -> Selection f c a Source #

Map over unselected values

mapUnselected = first

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

Collect all selected values into a list.

getSelected = toList

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

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

getUnselected = getSelected . invertSelection

unify :: Functor f => (b -> c) -> (a -> c) -> Selection f b a -> f c Source #

Unify selected and unselected and forget the selection

unify f g == forgetSelection . onUnselected f . onSelected g

hoist :: Functor f => (forall c. f c -> g c) -> Selection f b a -> Selection g b a Source #

Perform a natural transformation over the underlying container of a selectable