Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- inits :: [a] -> [[a]]
- tails :: [a] -> [[a]]
- groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
- group :: Eq a => [a] -> [[a]]
- unzip :: [(a, b)] -> ([a], [b])
- partition :: (a -> Bool) -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- chop :: (a -> Bool) -> [a] -> [[a]]
- breakAfter :: (a -> Bool) -> [a] -> ([a], [a])
- takeUntil :: (a -> Bool) -> [a] -> [a]
- segmentAfter :: (a -> Bool) -> [a] -> [[a]]
- segmentBefore :: (a -> Bool) -> [a] -> [[a]]
- segmentAfterJust :: (a -> Maybe b) -> [a] -> ([([a], b)], [a])
- segmentAfterMaybe :: (a -> Maybe b) -> [a] -> ([([a], b)], [a])
- segmentBeforeJust :: (a -> Maybe b) -> [a] -> ([a], [(b, [a])])
- segmentBeforeMaybe :: (a -> Maybe b) -> [a] -> ([a], [(b, [a])])
- segmentAfterRight :: [Either a b] -> ([([a], b)], [a])
- segmentBeforeRight :: [Either a b] -> ([a], [(b, [a])])
- removeEach :: [a] -> [(a, [a])]
- splitEverywhere :: [a] -> [([a], a, [a])]
- splitLast :: [a] -> ([a], a)
- viewL :: [a] -> Maybe (a, [a])
- viewR :: [a] -> Maybe ([a], a)
- switchL :: b -> (a -> [a] -> b) -> [a] -> b
- switchR :: b -> ([a] -> a -> b) -> [a] -> b
- dropRev :: Int -> [a] -> [a]
- takeRev :: Int -> [a] -> [a]
- splitAtRev :: Int -> [a] -> ([a], [a])
- dropWhileRev :: (a -> Bool) -> [a] -> [a]
- takeWhileRev :: (a -> Bool) -> [a] -> [a]
- maybePrefixOf :: Eq a => [a] -> [a] -> Maybe [a]
- maybeSuffixOf :: Eq a => [a] -> [a] -> Maybe [a]
- partitionMaybe :: (a -> Maybe b) -> [a] -> ([b], [a])
- takeWhileJust :: [Maybe a] -> [a]
- dropWhileNothing :: (a -> Maybe b) -> [a] -> Maybe (b, [a])
- breakJust :: (a -> Maybe b) -> [a] -> ([a], Maybe (b, [a]))
- spanJust :: (a -> Maybe b) -> [a] -> ([b], [a])
- unzipEithers :: [Either a b] -> ([a], [b])
- sieve :: Int -> [a] -> [a]
- sliceHorizontal :: Int -> [a] -> [[a]]
- sliceVertical :: Int -> [a] -> [[a]]
- search :: Eq a => [a] -> [a] -> [Int]
- replace :: Eq a => [a] -> [a] -> [a] -> [a]
- multiReplace :: Eq a => [([a], [a])] -> [a] -> [a]
- shear :: [[a]] -> [[a]]
- shearTranspose :: [[a]] -> [[a]]
- outerProduct :: (a -> b -> c) -> [a] -> [b] -> [[c]]
- takeWhileMulti :: [a -> Bool] -> [a] -> [a]
- rotate :: Int -> [a] -> [a]
- mergeBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- allEqual :: Eq a => [a] -> Bool
- isAscending :: Ord a => [a] -> Bool
- isAscendingLazy :: Ord a => [a] -> [Bool]
- mapAdjacent :: (a -> a -> b) -> [a] -> [b]
- mapAdjacent1 :: (a -> a -> b -> c) -> a -> [(a, b)] -> [c]
- range :: Num a => Int -> [a]
- padLeft :: a -> Int -> [a] -> [a]
- padRight :: a -> Int -> [a] -> [a]
- iterateAssociative :: (a -> a -> a) -> a -> [a]
- iterateLeaky :: (a -> a -> a) -> a -> [a]
- lengthAtLeast :: Int -> [a] -> Bool
- lengthAtMost :: Int -> [a] -> Bool
Improved standard functions
inits :: [a] -> [[a]] Source #
This function is lazier than the one suggested in the Haskell 98 report.
It is inits undefined = [] : undefined
,
in contrast to Data.List.inits undefined = undefined
.
tails :: [a] -> [[a]] Source #
This function is lazier than the one suggested in the Haskell 98 report.
It is tails undefined = ([] : undefined) : undefined
,
in contrast to Data.List.tails undefined = undefined
.
groupBy :: (a -> a -> Bool) -> [a] -> [[a]] Source #
This function compares adjacent elements of a list. If two adjacent elements satisfy a relation then they are put into the same sublist. Example:
>>>
groupBy (<) "abcdebcdef"
["abcde","bcdef"]
In contrast to that groupBy
compares
the head of each sublist with each candidate for this sublist.
This yields
>>>
List.groupBy (<) "abcdebcdef"
["abcdebcdef"]
The second
is compared with the leading b
.
Thus it is put into the same sublist as a
.a
The sublists are never empty.
Thus the more precise result type would be [(a,[a])]
.
unzip :: [(a, b)] -> ([a], [b]) Source #
Like standard unzip
but more lazy.
It is Data.List.unzip undefined == undefined
,
but unzip undefined == (undefined, undefined)
.
partition :: (a -> Bool) -> [a] -> ([a], [a]) Source #
partition
of GHC 6.2.1 fails on infinite lists.
But this one does not.
span :: (a -> Bool) -> [a] -> ([a], [a]) Source #
It is Data.List.span f undefined = undefined
,
whereas span f undefined = (undefined, undefined)
.
break :: (a -> Bool) -> [a] -> ([a], [a]) Source #
It is Data.List.span f undefined = undefined
,
whereas span f undefined = (undefined, undefined)
.
Split
chop :: (a -> Bool) -> [a] -> [[a]] Source #
Split the list at the occurrences of a separator into sub-lists.
Remove the separators.
This is somehow a generalization of lines
and words
.
But note the differences:
>>>
words "a a"
["a","a"]>>>
chop (' '==) "a a"
["a","","a"]
>>>
lines "a\n\na"
["a","","a"]>>>
chop ('\n'==) "a\n\na"
["a","","a"]
>>>
lines "a\n"
["a"]>>>
chop ('\n'==) "a\n"
["a",""]
breakAfter :: (a -> Bool) -> [a] -> ([a], [a]) Source #
Like break
, but splits after the matching element.
forAllPredicates $ \p xs -> uncurry (++) (breakAfter p xs) == xs
takeUntil :: (a -> Bool) -> [a] -> [a] Source #
Take all elements until one matches.
The matching element is returned, too.
This is the key difference to takeWhile (not . p)
.
It holds:
forAllPredicates $ \p xs -> takeUntil p xs == fst (breakAfter p xs)
segmentAfter :: (a -> Bool) -> [a] -> [[a]] Source #
Split the list after each occurence of a terminator.
Keep the terminator.
There is always a list for the part after the last terminator.
It may be empty.
See package non-empty
for more precise result type.
forAllPredicates $ \p xs -> concat (segmentAfter p xs) == xs
forAllPredicates $ \p xs -> length (filter p xs) == length (tail (segmentAfter p xs))
forAllPredicates $ \p -> all (p . last) . init . segmentAfter p
forAllPredicates $ \p -> all (all (not . p) . init) . init . segmentAfter p
This test captures both infinitely many groups and infinitely big groups:
forAllPredicates $ \p x -> flip seq True . (!!100) . concat . segmentAfter p . cycle . (x:)
segmentBefore :: (a -> Bool) -> [a] -> [[a]] Source #
Split the list before each occurence of a leading character.
Keep these characters.
There is always a list for the part before the first leading character.
It may be empty.
See package non-empty
for more precise result type.
forAllPredicates $ \p xs -> concat (segmentBefore p xs) == xs
forAllPredicates $ \p xs -> length (filter p xs) == length (tail (segmentBefore p xs))
forAllPredicates $ \p -> all (p . head) . tail . segmentBefore p
forAllPredicates $ \p -> all (all (not . p) . tail) . tail . segmentBefore p
forAllPredicates $ \p x -> flip seq True . (!!100) . concat . segmentBefore p . cycle . (x:)
segmentAfterJust :: (a -> Maybe b) -> [a] -> ([([a], b)], [a]) Source #
>>>
segmentAfterJust (\c -> toMaybe (isLetter c) (toUpper c)) "123a5345b---"
([("123",'A'),("5345",'B')],"---")
segmentAfterMaybe :: (a -> Maybe b) -> [a] -> ([([a], b)], [a]) Source #
Deprecated: use segmentAfterJust instead
segmentBeforeJust :: (a -> Maybe b) -> [a] -> ([a], [(b, [a])]) Source #
>>>
segmentBeforeJust (\c -> toMaybe (isLetter c) (toUpper c)) "123a5345b---"
("123",[('A',"5345"),('B',"---")])
segmentBeforeMaybe :: (a -> Maybe b) -> [a] -> ([a], [(b, [a])]) Source #
Deprecated: use segmentBeforeJust instead
segmentAfterRight :: [Either a b] -> ([([a], b)], [a]) Source #
>>>
segmentAfterRight [Left 'a', Right LT, Right GT, Left 'b']
([("a",LT),("",GT)],"b")
forAllMaybeFn $ \f xs -> segmentAfterJust f xs == segmentAfterRight (map (\x -> maybe (Left x) Right (f x)) xs)
segmentBeforeRight :: [Either a b] -> ([a], [(b, [a])]) Source #
>>>
segmentBeforeRight [Left 'a', Right LT, Right GT, Left 'b']
("a",[(LT,""),(GT,"b")])
forAllMaybeFn $ \f xs -> segmentBeforeJust f xs == segmentBeforeRight (map (\x -> maybe (Left x) Right (f x)) xs)
removeEach :: [a] -> [(a, [a])] Source #
removeEach xs
represents a list of sublists of xs
,
where each element of xs
is removed and
the removed element is separated.
It seems to be much simpler to achieve with
zip xs (map (flip List.delete xs) xs)
,
but the implementation of removeEach
does not need the Eq
instance
and thus can also be used for lists of functions.
See also the proposal http://www.haskell.org/pipermail/libraries/2008-February/009270.html
>>>
removeEach "abc"
[('a',"bc"),('b',"ac"),('c',"ab")]>>>
removeEach "a"
[('a',"")]>>>
removeEach ""
[]
splitEverywhere :: [a] -> [([a], a, [a])] Source #
>>>
splitEverywhere "abc"
[("",'a',"bc"),("a",'b',"c"),("ab",'c',"")]>>>
splitEverywhere "a"
[("",'a',"")]>>>
splitEverywhere ""
[]
splitLast :: [a] -> ([a], a) Source #
Deprecated: use viewR instead
It holds splitLast xs == (init xs, last xs)
,
but splitLast
is more efficient
if the last element is accessed after the initial ones,
because it avoids memoizing list.
\(NonEmpty xs) -> splitLast (xs::String) == (init xs, last xs)
List processing starting at the end
dropRev :: Int -> [a] -> [a] Source #
dropRev n
is like reverse . drop n . reverse
but it is lazy enough to work for infinite lists, too.
\n xs -> dropRev n (xs::String) == reverse (drop n (reverse xs))
takeRev :: Int -> [a] -> [a] Source #
takeRev n
is like reverse . take n . reverse
but it is lazy enough to work for infinite lists, too.
\n xs -> takeRev n (xs::String) == reverse (take n (reverse xs))
splitAtRev :: Int -> [a] -> ([a], [a]) Source #
splitAtRev n xs == (dropRev n xs, takeRev n xs)
.
\n xs -> splitAtRev n (xs::String) == (dropRev n xs, takeRev n xs)
\n xs -> (xs::String) == uncurry (++) (splitAtRev n xs)
dropWhileRev :: (a -> Bool) -> [a] -> [a] Source #
Deprecated: Use dropWhile from Data.List.Reverse.StrictElement or Data.List.Reverse.StrictSpine instead
takeWhileRev :: (a -> Bool) -> [a] -> [a] Source #
Deprecated: Use takeWhile from Data.List.Reverse.StrictElement or Data.List.Reverse.StrictSpine instead
List processing with Maybe and Either
maybePrefixOf :: Eq a => [a] -> [a] -> Maybe [a] Source #
maybePrefixOf xs ys
is Just zs
if xs
is a prefix of ys
,
where zs
is ys
without the prefix xs
.
Otherwise it is Nothing
.
It is the same as stripPrefix
.
>>>
maybePrefixOf "abc" "abcdef"
Just "def">>>
maybePrefixOf "def" "abcdef"
Nothing
maybeSuffixOf :: Eq a => [a] -> [a] -> Maybe [a] Source #
>>>
maybeSuffixOf "abc" "abcdef"
Nothing>>>
maybeSuffixOf "def" "abcdef"
Just "abc"
partitionMaybe :: (a -> Maybe b) -> [a] -> ([b], [a]) Source #
Partition a list into elements which evaluate to Just
or Nothing
by f
.
forAllMaybeFn $ \f xs -> partitionMaybe f xs == (mapMaybe f xs, filter (isNothing . f) xs)
forAllPredicates $ \p xs -> partition p xs == partitionMaybe (\x -> toMaybe (p x) x) xs
takeWhileJust :: [Maybe a] -> [a] Source #
This is the cousin of takeWhile
analogously to catMaybes
being the cousin of filter
.
>>>
takeWhileJust [Just 'a', Just 'b', Nothing, Just 'c']
"ab"
Example: Keep the heads of sublists until an empty list occurs.
>>>
takeWhileJust $ map (fmap fst . viewL) ["abc","def","","xyz"]
"ad"
For consistency with takeWhile
,
partitionMaybe
and dropWhileNothing
it should have been:
takeWhileJust_ :: (a -> Maybe b) -> a -> [b]
However, both variants are interchangeable:
takeWhileJust_ f == takeWhileJust . map f takeWhileJust == takeWhileJust_ id
dropWhileNothing :: (a -> Maybe b) -> [a] -> Maybe (b, [a]) Source #
breakJust :: (a -> Maybe b) -> [a] -> ([a], Maybe (b, [a])) Source #
forAllMaybeFn $ \f xs -> snd (breakJust f xs) == dropWhileNothing f xs
unzipEithers :: [Either a b] -> ([a], [b]) Source #
Sieve and slice
sieve :: Int -> [a] -> [a] Source #
keep every k-th value from the list
>>>
sieve 6 ['a'..'z']
"agmsy"
sliceHorizontal :: Int -> [a] -> [[a]] Source #
>>>
sliceHorizontal 6 ['a'..'z']
["agmsy","bhntz","ciou","djpv","ekqw","flrx"]
\(NonEmpty xs) -> QC.forAll (QC.choose (1, length xs)) $ \n -> sliceHorizontal n xs == transpose (sliceVertical n (xs::String))
\(NonEmpty xs) -> QC.forAll (QC.choose (1, length xs)) $ \n -> sliceVertical n xs == transpose (sliceHorizontal n (xs::String))
The properties do not hold for empty lists because of:
>>>
sliceHorizontal 4 ([]::[Int])
[[],[],[],[]]
sliceVertical :: Int -> [a] -> [[a]] Source #
>>>
sliceVertical 6 ['a'..'z']
["abcdef","ghijkl","mnopqr","stuvwx","yz"]
Search&replace
replace :: Eq a => [a] -> [a] -> [a] -> [a] Source #
\(NonEmpty xs) ys -> replace xs xs ys == (ys::String)
\(NonEmpty xs) (NonEmpty ys) -> equating (take 1000) (replace xs ys (cycle xs)) (cycle (ys::String))
multiReplace :: Eq a => [([a], [a])] -> [a] -> [a] Source #
prop src dst xs -> replace src dst xs == multiReplace (src,dst)
Lists of lists
shear :: [[a]] -> [[a]] Source #
Transform
[[00,01,02,...], [[00], [10,11,12,...], --> [10,01], [20,21,22,...], [20,11,02], ...] ...]
With concat . shear
you can perform a Cantor diagonalization,
that is an enumeration of all elements of the sub-lists
where each element is reachable within a finite number of steps.
It is also useful for polynomial multiplication (convolution).
shearTranspose :: [[a]] -> [[a]] Source #
Transform
[[00,01,02,...], [[00], [10,11,12,...], --> [01,10], [20,21,22,...], [02,11,20], ...] ...]
It's like shear
but the order of elements in the sub list is reversed.
Its implementation seems to be more efficient than that of shear
.
If the order does not matter, better choose shearTranspose
.
\xs -> shearTranspose xs == map reverse (shear (xs::[String]))
outerProduct :: (a -> b -> c) -> [a] -> [b] -> [[c]] Source #
Operate on each combination of elements of the first and the second list.
In contrast to the list instance of liftM2
it holds the results in a list of lists.
\xs ys -> let f x y = (x::Char,y::Int) in concat (outerProduct f xs ys) == liftM2 f xs ys
Miscellaneous
takeWhileMulti :: [a -> Bool] -> [a] -> [a] Source #
Take while first predicate holds, then continue taking while second predicate holds, and so on.
mergeBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #
Given two lists that are ordered
(i.e. p x y
holds for subsequent x
and y
)
mergeBy
them into a list that is ordered, again.
>>>
mergeBy (<=) "agh" "begz"
"abegghz"
allEqual :: Eq a => [a] -> Bool Source #
>>>
allEqual "aab"
False>>>
allEqual "aaa"
True>>>
allEqual "aa"
True>>>
allEqual "a"
True>>>
allEqual ""
True
isAscending :: Ord a => [a] -> Bool Source #
>>>
isAscending "abc"
True>>>
isAscending "abb"
True>>>
isAscending "aba"
False>>>
isAscending "cba"
False>>>
isAscending "a"
True>>>
isAscending ""
True
isAscendingLazy :: Ord a => [a] -> [Bool] Source #
mapAdjacent :: (a -> a -> b) -> [a] -> [b] Source #
This function combines every pair of neighbour elements in a list with a certain function.
>>>
mapAdjacent (<=) ""
[]>>>
mapAdjacent (<=) "a"
[]>>>
mapAdjacent (<=) "aba"
[True,False]>>>
mapAdjacent (,) "abc"
[('a','b'),('b','c')]
\x xs -> mapAdjacent subtract (scanl (+) x xs) == (xs::[Integer])
mapAdjacent1 :: (a -> a -> b -> c) -> a -> [(a, b)] -> [c] Source #
>>>
let f x y z = [x,y]++show(z::Int) in mapAdjacent1 f 'a' [('b',1), ('c',2), ('d',3)]
["ab1","bc2","cd3"]
range :: Num a => Int -> [a] Source #
Enumerate without Enum context. For Enum equivalent to enumFrom.
>>>
range 0 :: [Integer]
[]>>>
range 1 :: [Integer]
[0]>>>
range 8 :: [Integer]
[0,1,2,3,4,5,6,7]
\(NonNegative n) -> length (range n :: [Integer]) == n
iterateAssociative :: (a -> a -> a) -> a -> [a] Source #
For an associative operation op
this computes
iterateAssociative op a = iterate (op a) a
but it is even faster than map (powerAssociative op a a) [0..]
since it shares temporary results.
The idea is:
From the list map (powerAssociative op a a) [0,(2*n)..]
we compute the list map (powerAssociative op a a) [0,n..]
,
and iterate that until n==1
.
\x -> equating (take 1000) (List.iterate (x+) x) (iterateAssociative (+) (x::Integer))
iterateLeaky :: (a -> a -> a) -> a -> [a] Source #
This is equal to iterateAssociative
.
The idea is the following:
The list we search is the fixpoint of the function:
"Square all elements of the list,
then spread it and fill the holes with successive numbers
of their left neighbour."
This also preserves log n applications per value.
However it has a space leak,
because for the value with index n
all elements starting at div n 2
must be kept.
\x -> equating (take 1000) (List.iterate (x+) x) (iterateLeaky (+) (x::Integer))
lengthAtLeast :: Int -> [a] -> Bool Source #
>>>
lengthAtLeast 0 ""
True>>>
lengthAtLeast 3 "ab"
False>>>
lengthAtLeast 3 "abc"
True>>>
lengthAtLeast 3 $ repeat 'a'
True>>>
lengthAtLeast 3 $ "abc" ++ undefined
True
\n xs -> lengthAtLeast n (xs::String) == (length xs >= n)
lengthAtMost :: Int -> [a] -> Bool Source #
>>>
lengthAtMost 0 ""
True>>>
lengthAtMost 3 "ab"
True>>>
lengthAtMost 3 "abc"
True>>>
lengthAtMost 3 "abcd"
False>>>
lengthAtMost 3 $ repeat 'a'
False>>>
lengthAtMost 3 $ "abcd" ++ undefined
False
\n xs -> lengthAtMost n (xs::String) == (length xs <= n)