grouped-list-0.2.1.4: Grouped lists. Equal consecutive elements are grouped.

Safe HaskellNone
LanguageHaskell2010

Data.GroupedList

Contents

Description

Grouped lists are like lists, but internally they are represented as groups of consecutive elements.

For example, the list [1,2,2,3,4,5,5,5] would be internally represented as [[1],[2,2],[3],[4],[5,5,5]]. Use groupedGroups to see this.

Synopsis

Type

data Grouped a Source #

Type of grouped lists. Grouped lists are finite lists that behave well in the abundance of sublists that have all their elements equal.

Instances

Foldable Grouped Source # 

Methods

fold :: Monoid m => Grouped m -> m #

foldMap :: Monoid m => (a -> m) -> Grouped a -> m #

foldr :: (a -> b -> b) -> b -> Grouped a -> b #

foldr' :: (a -> b -> b) -> b -> Grouped a -> b #

foldl :: (b -> a -> b) -> b -> Grouped a -> b #

foldl' :: (b -> a -> b) -> b -> Grouped a -> b #

foldr1 :: (a -> a -> a) -> Grouped a -> a #

foldl1 :: (a -> a -> a) -> Grouped a -> a #

toList :: Grouped a -> [a] #

null :: Grouped a -> Bool #

length :: Grouped a -> Int #

elem :: Eq a => a -> Grouped a -> Bool #

maximum :: Ord a => Grouped a -> a #

minimum :: Ord a => Grouped a -> a #

sum :: Num a => Grouped a -> a #

product :: Num a => Grouped a -> a #

Pointed Grouped Source # 

Methods

point :: a -> Grouped a #

Eq a => IsList (Grouped a) Source #

Method fromList doesn't work for infinite lists. A grouped list cannot be infinite.

Associated Types

type Item (Grouped a) :: * #

Methods

fromList :: [Item (Grouped a)] -> Grouped a #

fromListN :: Int -> [Item (Grouped a)] -> Grouped a #

toList :: Grouped a -> [Item (Grouped a)] #

Eq a => Eq (Grouped a) Source # 

Methods

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

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

Show a => Show (Grouped a) Source # 

Methods

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

show :: Grouped a -> String #

showList :: [Grouped a] -> ShowS #

Eq a => Monoid (Grouped a) Source # 

Methods

mempty :: Grouped a #

mappend :: Grouped a -> Grouped a -> Grouped a #

mconcat :: [Grouped a] -> Grouped a #

NFData a => NFData (Grouped a) Source # 

Methods

rnf :: Grouped a -> () #

type Item (Grouped a) Source # 
type Item (Grouped a) = a

Builders

empty :: Grouped a Source #

Grouped list with no elements.

point :: Pointed p => forall a. a -> p a #

Use point to create a Grouped list with a single element.

concatMap :: Eq b => Grouped a -> (a -> Grouped b) -> Grouped b Source #

Map a function that produces a grouped list for each element in a grouped list, then concat the results.

replicate :: Int -> a -> Grouped a Source #

Replicate a single element the given number of times. If the given number is less or equal to zero, it produces an empty list.

fromGroup :: Group a -> Grouped a Source #

Build a grouped list from a group (see Group).

Info

length :: Foldable t => forall a. t a -> Int #

Returns the size/length of a finite structure as an Int. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.

Indexing

index :: Grouped a -> Int -> Maybe a Source #

Retrieve the element at the given index. If the index is out of the list index range, it returns Nothing.

adjust :: Eq a => (a -> a) -> Int -> Grouped a -> Grouped a Source #

Update the element at the given index. If the index is out of range, the original list is returned.

adjustM :: (Monad m, Eq a) => (a -> m a) -> Int -> Grouped a -> m (Grouped a) Source #

Just like adjust, but the function returns in a Monad.

Sublists

take :: Int -> Grouped a -> Grouped a Source #

Take the given number of elements from the left end of the list.

drop :: Int -> Grouped a -> Grouped a Source #

Discard the given number of elements from the left end of the list.

Mapping

map :: Eq b => (a -> b) -> Grouped a -> Grouped b Source #

Apply a function to every element in a grouped list.

Traversal

traverseGrouped :: (Applicative f, Eq b) => (a -> f b) -> Grouped a -> f (Grouped b) Source #

Apply a function with results residing in an applicative functor to every element in a grouped list.

traverseGroupedByGroup :: (Applicative f, Eq b) => (Group a -> f (Grouped b)) -> Grouped a -> f (Grouped b) Source #

Similar to traverseGrouped, but instead of applying a function to every element of the list, it is applied to groups of consecutive elements. You might return more than one element, so the result is of type Grouped. The results are then concatenated into a single value, embedded in the applicative functor.

traverseGroupedByGroupAccum Source #

Arguments

:: (Monad m, Eq b) 
=> (acc -> Group a -> m (acc, Grouped b)) 
-> acc

Initial value of the accumulator.

-> Grouped a 
-> m (acc, Grouped b) 

Like traverseGroupedByGroup, but carrying an accumulator. Note the Monad constraint instead of Applicative.

Filtering

partition :: Eq a => (a -> Bool) -> Grouped a -> (Grouped a, Grouped a) Source #

Break a grouped list in the elements that match a given condition and those that don't.

filter :: Eq a => (a -> Bool) -> Grouped a -> Grouped a Source #

Filter a grouped list by keeping only those elements that match a given condition.

Sorting

sort :: Ord a => Grouped a -> Grouped a Source #

Sort a grouped list.

Zipping

zipWith :: Eq c => (a -> b -> c) -> Grouped a -> Grouped b -> Grouped c Source #

Combine two lists using a combining function. If one list is longer, remaining elements are discarded.

zip :: (Eq a, Eq b) => Grouped a -> Grouped b -> Grouped (a, b) Source #

Combine two lists in a single list of pairs. If one list is longer, remaining elements are discarded.

List conversion

For to-list conversion use toList.

fromList :: Eq a => [a] -> Grouped a Source #

Build a grouped list from a regular list. It doesn't work if the input list is infinite.

Groups

data Group a Source #

A Group is a non-empty finite list that contains the same element repeated a number of times.

Instances

Monad Group Source # 

Methods

(>>=) :: Group a -> (a -> Group b) -> Group b #

(>>) :: Group a -> Group b -> Group b #

return :: a -> Group a #

fail :: String -> Group a #

Functor Group Source # 

Methods

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

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

Applicative Group Source # 

Methods

pure :: a -> Group a #

(<*>) :: Group (a -> b) -> Group a -> Group b #

(*>) :: Group a -> Group b -> Group b #

(<*) :: Group a -> Group b -> Group a #

Foldable Group Source # 

Methods

fold :: Monoid m => Group m -> m #

foldMap :: Monoid m => (a -> m) -> Group a -> m #

foldr :: (a -> b -> b) -> b -> Group a -> b #

foldr' :: (a -> b -> b) -> b -> Group a -> b #

foldl :: (b -> a -> b) -> b -> Group a -> b #

foldl' :: (b -> a -> b) -> b -> Group a -> b #

foldr1 :: (a -> a -> a) -> Group a -> a #

foldl1 :: (a -> a -> a) -> Group a -> a #

toList :: Group a -> [a] #

null :: Group a -> Bool #

length :: Group a -> Int #

elem :: Eq a => a -> Group a -> Bool #

maximum :: Ord a => Group a -> a #

minimum :: Ord a => Group a -> a #

sum :: Num a => Group a -> a #

product :: Num a => Group a -> a #

Pointed Group Source # 

Methods

point :: a -> Group a #

Eq a => Eq (Group a) Source # 

Methods

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

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

Ord a => Ord (Group a) Source #

A group is larger than other if its constituent element is larger. If they are equal, the group with more elements is the larger.

Methods

compare :: Group a -> Group a -> Ordering #

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

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

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

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

max :: Group a -> Group a -> Group a #

min :: Group a -> Group a -> Group a #

Show a => Show (Group a) Source # 

Methods

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

show :: Group a -> String #

showList :: [Group a] -> ShowS #

NFData a => NFData (Group a) Source # 

Methods

rnf :: Group a -> () #

buildGroup :: Int -> a -> Maybe (Group a) Source #

Build a group by repeating the given element a number of times. If the given number is less or equal to 0, Nothing is returned.

groupElement :: Group a -> a Source #

Get the element of a group.

groupSize :: Group a -> Int Source #

Size of a group.

In grouped lists

groupedGroups :: Grouped a -> [Group a] Source #

Groups of consecutive elements in a grouped list.

firstGroup :: Grouped a -> Maybe (Group a, Grouped a) Source #

Get the first group (if the list is not empty) and the rest of the list.

lastGroup :: Grouped a -> Maybe (Grouped a, Group a) Source #

Get the last group (if the list is not empty) and the rest of the list.