| Portability | portable | 
|---|---|
| Stability | provisional | 
| Maintainer | John Goerzen <jgoerzen@complete.org> | 
Data.ListLike.Base
Description
Generic operations over list-like structures
Written by John Goerzen, jgoerzen@complete.org
- 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
- 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 whereSource
The class implementing list-like functions.
It is worth noting that types such as Data.Map.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
The empty list
singleton :: item -> fullSource
Creates a single-element list out of an element
cons :: item -> full -> fullSource
Like (:) for lists: adds an element to the beginning of a list
snoc :: full -> item -> fullSource
Adds an element to the *end* of a ListLike. 
append :: full -> full -> fullSource
Combines two lists. Like (++).
Extracts the first element of a ListLike. 
Extracts the last element of a ListLike. 
Gives all elements after the head.
All elements of the list except the last one.  See also inits. 
Tests whether the list is empty.
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 -> fullSource
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 the elements in a list.
intersperse :: item -> full -> fullSource
Add an item between each element in the structure
concat :: (ListLike full' full, Monoid full) => full' -> fullSource
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 -> fullSource
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 -> BoolSource
True if any items satisfy the function
all :: (item -> Bool) -> full -> BoolSource
True if all items satisfy the function
maximum :: Ord item => full -> itemSource
The maximum value of the list
minimum :: Ord item => full -> itemSource
The minimum value of the list
replicate :: Int -> item -> fullSource
Generate a structure with the specified length with every element
    set to the item passed in.  See also genericReplicate 
take :: Int -> full -> fullSource
Takes the first n elements of the list.  See also genericTake. 
drop :: Int -> full -> fullSource
Drops the first n elements of the list.  See also genericDrop 
splitAt :: Int -> full -> (full, full)Source
Equivalent to (.  See also take n xs, drop n xs)genericSplitAt. 
takeWhile :: (item -> Bool) -> full -> fullSource
Returns all elements at start of list that satisfy the function.
dropWhile :: (item -> Bool) -> full -> fullSource
Drops all elements form the start of the list that satisfy the function.
span :: (item -> Bool) -> full -> (full, full)Source
break :: (item -> Bool) -> full -> (full, full)Source
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 -> BoolSource
True when the first list is at the beginning of the second.
isSuffixOf :: Eq item => full -> full -> BoolSource
True when the first list is at the beginning of the second.
isInfixOf :: Eq item => full -> full -> BoolSource
True when the first list is wholly containted within the second
elem :: Eq item => item -> full -> BoolSource
True if the item occurs in the list
notElem :: Eq item => item -> full -> BoolSource
True if the item does not occur in the list
find :: (item -> Bool) -> full -> Maybe itemSource
Take a function and return the first matching element, or Nothing if there is no such element.
filter :: (item -> Bool) -> full -> fullSource
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 -> itemSource
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 IntSource
Returns the index of the element, if it exists.
elemIndices :: (Eq item, ListLike result Int) => item -> full -> resultSource
Returns the indices of the matching elements.  See also 
       findIndices 
findIndex :: (item -> Bool) -> full -> Maybe IntSource
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 -> resultSource
Returns the indices of all elements satisfying the function
sequence :: (Monad m, ListLike fullinp (m item)) => fullinp -> m fullSource
Evaluate each action in the sequence and collect the results
mapM :: (Monad m, ListLike full' item') => (item -> m item') -> full -> m full'Source
rigidMapM :: Monad m => (item -> m item) -> full -> m fullSource
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 ()Source
nub :: Eq item => full -> fullSource
Removes duplicate elements from the list.  See also nubBy 
delete :: Eq item => item -> full -> fullSource
Removes the first instance of the element from the list.
       See also deleteBy 
deleteFirsts :: Eq item => full -> full -> fullSource
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 -> fullSource
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 -> fullSource
List intersection: the set of elements that occur in both lists.
         See also intersectBy 
sort :: Ord item => full -> fullSource
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 -> fullSource
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] -> fullSource
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 -> fullSource
Generic version of nub 
deleteBy :: (item -> item -> Bool) -> item -> full -> fullSource
Generic version of deleteBy 
deleteFirstsBy :: (item -> item -> Bool) -> full -> full -> fullSource
Generic version of deleteFirsts 
unionBy :: (item -> item -> Bool) -> full -> full -> fullSource
Generic version of union 
intersectBy :: (item -> item -> Bool) -> full -> full -> fullSource
Generic version of intersect 
groupBy :: (ListLike full' full, Eq item) => (item -> item -> Bool) -> full -> full'Source
Generic version of group. 
sortBy :: Ord item => (item -> item -> Ordering) -> full -> fullSource
Sort function taking a custom comparison function
insertBy :: Ord item => (item -> item -> Ordering) -> item -> full -> fullSource
Like insert, but with a custom comparison function 
genericLength :: Num a => full -> aSource
Length of the list
genericTake :: Integral a => a -> full -> fullSource
Generic version of take 
genericDrop :: Integral a => a -> full -> fullSource
Generic version of drop 
genericSplitAt :: Integral a => a -> full -> (full, full)Source
Generic version of splitAt 
genericReplicate :: Integral a => a -> item -> fullSource
Generic version of replicate 
class ListLike full item => InfiniteListLike full item | full -> item whereSource
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 -> fullSource
An infinite list of repeated calls of the function to args
An infinite list where each element is the same
Converts a finite list into a circular one
Instances
| InfiniteListLike [a] a | 
zip :: (ListLike full item, ListLike fullb itemb, ListLike result (item, itemb)) => full -> fullb -> resultSource
Takes two lists and returns a list of corresponding pairs.