Portability | portable |
---|---|
Stability | provisional |
Maintainer | John Goerzen <jgoerzen@complete.org> |
Safe Haskell | None |
- Introduction
- Creation & Basic Functions
- List transformations
- Reducing lists (folds), from FoldableLL
- Building lists
- Sublists
- Searching lists
- Indexing lists
- Zipping and unzipping lists
- Monadic Operations
- Input and Output
- Special lists
- Generalized functions
- Notes on specific instances
- Base Typeclasses
Generic operations over list-like structures
Written by John Goerzen, jgoerzen@complete.org
Please start with the introduction at Data.ListLike.
- and :: ListLike full Bool => full -> Bool
- or :: ListLike full Bool => full -> Bool
- sum :: (Num a, ListLike full a) => full -> a
- product :: (Num a, ListLike full a) => full -> a
- fold :: (FoldableLL full item, Monoid item) => full -> item
- foldMap :: (FoldableLL full item, Monoid m) => (item -> m) -> full -> m
- 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_ :: (Monad m, FoldableLL full (m item)) => full -> m ()
- mapM_ :: (Monad m, FoldableLL full item) => (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 ()
- newtype CharString = CS {
- unCS :: ByteString
- newtype CharStringLazy = CSL {
- unCSL :: ByteString
- 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
- 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 :: (item -> item -> Ordering) -> full -> full
- insertBy :: (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
- class StringLike s where
- class ListLike full item => InfiniteListLike full item | full -> item where
Introduction
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 Data.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 Data.ListLike (map)
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
List transformations
Conversions
Reducing lists (folds), from FoldableLL
Special folds
fold :: (FoldableLL full item, Monoid item) => full -> itemSource
foldMap :: (FoldableLL full item, Monoid m) => (item -> m) -> full -> mSource
Map each element to a monoid, then combine the results
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
zip :: (ListLike full item, ListLike fullb itemb, ListLike result (item, itemb)) => full -> fullb -> resultSource
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 -> resultSource
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)Source
Converts a list of pairs into two separate lists of elements
Monadic Operations
sequence_ :: (Monad m, FoldableLL full (m item)) => full -> m ()Source
mapM_ :: (Monad m, FoldableLL full item) => (item -> m b) -> full -> m ()Source
A map in monad space, discarding results.
Input and Output
class ListLike full item => ListLikeIO full item | full -> item whereSource
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
hGetLine :: Handle -> IO fullSource
Reads a line from the specified handle
hGetContents :: Handle -> IO fullSource
Read entire handle contents. May be done lazily like
hGetContents
.
hGet :: Handle -> Int -> IO fullSource
Read specified number of bytes. See hGet
for
particular semantics.
hGetNonBlocking :: Handle -> Int -> IO fullSource
Non-blocking read. See hGetNonBlocking
for more.
hPutStr :: Handle -> full -> IO ()Source
Writing entire data.
hPutStrLn :: Handle -> full -> IO ()Source
Write data plus newline character.
Read one line
getContents :: IO fullSource
Read entire content from stdin. See hGetContents
.
Write data to stdout.
putStrLn :: full -> IO ()Source
Write data plus newline character to stdout.
interact :: (full -> full) -> IO ()Source
Interact with stdin and stdout by using a function to transform
input to output. May be lazy. See interact
for more.
readFile :: FilePath -> IO fullSource
Read file. May be lazy.
writeFile :: FilePath -> full -> IO ()Source
Write data to file.
appendFile :: FilePath -> full -> IO ()Source
Append data to file.
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
Functions for operating on regular lists almost all use the native implementations in Data.List, Prelude, or similar standard modules. The exceptions are:
-
mapM
uses the defaultListLike
implementation -
hGet
does not exist forString
in the Haskell modules. It is implemented in terms of Data.ByteString.Lazy. -
hGetNonBlocking
is the same way.
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 otherListLike
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 ascons
will reduce the lower bound to do their job.snoc
andappend
increase the upper bound.drop
raises the lower bound andtake
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
, andfromList
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.
ByteStrings
Both strict and lazy ByteStreams can be used with ListLike
.
ByteString ListLike instances operate on Word8
elements. This is because
both Data.ByteString.ByteString and Data.ByteString.Char8.ByteString have
the same underlying type. If you wish to use the Char8 representation,
the newtype wrappers CharString
and CharStringLazy
are available.
Most ListLike
operations map directly to ByteStream options. Notable
exceptions:
-
map
uses theListLike
implementation.rigidMap
is more efficient. The same goes forconcatMap
vs.rigidConcatMap
. -
isInfixOf
,sequence
,mapM
and similar monad operations,insert
,union
,intersect
,sortBy
, and similar functions are not implemented inByteStream
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.
newtype CharString Source
Newtype wrapper around Data.ByteString.Char8.ByteString, this allows for ListLike instances with Char elements.
CS | |
|
newtype CharStringLazy Source
Newtype wrapper around Data.ByteString.Lazy.Char8.ByteString, this allows for ListLike instances with Char elements.
CSL | |
|
Base Typeclasses
The ListLike class
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 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
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.
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 :: (item -> item -> Ordering) -> full -> fullSource
Sort function taking a custom comparison function
insertBy :: (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
ListLike ByteString Word8 | |
ListLike ByteString Word8 | |
ListLike Text Char | |
ListLike Text Char | |
ListLike CharStringLazy Char | |
ListLike CharString Char | |
ListLike [a] a | |
(Monoid (v a), Eq (v a), Vector v a) => ListLike (v a) a | |
ListLike (Seq a) a | |
ListLike (Vector a) a | |
Unbox a => ListLike (Vector a) a | |
Storable a => ListLike (Vector a) a | |
(Integral i, Ix i) => ListLike (Array i e) e |
The FoldableLL class
class FoldableLL full item | full -> item whereSource
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.
foldl :: (a -> item -> a) -> a -> full -> aSource
Left-associative fold
foldl' :: (a -> item -> a) -> a -> full -> aSource
Strict version of foldl
.
foldl1 :: (item -> item -> item) -> full -> itemSource
A variant of foldl
with no base case. Requires at least 1
list element.
foldr :: (item -> b -> b) -> b -> full -> bSource
Right-associative fold
foldr' :: (item -> b -> b) -> b -> full -> bSource
Strict version of foldr
foldr1 :: (item -> item -> item) -> full -> itemSource
Like foldr
, but with no starting value
FoldableLL ByteString Word8 | |
FoldableLL ByteString Word8 | |
FoldableLL Text Char | |
FoldableLL Text Char | |
FoldableLL CharStringLazy Char | |
FoldableLL CharString Char | |
FoldableLL [a] a | |
Vector v a => FoldableLL (v a) a | |
FoldableLL (Seq a) a | |
FoldableLL (Vector a) a | |
Unbox a => FoldableLL (Vector a) a | |
Storable a => FoldableLL (Vector a) a | |
Ix i => FoldableLL (Array i e) e |
The StringLike class
class StringLike s whereSource
An extension to ListLike
for those data types that are similar
to a String
. Minimal complete definition is toString
and
fromString
.
Converts the structure to a String
fromString :: String -> sSource
Converts a String
to a list
lines :: ListLike full s => s -> fullSource
Breaks a string into a list of strings
words :: ListLike full s => s -> fullSource
Breaks a string into a list of words
StringLike String | |
StringLike ByteString | |
StringLike ByteString | |
StringLike Text | |
StringLike Text | |
StringLike CharStringLazy | |
StringLike CharString | |
(Eq (v Char), Vector v Char) => StringLike (v Char) | |
StringLike (Seq Char) | |
StringLike (Vector Char) | |
StringLike (Vector Char) | |
StringLike (Vector Char) | |
(Integral i, Ix i) => StringLike (Array i Char) |
The InfiniteListLike class
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.
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
InfiniteListLike [a] a |