ListLike-1.0.0: Generic support for list-like structuresContentsIndex
Data.ListLike
Portabilityportable
Stabilityprovisional
MaintainerJohn Goerzen <jgoerzen@complete.org>
Contents
Introduction
Creation & Basic Functions
List transformations
Conversions
Reducing lists (folds), from FoldableLL
Special folds
Building lists
Scans
Accumulating maps
Infinite lists
Unfolding
Sublists
Extracting sublists
Predicates
Searching lists
Searching by equality
Searching with a predicate
Indexing lists
Zipping and unzipping lists
Monadic Operations
Input and Output
Special lists
Strings
"Set" operations
Ordered lists
Generalized functions
The "By" operations
User-supplied equality (replacing an Eq context)
User-supplied comparison (replacing an Ord context)
The "generic" operations
Notes on specific instances
Lists
Arrays
Maps
ByteStrings
Base Typeclasses
The ListLike class
The FoldableLL class
The StringLike class
The InfiniteListLike class
Description

Generic operations over list-like structures

Written by John Goerzen, jgoerzen@complete.org

Please start with the introduction at Data.ListLike#intro.

Synopsis
empty :: ListLike full item => full
singleton :: ListLike full item => item -> full
cons :: ListLike full item => item -> full -> full
snoc :: ListLike full item => full -> item -> full
append :: ListLike full item => full -> full -> full
head :: ListLike full item => full -> item
last :: ListLike full item => full -> item
tail :: ListLike full item => full -> full
init :: ListLike full item => full -> full
null :: ListLike full item => full -> Bool
length :: ListLike full item => full -> Int
map :: (ListLike full item, ListLike full' item') => (item -> item') -> full -> full'
rigidMap :: ListLike full item => (item -> item) -> full -> full
reverse :: ListLike full item => full -> full
intersperse :: ListLike full item => item -> full -> full
toList :: ListLike full item => full -> [item]
fromList :: ListLike full item => [item] -> full
fromListLike :: (ListLike full item, ListLike full' item) => full -> full'
foldl :: FoldableLL full item => (a -> item -> a) -> a -> full -> a
foldl' :: FoldableLL full item => (a -> item -> a) -> a -> full -> a
foldl1 :: FoldableLL full item => (item -> item -> item) -> full -> item
foldr :: FoldableLL full item => (item -> b -> b) -> b -> full -> b
foldr' :: FoldableLL full item => (item -> b -> b) -> b -> full -> b
foldr1 :: FoldableLL full item => (item -> item -> item) -> full -> item
concat :: (ListLike full item, ListLike full' full, Monoid full) => full' -> full
concatMap :: (ListLike full item, ListLike full' item') => (item -> full') -> full -> full'
rigidConcatMap :: ListLike full item => (item -> full) -> full -> full
and :: ListLike full Bool => full -> Bool
or :: ListLike full Bool => full -> Bool
any :: ListLike full item => (item -> Bool) -> full -> Bool
all :: ListLike full item => (item -> Bool) -> full -> Bool
sum :: (Num a, ListLike full a) => full -> a
product :: (Num a, ListLike full a) => full -> a
maximum :: (ListLike full item, Ord item) => full -> item
minimum :: (ListLike full item, Ord item) => full -> item
fold :: (FoldableLL full item, Monoid item) => full -> item
foldMap :: (FoldableLL full item, Monoid m) => (item -> m) -> full -> m
iterate :: InfiniteListLike full item => (item -> item) -> item -> full
repeat :: InfiniteListLike full item => item -> full
replicate :: ListLike full item => Int -> item -> full
cycle :: InfiniteListLike full item => full -> full
take :: ListLike full item => Int -> full -> full
drop :: ListLike full item => Int -> full -> full
splitAt :: ListLike full item => Int -> full -> (full, full)
takeWhile :: ListLike full item => (item -> Bool) -> full -> full
dropWhile :: ListLike full item => (item -> Bool) -> full -> full
span :: ListLike full item => (item -> Bool) -> full -> (full, full)
break :: ListLike full item => (item -> Bool) -> full -> (full, full)
group :: (ListLike full item, ListLike full' full, Eq item) => full -> full'
inits :: (ListLike full item, ListLike full' full) => full -> full'
tails :: (ListLike full item, ListLike full' full) => full -> full'
isPrefixOf :: (ListLike full item, Eq item) => full -> full -> Bool
isSuffixOf :: (ListLike full item, Eq item) => full -> full -> Bool
isInfixOf :: (ListLike full item, Eq item) => full -> full -> Bool
elem :: (ListLike full item, Eq item) => item -> full -> Bool
notElem :: (ListLike full item, Eq item) => item -> full -> Bool
find :: ListLike full item => (item -> Bool) -> full -> Maybe item
filter :: ListLike full item => (item -> Bool) -> full -> full
partition :: ListLike full item => (item -> Bool) -> full -> (full, full)
index :: ListLike full item => full -> Int -> item
elemIndex :: (ListLike full item, Eq item) => item -> full -> Maybe Int
elemIndices :: (ListLike full item, Eq item, ListLike result Int) => item -> full -> result
findIndex :: ListLike full item => (item -> Bool) -> full -> Maybe Int
findIndices :: (ListLike full item, ListLike result Int) => (item -> Bool) -> full -> result
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
unzip :: (ListLike full (itema, itemb), ListLike ra itema, ListLike rb itemb) => full -> (ra, rb)
sequence :: (ListLike full item, Monad m, ListLike fullinp (m item)) => fullinp -> m full
sequence_ :: (Monad m, ListLike mfull (m item)) => mfull -> m ()
mapM :: (ListLike full item, Monad m, ListLike full' item') => (item -> m item') -> full -> m full'
rigidMapM :: (ListLike full item, Monad m) => (item -> m item) -> full -> m full
mapM_ :: (ListLike full item, Monad m) => (item -> m b) -> full -> m ()
class ListLike full item => ListLikeIO full item | full -> item where
hGetLine :: Handle -> IO full
hGetContents :: Handle -> IO full
hGet :: Handle -> Int -> IO full
hGetNonBlocking :: Handle -> Int -> IO full
hPutStr :: Handle -> full -> IO ()
hPutStrLn :: Handle -> full -> IO ()
getLine :: IO full
getContents :: IO full
putStr :: full -> IO ()
putStrLn :: full -> IO ()
interact :: (full -> full) -> IO ()
readFile :: FilePath -> IO full
writeFile :: FilePath -> full -> IO ()
appendFile :: FilePath -> full -> IO ()
toString :: StringLike s => s -> String
fromString :: StringLike s => String -> s
lines :: (StringLike s, ListLike full s) => s -> full
words :: (StringLike s, ListLike full s) => s -> full
nub :: (ListLike full item, Eq item) => full -> full
delete :: (ListLike full item, Eq item) => item -> full -> full
deleteFirsts :: (ListLike full item, Eq item) => full -> full -> full
union :: (ListLike full item, Eq item) => full -> full -> full
intersect :: (ListLike full item, Eq item) => full -> full -> full
sort :: (ListLike full item, Ord item) => full -> full
insert :: (ListLike full item, Ord item) => item -> full -> full
nubBy :: ListLike full item => (item -> item -> Bool) -> full -> full
deleteBy :: ListLike full item => (item -> item -> Bool) -> item -> full -> full
deleteFirstsBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full
unionBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full
intersectBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full
groupBy :: (ListLike full item, ListLike full' full, Eq item) => (item -> item -> Bool) -> full -> full'
sortBy :: (ListLike full item, Ord item) => (item -> item -> Ordering) -> full -> full
insertBy :: (ListLike full item, Ord item) => (item -> item -> Ordering) -> item -> full -> full
genericLength :: (ListLike full item, Num a) => full -> a
genericTake :: (ListLike full item, Integral a) => a -> full -> full
genericDrop :: (ListLike full item, Integral a) => a -> full -> full
genericSplitAt :: (ListLike full item, Integral a) => a -> full -> (full, full)
genericReplicate :: (ListLike full item, Integral a) => a -> item -> full
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 FoldableLL full item | full -> item where
foldl :: (a -> item -> a) -> a -> full -> a
foldl' :: (a -> item -> a) -> a -> full -> a
foldl1 :: (item -> item -> item) -> full -> item
foldr :: (item -> b -> b) -> b -> full -> b
foldr' :: (item -> b -> b) -> b -> full -> b
foldr1 :: (item -> item -> item) -> full -> item
class StringLike s where
toString :: s -> String
fromString :: String -> s
lines :: ListLike full s => s -> full
words :: ListLike full s => s -> full
class ListLike full item => InfiniteListLike full item | full -> item where
iterate :: (item -> item) -> item -> full
repeat :: item -> full
cycle :: full -> full
Introduction

Welcome to ListLike.

This module provides abstractions over typical list operations. It is designed to let you freely interchange different ways to represent sequences of data. It works with lists, various types of ByteStrings, and much more.

In this module, you'll find generic versions of most of the functions you're used to using in the Prelude, Data.List, and System.IO. They carry the same names, too. Therefore, you'll want to be careful how you import the module. I suggest using:

import qualified ListLike as LL

Then, you can use LL.fold, LL.map, etc. to get the generic version of the functions you want. Alternatively, you can hide the other versions from Prelude and import specific generic functions from here, such as:

import Prelude hiding (map)
import ListLike (map)

The I/O features of ListLike may a The module Data.ListLike actually simply re-exports the items found in a number of its sub-modules. If you want a smaller subset of Data.ListLike, look at the documentation for its sub-modules and import the relevant one.

In most cases, functions here can act as drop-in replacements for their list-specific counterparts. They will use the same underlying implementations for lists, so there should be no performance difference.

You can make your own types instances of ListLike as well. For more details, see the notes for the ListLike typeclass.

Creation & Basic Functions
empty :: ListLike full item => full
The empty list
singleton :: ListLike full item => item -> full
Creates a single-itement list out of an itement
cons :: ListLike full item => item -> full -> full
Like (:) for lists: adds an itement to the beginning of a list
snoc :: ListLike full item => full -> item -> full
Adds an itement to the *end* of a ListLike.
append :: ListLike full item => full -> full -> full
Combines two lists. Like (++).
head :: ListLike full item => full -> item
Extracts the first itement of a ListLike.
last :: ListLike full item => full -> item
Extracts the last itement of a ListLike.
tail :: ListLike full item => full -> full
Gives all itements after the head.
init :: ListLike full item => full -> full
All elements of the list except the last one. See also inits.
null :: ListLike full item => full -> Bool
Tests whether the list is empty.
length :: ListLike full item => full -> Int
Length of the list. See also genericLength.
List transformations
map :: (ListLike full item, 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 :: ListLike full item => (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 :: ListLike full item => full -> full
Reverse the elements in a list.
intersperse :: ListLike full item => item -> full -> full
Add an item between each element in the structure
Conversions
toList :: ListLike full item => full -> [item]
Converts the structure to a list. This is logically equivolent to fromListLike, but may have a more optimized implementation.
fromList :: ListLike full item => [item] -> full
Generates the structure from a list.
fromListLike :: (ListLike full item, ListLike full' item) => full -> full'
Converts one ListLike to another. See also toList. Default implementation is fromListLike = map id
Reducing lists (folds), from FoldableLL
foldl :: FoldableLL full item => (a -> item -> a) -> a -> full -> a
Left-associative fold
foldl' :: FoldableLL full item => (a -> item -> a) -> a -> full -> a
Strict version of foldl.
foldl1 :: FoldableLL full item => (item -> item -> item) -> full -> item
A variant of foldl with no base case. Requires at least 1 list element.
foldr :: FoldableLL full item => (item -> b -> b) -> b -> full -> b
Right-associative fold
foldr' :: FoldableLL full item => (item -> b -> b) -> b -> full -> b
Strict version of foldr
foldr1 :: FoldableLL full item => (item -> item -> item) -> full -> item
Like foldr, but with no starting value
Special folds
concat :: (ListLike full item, ListLike full' full, Monoid full) => full' -> full
Flatten the structure.
concatMap :: (ListLike full item, ListLike full' item') => (item -> full') -> full -> full'
Map a function over the items and concatenate the results. See also rigidConcatMap.
rigidConcatMap :: ListLike full item => (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.
and :: ListLike full Bool => full -> Bool
Returns True if all elements are True
or :: ListLike full Bool => full -> Bool
Returns True if any element is True
any :: ListLike full item => (item -> Bool) -> full -> Bool
True if any items satisfy the function
all :: ListLike full item => (item -> Bool) -> full -> Bool
True if all items satisfy the function
sum :: (Num a, ListLike full a) => full -> a
The sum of the list
product :: (Num a, ListLike full a) => full -> a
The product of the list
maximum :: (ListLike full item, Ord item) => full -> item
The maximum value of the list
minimum :: (ListLike full item, Ord item) => full -> item
The minimum value of the list
fold :: (FoldableLL full item, Monoid item) => full -> item
Combine the elements of a structure using a monoid. fold = foldMap id
foldMap :: (FoldableLL full item, Monoid m) => (item -> m) -> full -> m
Map each element to a monoid, then combine the results
Building lists
Scans
Accumulating maps
Infinite lists
iterate :: InfiniteListLike full item => (item -> item) -> item -> full
An infinite list of repeated calls of the function to args
repeat :: InfiniteListLike full item => item -> full
An infinite list where each element is the same
replicate :: ListLike full item => Int -> item -> full
Generate a structure with the specified length with every element set to the item passed in. See also genericReplicate
cycle :: InfiniteListLike full item => full -> full
Converts a finite list into a circular one
Unfolding
Sublists
Extracting sublists
take :: ListLike full item => Int -> full -> full
Takes the first n elements of the list. See also genericTake.
drop :: ListLike full item => Int -> full -> full
Drops the first n elements of the list. See also genericDrop
splitAt :: ListLike full item => Int -> full -> (full, full)
Equivalent to (take n xs, drop n xs). See also genericSplitAt.
takeWhile :: ListLike full item => (item -> Bool) -> full -> full
Returns all elements at start of list that satisfy the function.
dropWhile :: ListLike full item => (item -> Bool) -> full -> full
Drops all elements form the start of the list that satisfy the function.
span :: ListLike full item => (item -> Bool) -> full -> (full, full)
The equivalent of (takeWhile f xs, dropWhile f xs)
break :: ListLike full item => (item -> Bool) -> full -> (full, full)
The equivalent of span (not . f)
group :: (ListLike full item, 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 item, ListLike full' full) => full -> full'
All initial segments of the list, shortest first
tails :: (ListLike full item, ListLike full' full) => full -> full'
All final segnemts, longest first
Predicates
isPrefixOf :: (ListLike full item, Eq item) => full -> full -> Bool
True when the first list is at the beginning of the second.
isSuffixOf :: (ListLike full item, Eq item) => full -> full -> Bool
True when the first list is at the beginning of the second.
isInfixOf :: (ListLike full item, Eq item) => full -> full -> Bool
True when the first list is wholly containted within the second
Searching lists
Searching by equality
elem :: (ListLike full item, Eq item) => item -> full -> Bool
True if the item occurs in the list
notElem :: (ListLike full item, Eq item) => item -> full -> Bool
True if the item does not occur in the list
Searching with a predicate
find :: ListLike full item => (item -> Bool) -> full -> Maybe item
Take a function and return the first matching element, or Nothing if there is no such element.
filter :: ListLike full item => (item -> Bool) -> full -> full
Returns only the elements that satisfy the function.
partition :: ListLike full item => (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)
Indexing lists
index :: ListLike full item => full -> Int -> item
The element at 0-based index i. Raises an exception if i is out of bounds. Like (!!) for lists.
elemIndex :: (ListLike full item, Eq item) => item -> full -> Maybe Int
Returns the index of the element, if it exists.
elemIndices :: (ListLike full item, Eq item, ListLike result Int) => item -> full -> result
Returns the indices of the matching elements. See also findIndices
findIndex :: ListLike full item => (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 full item, ListLike result Int) => (item -> Bool) -> full -> result
Returns the indices of all elements satisfying the function
Zipping and unzipping lists
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
unzip :: (ListLike full (itema, itemb), ListLike ra itema, ListLike rb itemb) => full -> (ra, rb)
Converts a list of pairs into two separate lists of elements
Monadic Operations
sequence :: (ListLike full item, Monad m, ListLike fullinp (m item)) => fullinp -> m full
Evaluate each action in the sequence and collect the results
sequence_ :: (Monad m, ListLike mfull (m item)) => mfull -> m ()
Evaluate each action, ignoring the results
mapM :: (ListLike full item, Monad m, ListLike full' item') => (item -> m item') -> full -> m full'

A map in monad space. Same as sequence . map

See also rigidMapM

rigidMapM :: (ListLike full item, 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_ :: (ListLike full item, Monad m) => (item -> m b) -> full -> m ()
A map in monad space, discarding results. Same as sequence_ . map
Input and Output
class ListLike full item => ListLikeIO full item | full -> item where

An extension to ListLike for those data types that support I/O. These functions mirror those in System.IO for the most part. They also share the same names; see the comments in Data.ListLike for help importing them.

Note that some types may not be capable of lazy reading or writing. Therefore, the usual semantics of System.IO functions regarding laziness may or may not be available from a particular implementation.

Minimal complete definition:

  • hGetLine
  • hGetContents
  • hGet
  • hGetNonBlocking
  • hPutStr
Methods
hGetLine :: Handle -> IO full
Reads a line from the specified handle
hGetContents :: Handle -> IO full
Read entire handle contents. May be done lazily like hGetContents.
hGet :: Handle -> Int -> IO full
Read specified number of bytes. See hGet for particular semantics.
hGetNonBlocking :: Handle -> Int -> IO full
Non-blocking read. See hGetNonBlocking for more.
hPutStr :: Handle -> full -> IO ()
Writing entire data.
hPutStrLn :: Handle -> full -> IO ()
Write data plus newline character.
getLine :: IO full
Read one line
getContents :: IO full
Read entire content from stdin. See hGetContents.
putStr :: full -> IO ()
Write data to stdout.
putStrLn :: full -> IO ()
Write data plus newline character to stdout.
interact :: (full -> full) -> IO ()
Interact with stdin and stdout by using a function to transform input to output. May be lazy. See interact for more.
readFile :: FilePath -> IO full
Read file. May be lazy.
writeFile :: FilePath -> full -> IO ()
Write data to file.
appendFile :: FilePath -> full -> IO ()
Append data to file.
show/hide Instances
ListLikeIO ByteString Word8
ListLikeIO ByteString Word8
ListLikeIO String Char
(Integral i, Ix i) => ListLikeIO (Array i Char) Char
Special lists
Strings
toString :: StringLike s => s -> String
Converts the structure to a String
fromString :: StringLike s => String -> s
Converts a String to a list
lines :: (StringLike s, ListLike full s) => s -> full
Breaks a string into a list of strings
words :: (StringLike s, ListLike full s) => s -> full
Breaks a string into a list of words
"Set" operations
nub :: (ListLike full item, Eq item) => full -> full
Removes duplicate elements from the list. See also nubBy
delete :: (ListLike full item, Eq item) => item -> full -> full
Removes the first instance of the element from the list. See also deleteBy
deleteFirsts :: (ListLike full item, 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 :: (ListLike full item, 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 :: (ListLike full item, Eq item) => full -> full -> full
List intersection: the set of elements that occur in both lists. See also intersectBy
Ordered lists
sort :: (ListLike full item, 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 :: (ListLike full item, 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.
Generalized functions
The "By" operations
User-supplied equality (replacing an Eq context)
nubBy :: ListLike full item => (item -> item -> Bool) -> full -> full
Generic version of nub
deleteBy :: ListLike full item => (item -> item -> Bool) -> item -> full -> full
Generic version of deleteBy
deleteFirstsBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full
Generic version of deleteFirsts
unionBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full
Generic version of union
intersectBy :: ListLike full item => (item -> item -> Bool) -> full -> full -> full
Generic version of intersect
groupBy :: (ListLike full item, ListLike full' full, Eq item) => (item -> item -> Bool) -> full -> full'
Generic version of group.
User-supplied comparison (replacing an Ord context)
sortBy :: (ListLike full item, Ord item) => (item -> item -> Ordering) -> full -> full
Sort function taking a custom comparison function
insertBy :: (ListLike full item, Ord item) => (item -> item -> Ordering) -> item -> full -> full
Like insert, but with a custom comparison function
The "generic" operations
genericLength :: (ListLike full item, Num a) => full -> a
Length of the list
genericTake :: (ListLike full item, Integral a) => a -> full -> full
Generic version of take
genericDrop :: (ListLike full item, Integral a) => a -> full -> full
Generic version of drop
genericSplitAt :: (ListLike full item, Integral a) => a -> full -> (full, full)
Generic version of splitAt
genericReplicate :: (ListLike full item, Integral a) => a -> item -> full
Generic version of replicate
Notes on specific instances
Lists

Functions for operating on regular lists almost all use the native implementations in Data.List, Prelude, or similar standard modules. The exceptions are:

Arrays

Array is an instance of ListLike. Here are some notes about it:

  • The index you use must be an integral
  • ListLike functions that take an index always take a 0-based index for compatibility with other ListLike instances. This is translated by the instance functions into the proper offset from the bounds in the Array.
  • ListLike functions preserve the original Array index numbers when possible. Functions such as cons will reduce the lower bound to do their job. snoc and append increase the upper bound. drop raises the lower bound and take lowers the upper bound.
  • Functions that change the length of the array by an amount not known in advance, such as filter, will generate a new array with the lower bound set to 0. Furthermore, these functions cannot operate on infinite lists because they must know their length in order to generate the array. hGetContents and its friends will therefore require the entire file to be read into memory before processing is possible.
  • empty, singleton, and fromList also generate an array with the lower bound set to 0.
  • Many of these functions will generate runtime exceptions if you have not assigned a value to every slot in the array.
Maps

Map is an instance of ListLike and is a rather interesting one at that. The "item" for the Map instance is a (key, value) pair. This permits you to do folds, maps, etc. over a Map just like you would on a list.

The nature of a Map -- that every key is unique, and that it is internally sorted -- means that there are some special things to take note of:

  • cons may or may not actually increase the size of the Map. If the given key is already in the map, its value will simply be updated. Since a Map has a set internal ordering, it is also not guaranteed that cons will add something to the beginning of the Map.
  • snoc is the same operation as cons.
  • append is union
  • nub, nubBy, reverse, sort, sortBy, etc. are the identity function and don't actually perform any computation
  • insert is the same as cons.
  • replicate and genericReplicate ignore the count and return a Map with a single element.
ByteStrings

Both strict and lazy ByteStreams can be used with ListLike.

Most ListLike operations map directly to ByteStream options. Notable exceptions:

  • map uses the ListLike implementation. rigidMap is more efficient. The same goes for concatMap vs. rigidConcatMap.
  • isInfixOf, sequence, mapM and similar monad operations, insert, union, intersect, sortBy, and similar functions are not implemented in ByteStream and use a naive default implementation.
  • The lazy ByteStream module implements fewer funtions than the strict ByteStream module. In some cases, default implementations are used. In others, notably related to I/O, the lazy ByteStreams are converted back and forth to strict ones as appropriate.
Base Typeclasses
The ListLike class
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)
The FoldableLL class
class FoldableLL full item | full -> item where

This is the primary class for structures that are to be considered foldable. A minimum complete definition provides foldl and foldr.

Instances of FoldableLL can be folded, and can be many and varied.

These functions are used heavily in Data.ListLike.

Methods
foldl :: (a -> item -> a) -> a -> full -> a
Left-associative fold
foldl' :: (a -> item -> a) -> a -> full -> a
Strict version of foldl.
foldl1 :: (item -> item -> item) -> full -> item
A variant of foldl with no base case. Requires at least 1 list element.
foldr :: (item -> b -> b) -> b -> full -> b
Right-associative fold
foldr' :: (item -> b -> b) -> b -> full -> b
Strict version of foldr
foldr1 :: (item -> item -> item) -> full -> item
Like foldr, but with no starting value
show/hide Instances
FoldableLL ByteString Word8
FoldableLL ByteString Word8
FoldableLL [a] a
Ix i => FoldableLL (Array i e) e
Ord key => FoldableLL (Map key val) (key, val)
The StringLike class
class StringLike s where
An extension to ListLike for those data types that are similar to a String. Minimal complete definition is toString and fromString.
Methods
toString :: s -> String
Converts the structure to a String
fromString :: String -> s
Converts a String to a list
lines :: ListLike full s => s -> full
Breaks a string into a list of strings
words :: ListLike full s => s -> full
Breaks a string into a list of words
show/hide Instances
StringLike ByteString
StringLike ByteString
StringLike String
(Integral i, Ix i) => StringLike (Array i Char)
The InfiniteListLike class
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
Produced by Haddock version 0.8