ListLike-4.2.1: Generic support for list-like structures

CopyrightCopyright (C) 2007 John Goerzen
LicenseBSD3
MaintainerJohn Lato <jwlato@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.ListLike.Base

Description

Generic operations over list-like structures

Written by John Goerzen, jgoerzen@complete.org

Synopsis

Documentation

class (FoldableLL full item, Monoid full) => ListLike full item | full -> item where Source

The class implementing list-like functions.

It is worth noting that types such as Map can be instances of ListLike. Due to their specific ways of operating, they may not behave in the expected way in some cases. For instance, cons may not increase the size of a map if the key you have given is already in the map; it will just replace the value already there.

Implementators must define at least:

  • singleton
  • head
  • tail
  • null or genericLength

Minimal complete definition

singleton, head, tail

Methods

empty :: full Source

The empty list

singleton :: item -> full Source

Creates a single-element list out of an element

cons :: item -> full -> full Source

Like (:) for lists: adds an element to the beginning of a list

snoc :: full -> item -> full Source

Adds an element to the *end* of a ListLike.

append :: full -> full -> full Source

Combines two lists. Like (++).

head :: full -> item Source

Extracts the first element of a ListLike.

last :: full -> item Source

Extracts the last element of a ListLike.

tail :: full -> full Source

Gives all elements after the head.

init :: full -> full Source

All elements of the list except the last one. See also inits.

null :: full -> Bool Source

Tests whether the list is empty.

length :: full -> Int Source

Length of the list. See also genericLength.

map :: ListLike full' item' => (item -> item') -> full -> full' Source

Apply a function to each element, returning any other valid ListLike. rigidMap will always be at least as fast, if not faster, than this function and is recommended if it will work for your purposes. See also mapM.

rigidMap :: (item -> item) -> full -> full Source

Like map, but without the possibility of changing the type of the item. This can have performance benefits for things such as ByteStrings, since it will let the ByteString use its native low-level map implementation.

reverse :: full -> full Source

Reverse the elements in a list.

intersperse :: item -> full -> full Source

Add an item between each element in the structure

concat :: (ListLike full' full, Monoid full) => full' -> full Source

Flatten the structure.

concatMap :: ListLike full' item' => (item -> full') -> full -> full' Source

Map a function over the items and concatenate the results. See also rigidConcatMap.

rigidConcatMap :: (item -> full) -> full -> full Source

Like concatMap, but without the possibility of changing the type of the item. This can have performance benefits for some things such as ByteString.

any :: (item -> Bool) -> full -> Bool Source

True if any items satisfy the function

all :: (item -> Bool) -> full -> Bool Source

True if all items satisfy the function

maximum :: Ord item => full -> item Source

The maximum value of the list

minimum :: Ord item => full -> item Source

The minimum value of the list

replicate :: Int -> item -> full Source

Generate a structure with the specified length with every element set to the item passed in. See also genericReplicate

take :: Int -> full -> full Source

Takes the first n elements of the list. See also genericTake.

drop :: Int -> full -> full Source

Drops the first n elements of the list. See also genericDrop

splitAt :: Int -> full -> (full, full) Source

Equivalent to (take n xs, drop n xs). See also genericSplitAt.

takeWhile :: (item -> Bool) -> full -> full Source

Returns all elements at start of list that satisfy the function.

dropWhile :: (item -> Bool) -> full -> full Source

Drops all elements from the start of the list that satisfy the function.

dropWhileEnd :: (item -> Bool) -> full -> full Source

Drops all elements from the end of the list that satisfy the function.

span :: (item -> Bool) -> full -> (full, full) Source

The equivalent of (takeWhile f xs, dropWhile f xs)

break :: (item -> Bool) -> full -> (full, full) Source

The equivalent of span (not . f)

group :: (ListLike full' full, Eq item) => full -> full' Source

Split a list into sublists, each which contains equal arguments. For order-preserving types, concatenating these sublists will produce the original list. See also groupBy.

inits :: ListLike full' full => full -> full' Source

All initial segments of the list, shortest first

tails :: ListLike full' full => full -> full' Source

All final segnemts, longest first

isPrefixOf :: Eq item => full -> full -> Bool Source

True when the first list is at the beginning of the second.

isSuffixOf :: Eq item => full -> full -> Bool Source

True when the first list is at the beginning of the second.

isInfixOf :: Eq item => full -> full -> Bool Source

True when the first list is wholly containted within the second

elem :: Eq item => item -> full -> Bool Source

True if the item occurs in the list

notElem :: Eq item => item -> full -> Bool Source

True if the item does not occur in the list

find :: (item -> Bool) -> full -> Maybe item Source

Take a function and return the first matching element, or Nothing if there is no such element.

filter :: (item -> Bool) -> full -> full Source

Returns only the elements that satisfy the function.

partition :: (item -> Bool) -> full -> (full, full) Source

Returns the lists that do and do not satisfy the function. Same as (filter p xs, filter (not . p) xs)

index :: full -> Int -> item Source

The element at 0-based index i. Raises an exception if i is out of bounds. Like (!!) for lists.

elemIndex :: Eq item => item -> full -> Maybe Int Source

Returns the index of the element, if it exists.

elemIndices :: (Eq item, ListLike result Int) => item -> full -> result Source

Returns the indices of the matching elements. See also findIndices

findIndex :: (item -> Bool) -> full -> Maybe Int Source

Take a function and return the index of the first matching element, or Nothing if no element matches

findIndices :: ListLike result Int => (item -> Bool) -> full -> result Source

Returns the indices of all elements satisfying the function

sequence :: (Monad m, ListLike fullinp (m item)) => fullinp -> m full Source

Evaluate each action in the sequence and collect the results

mapM :: (Monad m, ListLike full' item') => (item -> m item') -> full -> m full' Source

A map in monad space. Same as sequence . map

See also rigidMapM

rigidMapM :: Monad m => (item -> m item) -> full -> m full Source

Like mapM, but without the possibility of changing the type of the item. This can have performance benefits with some types.

nub :: Eq item => full -> full Source

Removes duplicate elements from the list. See also nubBy

delete :: Eq item => item -> full -> full Source

Removes the first instance of the element from the list. See also deleteBy

deleteFirsts :: Eq item => full -> full -> full Source

List difference. Removes from the first list the first instance of each element of the second list. See '(\)' and deleteFirstsBy

union :: Eq item => full -> full -> full Source

List union: the set of elements that occur in either list. Duplicate elements in the first list will remain duplicate. See also unionBy.

intersect :: Eq item => full -> full -> full Source

List intersection: the set of elements that occur in both lists. See also intersectBy

sort :: Ord item => full -> full Source

Sorts the list. On data types that do not preserve ordering, or enforce their own ordering, the result may not be what you expect. See also sortBy.

insert :: Ord item => item -> full -> full Source

Inserts the element at the last place where it is still less than or equal to the next element. On data types that do not preserve ordering, or enforce their own ordering, the result may not be what you expect. On types such as maps, this may result in changing an existing item. See also insertBy.

toList :: full -> [item] Source

Converts the structure to a list. This is logically equivolent to fromListLike, but may have a more optimized implementation.

fromList :: [item] -> full Source

Generates the structure from a list.

fromListLike :: ListLike full' item => full -> full' Source

Converts one ListLike to another. See also toList. Default implementation is fromListLike = map id

nubBy :: (item -> item -> Bool) -> full -> full Source

Generic version of nub

deleteBy :: (item -> item -> Bool) -> item -> full -> full Source

Generic version of deleteBy

deleteFirstsBy :: (item -> item -> Bool) -> full -> full -> full Source

Generic version of deleteFirsts

unionBy :: (item -> item -> Bool) -> full -> full -> full Source

Generic version of union

intersectBy :: (item -> item -> Bool) -> full -> full -> full Source

Generic version of intersect

groupBy :: (ListLike full' full, Eq item) => (item -> item -> Bool) -> full -> full' Source

Generic version of group.

sortBy :: (item -> item -> Ordering) -> full -> full Source

Sort function taking a custom comparison function

insertBy :: (item -> item -> Ordering) -> item -> full -> full Source

Like insert, but with a custom comparison function

genericLength :: Num a => full -> a Source

Length of the list

genericTake :: Integral a => a -> full -> full Source

Generic version of take

genericDrop :: Integral a => a -> full -> full Source

Generic version of drop

genericSplitAt :: Integral a => a -> full -> (full, full) Source

Generic version of splitAt

genericReplicate :: Integral a => a -> item -> full Source

Generic version of replicate

class ListLike full item => InfiniteListLike full item | full -> item where Source

An extension to ListLike for those data types that are capable of dealing with infinite lists. Some ListLike functions are capable of working with finite or infinite lists. The functions here require infinite list capability in order to work at all.

Minimal complete definition

Nothing

Methods

iterate :: (item -> item) -> item -> full Source

An infinite list of repeated calls of the function to args

repeat :: item -> full Source

An infinite list where each element is the same

cycle :: full -> full Source

Converts a finite list into a circular one

zip :: (ListLike full item, ListLike fullb itemb, ListLike result (item, itemb)) => full -> fullb -> result Source

Takes two lists and returns a list of corresponding pairs.

zipWith :: (ListLike full item, ListLike fullb itemb, ListLike result resultitem) => (item -> itemb -> resultitem) -> full -> fullb -> result Source

Takes two lists and combines them with a custom combining function

sequence_ :: (Monad m, FoldableLL full (m item)) => full -> m () Source

Evaluate each action, ignoring the results. Same as mapM_ id.