ListLike-1.0.0: Generic support for list-like structuresContentsIndex
Data.ListLike.Base
Portabilityportable
Stabilityprovisional
MaintainerJohn Goerzen <jgoerzen@complete.org>
Description

Generic operations over list-like structures

Written by John Goerzen, jgoerzen@complete.org

Synopsis
class (FoldableLL full item, Monoid full) => ListLike full item | full -> item where
empty :: full
singleton :: item -> full
cons :: item -> full -> full
snoc :: full -> item -> full
append :: full -> full -> full
head :: full -> item
last :: full -> item
tail :: full -> full
init :: full -> full
null :: full -> Bool
length :: full -> Int
map :: ListLike full' item' => (item -> item') -> full -> full'
rigidMap :: (item -> item) -> full -> full
reverse :: full -> full
intersperse :: item -> full -> full
concat :: (ListLike full' full, Monoid full) => full' -> full
concatMap :: ListLike full' item' => (item -> full') -> full -> full'
rigidConcatMap :: (item -> full) -> full -> full
any :: (item -> Bool) -> full -> Bool
all :: (item -> Bool) -> full -> Bool
maximum :: Ord item => full -> item
minimum :: Ord item => full -> item
replicate :: Int -> item -> full
take :: Int -> full -> full
drop :: Int -> full -> full
splitAt :: Int -> full -> (full, full)
takeWhile :: (item -> Bool) -> full -> full
dropWhile :: (item -> Bool) -> full -> full
span :: (item -> Bool) -> full -> (full, full)
break :: (item -> Bool) -> full -> (full, full)
group :: (ListLike full' full, Eq item) => full -> full'
inits :: ListLike full' full => full -> full'
tails :: ListLike full' full => full -> full'
isPrefixOf :: Eq item => full -> full -> Bool
isSuffixOf :: Eq item => full -> full -> Bool
isInfixOf :: Eq item => full -> full -> Bool
elem :: Eq item => item -> full -> Bool
notElem :: Eq item => item -> full -> Bool
find :: (item -> Bool) -> full -> Maybe item
filter :: (item -> Bool) -> full -> full
partition :: (item -> Bool) -> full -> (full, full)
index :: full -> Int -> item
elemIndex :: Eq item => item -> full -> Maybe Int
elemIndices :: (Eq item, ListLike result Int) => item -> full -> result
findIndex :: (item -> Bool) -> full -> Maybe Int
findIndices :: ListLike result Int => (item -> Bool) -> full -> result
sequence :: (Monad m, ListLike fullinp (m item)) => fullinp -> m full
mapM :: (Monad m, ListLike full' item') => (item -> m item') -> full -> m full'
rigidMapM :: Monad m => (item -> m item) -> full -> m full
mapM_ :: Monad m => (item -> m b) -> full -> m ()
nub :: Eq item => full -> full
delete :: Eq item => item -> full -> full
deleteFirsts :: Eq item => full -> full -> full
union :: Eq item => full -> full -> full
intersect :: Eq item => full -> full -> full
sort :: Ord item => full -> full
insert :: Ord item => item -> full -> full
toList :: full -> [item]
fromList :: [item] -> full
fromListLike :: ListLike full' item => full -> full'
nubBy :: (item -> item -> Bool) -> full -> full
deleteBy :: (item -> item -> Bool) -> item -> full -> full
deleteFirstsBy :: (item -> item -> Bool) -> full -> full -> full
unionBy :: (item -> item -> Bool) -> full -> full -> full
intersectBy :: (item -> item -> Bool) -> full -> full -> full
groupBy :: (ListLike full' full, Eq item) => (item -> item -> Bool) -> full -> full'
sortBy :: Ord item => (item -> item -> Ordering) -> full -> full
insertBy :: Ord item => (item -> item -> Ordering) -> item -> full -> full
genericLength :: Num a => full -> a
genericTake :: Integral a => a -> full -> full
genericDrop :: Integral a => a -> full -> full
genericSplitAt :: Integral a => a -> full -> (full, full)
genericReplicate :: Integral a => a -> item -> full
class ListLike full item => InfiniteListLike full item | full -> item where
iterate :: (item -> item) -> item -> full
repeat :: item -> full
cycle :: full -> full
zip :: (ListLike full item, ListLike fullb itemb, ListLike result (item, itemb)) => full -> fullb -> result
zipWith :: (ListLike full item, ListLike fullb itemb, ListLike result resultitem) => (item -> itemb -> resultitem) -> full -> fullb -> result
sequence_ :: (Monad m, ListLike mfull (m item)) => mfull -> m ()
Documentation
class (FoldableLL full item, Monoid full) => ListLike full item | full -> item where

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
Methods
empty :: full
The empty list
singleton :: item -> full
Creates a single-itement list out of an itement
cons :: item -> full -> full
Like (:) for lists: adds an itement to the beginning of a list
snoc :: full -> item -> full
Adds an itement to the *end* of a ListLike.
append :: full -> full -> full
Combines two lists. Like (++).
head :: full -> item
Extracts the first itement of a ListLike.
last :: full -> item
Extracts the last itement of a ListLike.
tail :: full -> full
Gives all itements after the head.
init :: full -> full
All elements of the list except the last one. See also inits.
null :: full -> Bool
Tests whether the list is empty.
length :: full -> Int
Length of the list. See also genericLength.
map :: ListLike full' item' => (item -> item') -> full -> full'
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
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
Reverse the elements in a list.
intersperse :: item -> full -> full
Add an item between each element in the structure
concat :: (ListLike full' full, Monoid full) => full' -> full
Flatten the structure.
concatMap :: ListLike full' item' => (item -> full') -> full -> full'
Map a function over the items and concatenate the results. See also rigidConcatMap.
rigidConcatMap :: (item -> full) -> full -> full
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
True if any items satisfy the function
all :: (item -> Bool) -> full -> Bool
True if all items satisfy the function
maximum :: Ord item => full -> item
The maximum value of the list
minimum :: Ord item => full -> item
The minimum value of the list
replicate :: Int -> item -> full
Generate a structure with the specified length with every element set to the item passed in. See also genericReplicate
take :: Int -> full -> full
Takes the first n elements of the list. See also genericTake.
drop :: Int -> full -> full
Drops the first n elements of the list. See also genericDrop
splitAt :: Int -> full -> (full, full)
Equivalent to (take n xs, drop n xs). See also genericSplitAt.
takeWhile :: (item -> Bool) -> full -> full
Returns all elements at start of list that satisfy the function.
dropWhile :: (item -> Bool) -> full -> full
Drops all elements form the start of the list that satisfy the function.
span :: (item -> Bool) -> full -> (full, full)
The equivalent of (takeWhile f xs, dropWhile f xs)
break :: (item -> Bool) -> full -> (full, full)
The equivalent of span (not . f)
group :: (ListLike full' full, Eq item) => full -> full'
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'
All initial segments of the list, shortest first
tails :: ListLike full' full => full -> full'
All final segnemts, longest first
isPrefixOf :: Eq item => full -> full -> Bool
True when the first list is at the beginning of the second.
isSuffixOf :: Eq item => full -> full -> Bool
True when the first list is at the beginning of the second.
isInfixOf :: Eq item => full -> full -> Bool
True when the first list is wholly containted within the second
elem :: Eq item => item -> full -> Bool
True if the item occurs in the list
notElem :: Eq item => item -> full -> Bool
True if the item does not occur in the list
find :: (item -> Bool) -> full -> Maybe item
Take a function and return the first matching element, or Nothing if there is no such element.
filter :: (item -> Bool) -> full -> full
Returns only the elements that satisfy the function.
partition :: (item -> Bool) -> full -> (full, full)
Returns the lists that do and do not satisfy the function. Same as (filter p xs, filter (not . p) xs)
index :: full -> Int -> item
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
Returns the index of the element, if it exists.
elemIndices :: (Eq item, ListLike result Int) => item -> full -> result
Returns the indices of the matching elements. See also findIndices
findIndex :: (item -> Bool) -> full -> Maybe Int
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
Returns the indices of all elements satisfying the function
sequence :: (Monad m, ListLike fullinp (m item)) => fullinp -> m full
Evaluate each action in the sequence and collect the results
mapM :: (Monad m, ListLike full' item') => (item -> m item') -> full -> m full'

A map in monad space. Same as sequence . map

See also rigidMapM

rigidMapM :: Monad m => (item -> m item) -> full -> m full
Like mapM, but without the possibility of changing the type of the item. This can have performance benefits with some types.
mapM_ :: Monad m => (item -> m b) -> full -> m ()
A map in monad space, discarding results. Same as sequence_ . map
nub :: Eq item => full -> full
Removes duplicate elements from the list. See also nubBy
delete :: Eq item => item -> full -> full
Removes the first instance of the element from the list. See also deleteBy
deleteFirsts :: Eq item => full -> full -> full
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
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
List intersection: the set of elements that occur in both lists. See also intersectBy
sort :: Ord item => full -> full
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
Inserts the itement at the last place where it is still less than or equal to the next itement. 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]
Converts the structure to a list. This is logically equivolent to fromListLike, but may have a more optimized implementation.
fromList :: [item] -> full
Generates the structure from a list.
fromListLike :: ListLike full' item => full -> full'
Converts one ListLike to another. See also toList. Default implementation is fromListLike = map id
nubBy :: (item -> item -> Bool) -> full -> full
Generic version of nub
deleteBy :: (item -> item -> Bool) -> item -> full -> full
Generic version of deleteBy
deleteFirstsBy :: (item -> item -> Bool) -> full -> full -> full
Generic version of deleteFirsts
unionBy :: (item -> item -> Bool) -> full -> full -> full
Generic version of union
intersectBy :: (item -> item -> Bool) -> full -> full -> full
Generic version of intersect
groupBy :: (ListLike full' full, Eq item) => (item -> item -> Bool) -> full -> full'
Generic version of group.
sortBy :: Ord item => (item -> item -> Ordering) -> full -> full
Sort function taking a custom comparison function
insertBy :: Ord item => (item -> item -> Ordering) -> item -> full -> full
Like insert, but with a custom comparison function
genericLength :: Num a => full -> a
Length of the list
genericTake :: Integral a => a -> full -> full
Generic version of take
genericDrop :: Integral a => a -> full -> full
Generic version of drop
genericSplitAt :: Integral a => a -> full -> (full, full)
Generic version of splitAt
genericReplicate :: Integral a => a -> item -> full
Generic version of replicate
show/hide Instances
ListLike ByteString Word8
ListLike ByteString Word8
ListLike [a] a
(Integral i, Ix i) => ListLike (Array i e) e
(Ord key, Eq val) => ListLike (Map key val) (key, val)
class ListLike full item => InfiniteListLike full item | full -> item where
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.
Methods
iterate :: (item -> item) -> item -> full
An infinite list of repeated calls of the function to args
repeat :: item -> full
An infinite list where each element is the same
cycle :: full -> full
Converts a finite list into a circular one
show/hide Instances
zip :: (ListLike full item, ListLike fullb itemb, ListLike result (item, itemb)) => full -> fullb -> result
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
Takes two lists and combines them with a custom combining function
sequence_ :: (Monad m, ListLike mfull (m item)) => mfull -> m ()
Evaluate each action, ignoring the results
Produced by Haddock version 0.8