| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Agda.Utils.List
Contents
Description
Utility functions for lists.
Synopsis
- snoc :: [a] -> a -> [a]
 - caseList :: [a] -> b -> (a -> [a] -> b) -> b
 - caseListM :: Monad m => m [a] -> m b -> (a -> [a] -> m b) -> m b
 - listCase :: b -> (a -> [a] -> b) -> [a] -> b
 - headWithDefault :: a -> [a] -> a
 - tailMaybe :: [a] -> Maybe [a]
 - tailWithDefault :: [a] -> [a] -> [a]
 - lastMaybe :: [a] -> Maybe a
 - last2 :: [a] -> Maybe (a, a)
 - uncons :: [a] -> Maybe (a, [a])
 - mcons :: Maybe a -> [a] -> [a]
 - initLast :: [a] -> Maybe ([a], a)
 - initMaybe :: [a] -> Maybe [a]
 - (!!!) :: [a] -> Int -> Maybe a
 - indexWithDefault :: a -> [a] -> Int -> a
 - findWithIndex :: (a -> Bool) -> [a] -> Maybe (a, Int)
 - genericElemIndex :: (Eq a, Integral i) => a -> [a] -> Maybe i
 - downFrom :: Integral a => a -> [a]
 - updateHead :: (a -> a) -> [a] -> [a]
 - updateLast :: (a -> a) -> [a] -> [a]
 - updateAt :: Int -> (a -> a) -> [a] -> [a]
 - type Prefix a = [a]
 - type Suffix a = [a]
 - splitExactlyAt :: Integral n => n -> [a] -> Maybe (Prefix a, Suffix a)
 - dropEnd :: forall a. Int -> [a] -> Prefix a
 - spanEnd :: forall a. (a -> Bool) -> [a] -> (Prefix a, Suffix a)
 - takeWhileJust :: (a -> Maybe b) -> [a] -> Prefix b
 - spanJust :: (a -> Maybe b) -> [a] -> (Prefix b, Suffix a)
 - partitionMaybe :: (a -> Maybe b) -> [a] -> ([a], [b])
 - filterAndRest :: (a -> Bool) -> [a] -> ([a], Suffix a)
 - mapMaybeAndRest :: (a -> Maybe b) -> [a] -> ([b], Suffix a)
 - isSublistOf :: Eq a => [a] -> [a] -> Bool
 - holes :: [a] -> [(a, [a])]
 - commonPrefix :: Eq a => [a] -> [a] -> Prefix a
 - dropCommon :: [a] -> [b] -> (Suffix a, Suffix b)
 - stripPrefixBy :: (a -> a -> Bool) -> Prefix a -> [a] -> Maybe (Suffix a)
 - commonSuffix :: Eq a => [a] -> [a] -> Suffix a
 - stripSuffix :: Eq a => Suffix a -> [a] -> Maybe (Prefix a)
 - type ReversedSuffix a = [a]
 - stripReversedSuffix :: forall a. Eq a => ReversedSuffix a -> [a] -> Maybe (Prefix a)
 - data StrSufSt a
- = SSSMismatch
 - | SSSStrip (ReversedSuffix a)
 - | SSSResult [a]
 
 - groupOn :: Ord b => (a -> b) -> [a] -> [[a]]
 - groupBy' :: (a -> a -> Bool) -> [a] -> [[a]]
 - wordsBy :: (a -> Bool) -> [a] -> [[a]]
 - chop :: Int -> [a] -> [[a]]
 - chopWhen :: (a -> Bool) -> [a] -> [[a]]
 - hasElem :: Ord a => [a] -> a -> Bool
 - sorted :: Ord a => [a] -> Bool
 - distinct :: Eq a => [a] -> Bool
 - fastDistinct :: Ord a => [a] -> Bool
 - duplicates :: Ord a => [a] -> [a]
 - allDuplicates :: Ord a => [a] -> [a]
 - nubOn :: Ord b => (a -> b) -> [a] -> [a]
 - uniqOn :: Ord b => (a -> b) -> [a] -> [a]
 - allEqual :: Eq a => [a] -> Bool
 - zipWith' :: (a -> b -> c) -> [a] -> [b] -> Maybe [c]
 - zipWithKeepRest :: (a -> b -> b) -> [a] -> [b] -> [b]
 - unzipWith :: (a -> (b, c)) -> [a] -> ([b], [c])
 - editDistanceSpec :: Eq a => [a] -> [a] -> Int
 - editDistance :: forall a. Eq a => [a] -> [a] -> Int
 
Variants of list case, cons, head, tail, init, last
snoc :: [a] -> a -> [a] Source #
Append a single element at the end. Time: O(length); use only on small lists.
caseList :: [a] -> b -> (a -> [a] -> b) -> b Source #
Case distinction for lists, with list first. O(1).
Cf. ifNull.
caseListM :: Monad m => m [a] -> m b -> (a -> [a] -> m b) -> m b Source #
Case distinction for lists, with list first. O(1).
Cf. ifNull.
listCase :: b -> (a -> [a] -> b) -> [a] -> b Source #
Case distinction for lists, with list last. O(1).
headWithDefault :: a -> [a] -> a Source #
Head function (safe). Returns a default value on empty lists. O(1).
headWithDefault 42 [] = 42 headWithDefault 42 [1,2,3] = 1
tailWithDefault :: [a] -> [a] -> [a] Source #
Tail function (safe). Returns a default list on empty lists. O(1).
Lookup and indexing
indexWithDefault :: a -> [a] -> Int -> a Source #
Lookup function with default value for index out of range. O(min n index).
The name is chosen akin to genericIndex.
findWithIndex :: (a -> Bool) -> [a] -> Maybe (a, Int) Source #
Find an element satisfying a predicate and return it with its index.
   O(n) in the worst case, e.g. findWithIndex f xs = Nothing.
TODO: more efficient implementation!?
genericElemIndex :: (Eq a, Integral i) => a -> [a] -> Maybe i Source #
A generalised variant of elemIndex.
 O(n).
Update
updateHead :: (a -> a) -> [a] -> [a] Source #
Update the first element of a list, if it exists. O(1).
updateLast :: (a -> a) -> [a] -> [a] Source #
Update the last element of a list, if it exists. O(n).
updateAt :: Int -> (a -> a) -> [a] -> [a] Source #
Update nth element of a list, if it exists.
   O(min index n).
Precondition: the index is >= 0.
Sublist extraction and partitioning
splitExactlyAt :: Integral n => n -> [a] -> Maybe (Prefix a, Suffix a) Source #
splitExactlyAt n xs = Just (ys, zs) iff xs = ys ++ zs
   and genericLength ys = n.
dropEnd :: forall a. Int -> [a] -> Prefix a Source #
Drop from the end of a list. O(length).
dropEnd n = reverse . drop n . reverse
Forces the whole list even for n==0.
spanEnd :: forall a. (a -> Bool) -> [a] -> (Prefix a, Suffix a) Source #
Split off the largest suffix whose elements satisfy a predicate. O(n).
spanEnd p xs = (ys, zs)
   where xs = ys ++ zs
   and all p zs
   and maybe True (not . p) (lastMaybe yz).
takeWhileJust :: (a -> Maybe b) -> [a] -> Prefix b Source #
A generalized version of takeWhile.
   (Cf. mapMaybe vs. filter).
   @O(length . takeWhileJust f).
takeWhileJust f = fst . spanJust f.
spanJust :: (a -> Maybe b) -> [a] -> (Prefix b, Suffix a) Source #
A generalized version of span.
   O(length . fst . spanJust f).
partitionMaybe :: (a -> Maybe b) -> [a] -> ([a], [b]) Source #
filterAndRest :: (a -> Bool) -> [a] -> ([a], Suffix a) Source #
Like filter, but additionally return the last partition
   of the list where the predicate is False everywhere.
   O(n).
mapMaybeAndRest :: (a -> Maybe b) -> [a] -> ([b], Suffix a) Source #
Like mapMaybe, but additionally return the last partition
   of the list where the function always returns Nothing.
   O(n).
isSublistOf :: Eq a => [a] -> [a] -> Bool Source #
Sublist relation.
Prefix and suffix
Prefix
commonPrefix :: Eq a => [a] -> [a] -> Prefix a Source #
Compute the common prefix of two lists. O(min n m).
dropCommon :: [a] -> [b] -> (Suffix a, Suffix b) Source #
Drops from both lists simultaneously until one list is empty. O(min n m).
stripPrefixBy :: (a -> a -> Bool) -> Prefix a -> [a] -> Maybe (Suffix a) Source #
Check if a list has a given prefix. If so, return the list minus the prefix. O(length prefix).
Suffix
commonSuffix :: Eq a => [a] -> [a] -> Suffix a Source #
Compute the common suffix of two lists. O(n + m).
stripSuffix :: Eq a => Suffix a -> [a] -> Maybe (Prefix a) Source #
stripSuffix suf xs = Just pre iff xs = pre ++ suf.
 O(n).
type ReversedSuffix a = [a] Source #
stripReversedSuffix :: forall a. Eq a => ReversedSuffix a -> [a] -> Maybe (Prefix a) Source #
stripReversedSuffix rsuf xs = Just pre iff xs = pre ++ reverse suf.
   O(n).
Internal state for stripping suffix.
Constructors
| SSSMismatch | Error.  | 
| SSSStrip (ReversedSuffix a) | "Negative string" to remove from end. List may be empty.  | 
| SSSResult [a] | "Positive string" (result). Non-empty list.  | 
Groups and chunks
groupBy' :: (a -> a -> Bool) -> [a] -> [[a]] Source #
A variant of groupBy which applies the predicate to consecutive
 pairs.
 O(n).
wordsBy :: (a -> Bool) -> [a] -> [[a]] Source #
Split a list into sublists. Generalisation of the prelude function
   words.
   O(n).
words xs == wordsBy isSpace xs
chopWhen :: (a -> Bool) -> [a] -> [[a]] Source #
Chop a list at the positions when the predicate holds. Contrary to
   wordsBy, consecutive separator elements will result in an empty segment
   in the result.
   O(n).
intercalate [x] (chopWhen (== x) xs) == xs
List as sets
hasElem :: Ord a => [a] -> a -> Bool Source #
Check membership for the same list often.
   Use partially applied to create membership predicate
   hasElem xs :: a -> Bool.
- First time: 
O(n log n)in the worst case. - Subsequently: 
O(log n). 
Specification: hasElem xs == (.elem xs)
sorted :: Ord a => [a] -> Bool Source #
Check whether a list is sorted. O(n).
Assumes that the Ord instance implements a partial order.
distinct :: Eq a => [a] -> Bool Source #
Check whether all elements in a list are distinct from each other.
   Assumes that the Eq instance stands for an equivalence relation.
O(n²) in the worst case distinct xs == True.
fastDistinct :: Ord a => [a] -> Bool Source #
duplicates :: Ord a => [a] -> [a] Source #
Returns an (arbitrary) representative for each list element that occurs more than once. O(n log n).
allDuplicates :: Ord a => [a] -> [a] Source #
Remove the first representative for each list element. Thus, returns all duplicate copies. O(n log n).
allDuplicates xs == sort $ xs \ nub xs.
nubOn :: Ord b => (a -> b) -> [a] -> [a] Source #
Efficient variant of nubBy for lists, using a set to store already seen elements.
 O(n log n)
Specification:
nubOn f xs == 'nubBy' ((==) `'on'` f) xs.
uniqOn :: Ord b => (a -> b) -> [a] -> [a] Source #
Efficient variant of nubBy for finite lists.
 O(n log n).
Specification: For each list xs there is a list ys which is a
 permutation of xs such that
uniqOn f xs == 'nubBy' ((==) `'on'` f) ys.
Furthermore:
List.sortBy (compare `on` f) (uniqOn f xs) == uniqOn f xs uniqOn id == Set.toAscList . Set.fromList
allEqual :: Eq a => [a] -> Bool Source #
Checks if all the elements in the list are equal. Assumes that
   the Eq instance stands for an equivalence relation.
   O(n).
Zipping
zipWith' :: (a -> b -> c) -> [a] -> [b] -> Maybe [c] Source #
Requires both lists to have the same length. O(n).
Otherwise, Nothing is returned.
zipWithKeepRest :: (a -> b -> b) -> [a] -> [b] -> [b] Source #
Like zipWith but keep the rest of the second list as-is
   (in case the second list is longer).
 O(n).
zipWithKeepRest f as bs == zipWith f as bs ++ drop (length as) bs
Unzipping
Edit distance
editDistanceSpec :: Eq a => [a] -> [a] -> Int Source #
Implemented using tree recursion, don't run me at home! O(3^(min n m)).
editDistance :: forall a. Eq a => [a] -> [a] -> Int Source #
Implemented using dynamic programming and Data.Array.
   O(n*m).