Safe Haskell | Safe |
---|---|
Language | Haskell98 |
List functions.
- slice :: Int -> Int -> [a] -> [a]
- section :: Int -> Int -> [a] -> [a]
- bracket :: (a, a) -> [a] -> [a]
- unbracket' :: [a] -> (Maybe a, [a], Maybe a)
- unbracket :: [t] -> Maybe (t, [t], t)
- unbracket_err :: [t] -> (t, [t], t)
- bracket_l :: ([a], [a]) -> [a] -> [a]
- separate_at :: Eq a => [a] -> [a] -> Maybe ([a], [a])
- on_elem :: Eq a => a -> Splitter a
- split_before :: Eq a => a -> [a] -> [[a]]
- genericRotate_left :: Integral i => i -> [a] -> [a]
- rotate_left :: Int -> [a] -> [a]
- genericRotate_right :: Integral n => n -> [a] -> [a]
- rotate_right :: Int -> [a] -> [a]
- rotate :: Integral n => n -> [a] -> [a]
- rotate_r :: Integral n => n -> [a] -> [a]
- rotations :: [a] -> [[a]]
- rotate_starting_from :: Eq a => a -> [a] -> Maybe [a]
- rotate_starting_from_err :: Eq a => a -> [a] -> [a]
- adj :: Int -> Int -> [a] -> [[a]]
- adj' :: Int -> Int -> [a] -> [[a]]
- genericAdj2 :: Integral n => n -> [t] -> [(t, t)]
- adj2 :: Int -> [t] -> [(t, t)]
- close :: [a] -> [a]
- adj2_cyclic :: Int -> [t] -> [(t, t)]
- interleave :: [a] -> [a] -> [a]
- interleave_set :: [[a]] -> [a]
- deinterleave :: Int -> [a] -> [[a]]
- deinterleave2 :: [t] -> ([t], [t])
- interleave_continue :: [a] -> [a] -> [a]
- interleave_rotations :: Int -> Int -> [b] -> [b]
- generic_histogram :: (Ord a, Integral i) => [a] -> [(a, i)]
- histogram_by :: Ord a => (a -> a -> Bool) -> [a] -> [(a, Int)]
- histogram :: Ord a => [a] -> [(a, Int)]
- duplicates_by :: Ord a => (a -> a -> Bool) -> [a] -> [a]
- duplicates :: Ord a => [a] -> [a]
- segments :: Int -> Int -> [a] -> [[a]]
- intersect_l :: Eq a => [[a]] -> [a]
- union_l :: Eq a => [[a]] -> [a]
- adj_intersect :: Eq a => Int -> [[a]] -> [[a]]
- cycles :: Int -> [a] -> [[a]]
- filter_halt :: (a -> Bool) -> (a -> Bool) -> [a] -> [a]
- replace :: Eq a => [a] -> [a] -> [a] -> [a]
- replace_at :: Integral i => [a] -> i -> a -> [a]
- group_on :: Eq x => (a -> x) -> [a] -> [[a]]
- collate_on_adjacent :: (Eq k, Ord k) => (a -> k) -> (a -> v) -> [a] -> [(k, [v])]
- collate_adjacent :: Ord a => [(a, b)] -> [(a, [b])]
- collate_on :: Ord k => (a -> k) -> (a -> v) -> [a] -> [(k, [v])]
- collate :: Ord a => [(a, b)] -> [(a, [b])]
- uncollate :: [(k, [v])] -> [(k, v)]
- with_key :: k -> [v] -> [(k, v)]
- dx_d :: Num a => a -> [a] -> [a]
- dx_d' :: Num t => t -> [t] -> (t, [t])
- d_dx_by :: (t -> t -> u) -> [t] -> [u]
- d_dx :: Num a => [a] -> [a]
- difference :: Eq a => [a] -> [a] -> [a]
- is_subset :: Eq a => [a] -> [a] -> Bool
- is_superset :: Eq a => [a] -> [a] -> Bool
- subsequence :: Eq a => [a] -> [a] -> Bool
- elem_index_unique :: Eq a => a -> [a] -> Int
- lookup_err_msg :: (Eq k, Show k) => String -> k -> [(k, v)] -> v
- lookup_err :: Eq k => k -> [(k, v)] -> v
- lookup_def :: Eq k => k -> v -> [(k, v)] -> v
- reverse_lookup :: Eq b => b -> [(a, b)] -> Maybe a
- find_bounds' :: (t -> s -> Ordering) -> [(t, t)] -> s -> Either ((t, t), Ordering) (t, t)
- decide_nearest' :: Ord o => (p -> o) -> (p, p) -> p
- decide_nearest :: (Num o, Ord o) => o -> (o, o) -> o
- find_nearest_err :: (Num n, Ord n) => [n] -> n -> n
- find_nearest :: (Num n, Ord n) => [n] -> n -> Maybe n
- find_bounds_scl :: Bool -> (t -> s -> Ordering) -> [(t, t)] -> s -> Maybe (t, t)
- find_bounds :: Bool -> (t -> s -> Ordering) -> [t] -> s -> Maybe (t, t)
- drop_last :: [t] -> [t]
- dropRight :: Int -> [a] -> [a]
- dropWhileRight :: (a -> Bool) -> [a] -> [a]
- take_right :: Int -> [a] -> [a]
- take_while_right :: (a -> Bool) -> [a] -> [a]
- at_head :: (a -> b) -> (a -> b) -> [a] -> [b]
- at_last :: (a -> b) -> (a -> b) -> [a] -> [b]
- separate_last' :: [a] -> ([a], Maybe a)
- separate_last :: [a] -> ([a], a)
- indicate_repetitions :: Eq a => [a] -> [Maybe a]
- zip_with_adj :: (a -> a -> b) -> [a] -> [b]
- compare_adjacent_by :: (a -> a -> Ordering) -> [a] -> [Ordering]
- compare_adjacent :: Ord a => [a] -> [Ordering]
- adjacent_groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
- group_ranges :: (Num t, Eq t) => [t] -> [(t, t)]
- group_just :: [Maybe a] -> [[Maybe a]]
- all_equal :: Eq a => [a] -> Bool
- all_eq :: Eq n => [n] -> Bool
- sort_group_on :: Ord b => (a -> b) -> [a] -> [[a]]
- mcons :: Maybe a -> [a] -> [a]
- type Compare_F a = a -> a -> Ordering
- two_stage_compare :: Compare_F a -> Compare_F a -> Compare_F a
- n_stage_compare :: [Compare_F a] -> Compare_F a
- sort_to :: Ord i => [e] -> [i] -> [e]
- sort_on :: Ord i => [i] -> [e] -> [e]
- sort_by_two_stage :: (Ord b, Ord c) => (a -> b) -> (a -> c) -> [a] -> [a]
- sort_by_n_stage :: Ord b => [a -> b] -> [a] -> [a]
- merge_by :: Compare_F a -> [a] -> [a] -> [a]
- merge_on :: Ord x => (a -> x) -> [a] -> [a] -> [a]
- merge_by_two_stage :: Ord b => (a -> b) -> Compare_F c -> (a -> c) -> [a] -> [a] -> [a]
- merge :: Ord a => [a] -> [a] -> [a]
- merge_set_by :: (a -> a -> Ordering) -> [[a]] -> [a]
- merge_set :: Ord a => [[a]] -> [a]
- merge_by_resolve :: (a -> a -> a) -> Compare_F a -> [a] -> [a] -> [a]
- find_non_ascending :: (a -> a -> Ordering) -> [a] -> Maybe (a, a)
- is_ascending_by :: (a -> a -> Ordering) -> [a] -> Bool
- is_ascending :: Ord a => [a] -> Bool
- elem_ordered :: Ord t => t -> [t] -> Bool
- elemIndex_ordered :: Ord t => t -> [t] -> Maybe Int
- zip_with_kr :: (a -> b -> c) -> [a] -> [b] -> ([c], [b])
- zip_with_perhaps_rhs :: (a -> b -> Either c c) -> (a -> c) -> [a] -> [b] -> [c]
- fill_gaps_ascending :: (Enum n, Ord n) => t -> (n, n) -> [(n, t)] -> [(n, t)]
- fill_gaps_ascending' :: (Num n, Enum n, Ord n) => t -> (n, n) -> [(n, t)] -> [(n, t)]
- minmax :: Ord t => [t] -> (t, t)
- bimap1 :: (t -> u) -> (t, t) -> (u, u)
- pad_right :: a -> Int -> [a] -> [a]
- pad_left :: a -> Int -> [a] -> [a]
- embedding :: Eq t => ([t], [t]) -> Either [Int] [Int]
- embedding_err :: Eq t => ([t], [t]) -> [Int]
- is_embedding :: Eq t => [t] -> [t] -> Bool
- all_embeddings_m :: (Eq t, MonadLogic m) => [t] -> [t] -> m [Int]
- all_embeddings :: Eq t => [t] -> [t] -> [[Int]]
- unlist1 :: [t] -> Maybe t
- unlist1_err :: [t] -> t
- adopt_shape :: Traversable t => (a -> b -> c) -> [b] -> t a -> t c
- adopt_shape_m :: Traversable t => (a -> b -> c) -> [b] -> t (Maybe a) -> t (Maybe c)
- group_tree :: (a -> Bool, a -> Bool) -> [a] -> Tree (Maybe a)
- remove_ix :: Int -> [a] -> [a]
- operate_ixs :: Bool -> [Int] -> [a] -> [a]
- select_ixs :: [Int] -> [a] -> [a]
- remove_ixs :: [Int] -> [a] -> [a]
- replace_ix :: (a -> a) -> Int -> [a] -> [a]
- at_cyclic :: [a] -> Int -> a
Documentation
slice :: Int -> Int -> [a] -> [a] Source #
Data.Vector.slice, ie. starting index (zero-indexed) and number of elements.
slice 4 5 [1..] == [5,6,7,8,9]
section :: Int -> Int -> [a] -> [a] Source #
Variant of slice with start and end indices (zero-indexed).
section 4 8 [1..] == [5,6,7,8,9]
bracket :: (a, a) -> [a] -> [a] Source #
Bracket sequence with left and right values.
bracket ('<','>') "1,2,3" == "<1,2,3>"
unbracket' :: [a] -> (Maybe a, [a], Maybe a) Source #
unbracket :: [t] -> Maybe (t, [t], t) Source #
The first & middle & last elements of a list.
unbracket "[12]" == Just ('[',"12",']')
unbracket_err :: [t] -> (t, [t], t) Source #
bracket_l :: ([a], [a]) -> [a] -> [a] Source #
Variant where brackets are sequences.
bracket_l ("<:",":>") "1,2,3" == "<:1,2,3:>"
Split
separate_at :: Eq a => [a] -> [a] -> Maybe ([a], [a]) Source #
Relative of splitOn
, but only makes first separation.
splitOn "//" "lhs//rhs//rem" == ["lhs","rhs","rem"] separate_at "//" "lhs//rhs//rem" == Just ("lhs","rhs//rem")
split_before :: Eq a => a -> [a] -> [[a]] Source #
Split before the indicated element.
split_before 'x' "axbcxdefx" == ["a","xbc","xdef","x"] split_before 'x' "xa" == ["","xa"]
map (flip split_before "abcde") "ae_" == [["","abcde"],["abcd","e"],["abcde"]] map (flip break "abcde" . (==)) "ae_" == [("","abcde"),("abcd","e"),("abcde","")]
Rotate
genericRotate_left :: Integral i => i -> [a] -> [a] Source #
Generic form of rotate_left
.
rotate_left :: Int -> [a] -> [a] Source #
Left rotation.
rotate_left 1 [1..3] == [2,3,1] rotate_left 3 [1..5] == [4,5,1,2,3]
genericRotate_right :: Integral n => n -> [a] -> [a] Source #
Generic form of rotate_right
.
rotate_right :: Int -> [a] -> [a] Source #
Right rotation.
rotate_right 1 [1..3] == [3,1,2]
rotate :: Integral n => n -> [a] -> [a] Source #
Rotate left by n mod
#p places.
rotate 1 [1..3] == [2,3,1] rotate 8 [1..5] == [4,5,1,2,3]
rotate_r :: Integral n => n -> [a] -> [a] Source #
Rotate right by n places.
rotate_r 8 [1..5] == [3,4,5,1,2]
rotate_starting_from :: Eq a => a -> [a] -> Maybe [a] Source #
Rotate list so that is starts at indicated element.
rotate_starting_from 'c' "abcde" == Just "cdeab" rotate_starting_from '_' "abc" == Nothing
rotate_starting_from_err :: Eq a => a -> [a] -> [a] Source #
Erroring variant.
adj :: Int -> Int -> [a] -> [[a]] Source #
Sequence of n adjacent elements, moving forward by k places. The last element may have fewer than n places, but will reach the end of the input sequence.
adj 3 2 "adjacent" == ["adj","jac","cen","nt"]
adj' :: Int -> Int -> [a] -> [[a]] Source #
Variant of adj
where the last element has n places but may
not reach the end of the input sequence.
adj' 3 2 "adjacent" == ["adj","jac","cen"]
genericAdj2 :: Integral n => n -> [t] -> [(t, t)] Source #
Generic form of adj2
.
adj2 :: Int -> [t] -> [(t, t)] Source #
Adjacent elements of list, at indicated distance, as pairs.
adj2 1 [1..5] == [(1,2),(2,3),(3,4),(4,5)] let l = [1..5] in zip l (tail l) == adj2 1 l adj2 2 [1..4] == [(1,2),(3,4)] adj2 3 [1..5] == [(1,2),(4,5)]
adj2_cyclic :: Int -> [t] -> [(t, t)] Source #
interleave :: [a] -> [a] -> [a] Source #
Interleave elements of p and q.
interleave [1..3] [4..6] == [1,4,2,5,3,6] interleave ".+-" "abc" == ".a+b-c" interleave [1..3] [] == []
interleave_set :: [[a]] -> [a] Source #
Interleave list of lists. Allows lists to be of non-equal lenghts.
interleave_set ["abcd","efgh","ijkl"] == "aeibfjcgkdhl" interleave_set ["abc","defg","hijkl"] == "adhbeicfjgkl"
deinterleave :: Int -> [a] -> [[a]] Source #
De-interleave n lists.
deinterleave 2 ".a+b-c" == [".+-","abc"] deinterleave 3 "aeibfjcgkdhl" == ["abcd","efgh","ijkl"]
deinterleave2 :: [t] -> ([t], [t]) Source #
Special case for two-part deinterleaving.
deinterleave2 ".a+b-c" == (".+-","abc")
interleave_continue :: [a] -> [a] -> [a] Source #
Variant that continues with the longer input.
interleave_continue ".+-" "abc" == ".a+b-c" interleave_continue [1..3] [] == [1..3] interleave_continue [] [1..3] == [1..3]
interleave_rotations :: Int -> Int -> [b] -> [b] Source #
interleave
of rotate_left
by i and j.
interleave_rotations 9 3 [1..13] == [10,4,11,5,12,6,13,7,1,8,2,9,3,10,4,11,5,12,6,13,7,1,8,2,9,3]
generic_histogram :: (Ord a, Integral i) => [a] -> [(a, i)] Source #
histogram :: Ord a => [a] -> [(a, Int)] Source #
Count occurences of elements in list.
map histogram ["","hohoh"] == [[],[('h',3),('o',2)]]
duplicates_by :: Ord a => (a -> a -> Bool) -> [a] -> [a] Source #
duplicates :: Ord a => [a] -> [a] Source #
Elements that appear more than once in the input.
map duplicates ["duplicates","redundant"] == ["","dn"]
segments :: Int -> Int -> [a] -> [[a]] Source #
List segments of length i at distance j.
segments 2 1 [1..5] == [[1,2],[2,3],[3,4],[4,5]] segments 2 2 [1..5] == [[1,2],[3,4]]
intersect_l :: Eq a => [[a]] -> [a] Source #
adj_intersect :: Eq a => Int -> [[a]] -> [[a]] Source #
Intersection of adjacent elements of list at distance n.
adj_intersect 1 [[1,2],[1,2,3],[1,2,3,4]] == [[1,2],[1,2,3]]
cycles :: Int -> [a] -> [[a]] Source #
List of cycles at distance n.
cycles 2 [1..6] == [[1,3,5],[2,4,6]] cycles 3 [1..9] == [[1,4,7],[2,5,8],[3,6,9]] cycles 4 [1..8] == [[1,5],[2,6],[3,7],[4,8]]
filter_halt :: (a -> Bool) -> (a -> Bool) -> [a] -> [a] Source #
replace :: Eq a => [a] -> [a] -> [a] -> [a] Source #
Replace all p with q in s.
replace "_x_" "-X-" "an _x_ string" == "an -X- string" replace "ab" "cd" "ab ab cd ab" == "cd cd cd cd"
replace_at :: Integral i => [a] -> i -> a -> [a] Source #
Replace the ith value at ns with x.
replace_at "test" 2 'n' == "tent"
Association lists
collate_on_adjacent :: (Eq k, Ord k) => (a -> k) -> (a -> v) -> [a] -> [(k, [v])] Source #
Given accesors for key and value collate adjacent values.
collate_adjacent :: Ord a => [(a, b)] -> [(a, [b])] Source #
collate_on_adjacent
of fst
and snd
.
collate_adjacent (zip "TDD" "xyz") == [('T',"x"),('D',"yz")]
collate_on :: Ord k => (a -> k) -> (a -> v) -> [a] -> [(k, [v])] Source #
sortOn
prior to collate_on_adjacent
.
let r = [('A',"a"),('B',"bd"),('C',"ce"),('D',"f")] in collate_on fst snd (zip "ABCBCD" "abcdef") == r
collate :: Ord a => [(a, b)] -> [(a, [b])] Source #
collate_on
of fst
and snd
.
collate (zip "TDD" "xyz") == [('D',"yz"),('T',"x")] collate (zip [1,2,1] "abc") == [(1,"ac"),(2,"b")]
uncollate :: [(k, [v])] -> [(k, v)] Source #
Reverse of collate
, inverse if order is not considered.
uncollate [(1,"ac"),(2,"b")] == zip [1,1,2] "acb"
with_key :: k -> [v] -> [(k, v)] Source #
Make assoc list with given key.
with_key 'a' [1..3] == [('a',1),('a',2),('a',3)]
dx_d :: Num a => a -> [a] -> [a] Source #
Intervals to values, zero is n.
dx_d 5 [1,2,3] == [5,6,8,11]
dx_d' :: Num t => t -> [t] -> (t, [t]) Source #
Variant that takes initial value and separates final value. This
is an appropriate function for mapAccumL
.
dx_d' 5 [1,2,3] == (11,[5,6,8]) dx_d' 0 [1,1,1] == (3,[0,1,2])
d_dx_by :: (t -> t -> u) -> [t] -> [u] Source #
Apply flip of f between elements of l.
d_dx_by (,) "abcd" == [('b','a'),('c','b'),('d','c')]
difference :: Eq a => [a] -> [a] -> [a] Source #
Elements of p not in q.
[1,2,3] `difference` [1,2] == [3]
is_superset :: Eq a => [a] -> [a] -> Bool Source #
subsequence :: Eq a => [a] -> [a] -> Bool Source #
Is p a subsequence of q, ie. synonym for isInfixOf
.
subsequence [1,2] [1,2,3] == True
elem_index_unique :: Eq a => a -> [a] -> Int Source #
Variant of elemIndices
that requires e to be unique in p.
elem_index_unique 'a' "abcda" == undefined
lookup_err_msg :: (Eq k, Show k) => String -> k -> [(k, v)] -> v Source #
Lookup that errors and prints message.
lookup_err :: Eq k => k -> [(k, v)] -> v Source #
Error variant.
lookup_def :: Eq k => k -> v -> [(k, v)] -> v Source #
lookup
variant with default value.
reverse_lookup :: Eq b => b -> [(a, b)] -> Maybe a Source #
Reverse lookup.
reverse_lookup 'c' [] == Nothing reverse_lookup 'c' (zip [0..4] ['a'..]) == Just 2
find_bounds' :: (t -> s -> Ordering) -> [(t, t)] -> s -> Either ((t, t), Ordering) (t, t) Source #
Basis of find_bounds_scl
, indicates if x is to the left or
right of the list, and it to the right whether equal or not.
Right
values will be correct if the list is not ascending,
however Left
values only make sense for ascending ranges.
map (find_bounds' compare [(0,1),(1,2)]) [-1,0,1,2,3]
decide_nearest' :: Ord o => (p -> o) -> (p, p) -> p Source #
decide_nearest :: (Num o, Ord o) => o -> (o, o) -> o Source #
Decide if value is nearer the left or right value of a range.
find_nearest_err :: (Num n, Ord n) => [n] -> n -> n Source #
Find the number that is nearest the requested value in an ascending list of numbers.
map (find_nearest_err [0,3.5,4,7]) [-1,1,3,5,7,9] == [0,0,3.5,4,7,7]
find_bounds_scl :: Bool -> (t -> s -> Ordering) -> [(t, t)] -> s -> Maybe (t, t) Source #
Basis of find_bounds
. There is an option to consider the last
element specially, and if equal to the last span is given.
find_bounds :: Bool -> (t -> s -> Ordering) -> [t] -> s -> Maybe (t, t) Source #
Find adjacent elements of list that bound element under given comparator.
let {f = find_bounds True compare [1..5] ;r = [Nothing,Just (1,2),Just (3,4),Just (4,5)]} in map f [0,1,3.5,5] == r
drop_last :: [t] -> [t] Source #
Special case of dropRight
.
map drop_last ["","?","remove"] == ["","","remov"]
dropRight :: Int -> [a] -> [a] Source #
Variant of drop
from right of list.
dropRight 1 [1..9] == [1..8]
dropWhileRight :: (a -> Bool) -> [a] -> [a] Source #
Variant of dropWhile
from right of list.
dropWhileRight Data.Char.isDigit "A440" == "A"
take_right :: Int -> [a] -> [a] Source #
take
from right.
take_right 3 "taking" == "ing"
take_while_right :: (a -> Bool) -> [a] -> [a] Source #
takeWhile
from right.
take_while_right Data.Char.isDigit "A440" == "440"
at_head :: (a -> b) -> (a -> b) -> [a] -> [b] Source #
Apply f at first element, and g at all other elements.
at_head negate id [1..5] == [-1,2,3,4,5]
at_last :: (a -> b) -> (a -> b) -> [a] -> [b] Source #
Apply f at all but last element, and g at last element.
at_last (* 2) negate [1..4] == [2,4,6,-4]
separate_last' :: [a] -> ([a], Maybe a) Source #
Separate list into an initial list and perhaps the last element tuple.
separate_last' [] == ([],Nothing)
separate_last :: [a] -> ([a], a) Source #
Error on null input.
separate_last [1..5] == ([1..4],5)
indicate_repetitions :: Eq a => [a] -> [Maybe a] Source #
Replace directly repeated elements with Nothing
.
indicate_repetitions "abba" == [Just 'a',Just 'b',Nothing,Just 'a']
zip_with_adj :: (a -> a -> b) -> [a] -> [b] Source #
zipWith
of list and it's own tail.
zip_with_adj (,) "abcde" == [('a','b'),('b','c'),('c','d'),('d','e')]
compare_adjacent_by :: (a -> a -> Ordering) -> [a] -> [Ordering] Source #
Type-specialised zip_with_adj
.
compare_adjacent :: Ord a => [a] -> [Ordering] Source #
compare_adjacent_by
of compare
.
compare_adjacent [0,1,3,2] == [LT,LT,GT]
adjacent_groupBy :: (a -> a -> Bool) -> [a] -> [[a]] Source #
groupBy
does not make adjacent comparisons, it
compares each new element to the start of the group. This function
is the adjacent variant.
groupBy (<) [1,2,3,2,4,1,5,9] == [[1,2,3,2,4],[1,5,9]] adjacent_groupBy (<) [1,2,3,2,4,1,5,9] == [[1,2,3],[2,4],[1,5,9]]
group_ranges :: (Num t, Eq t) => [t] -> [(t, t)] Source #
Reduce sequences of consecutive values to ranges.
group_ranges [-1,0,3,4,5,8,9,12] == [(-1,0),(3,5),(8,9),(12,12)] group_ranges [3,2,3,4,3] == [(3,3),(2,4),(3,3)]
group_just :: [Maybe a] -> [[Maybe a]] Source #
all_equal :: Eq a => [a] -> Bool Source #
Predicate to determine if all elements of the list are ==
.
all_equal "aaa" == True
sort_group_on :: Ord b => (a -> b) -> [a] -> [[a]] Source #
mcons :: Maybe a -> [a] -> [a] Source #
Maybe cons element onto list.
Nothing `mcons` "something" == "something" Just 's' `mcons` "omething" == "something"
Ordering
two_stage_compare :: Compare_F a -> Compare_F a -> Compare_F a Source #
If f compares EQ
, defer to g.
n_stage_compare :: [Compare_F a] -> Compare_F a Source #
Sequence of comparison functions, continue comparing until not EQ.
compare (1,0) (0,1) == GT n_stage_compare [compare `on` snd,compare `on` fst] (1,0) (0,1) == LT
sort_to :: Ord i => [e] -> [i] -> [e] Source #
Sort sequence a based on ordering of sequence b.
sort_to "abc" [1,3,2] == "acb" sort_to "adbce" [1,4,2,3,5] == "abcde"
sort_by_two_stage :: (Ord b, Ord c) => (a -> b) -> (a -> c) -> [a] -> [a] Source #
sort_by_n_stage :: Ord b => [a -> b] -> [a] -> [a] Source #
merge_by :: Compare_F a -> [a] -> [a] -> [a] Source #
Given a comparison function, merge two ascending lists.
mergeBy compare [1,3,5] [2,4] == [1..5]
merge_by_two_stage :: Ord b => (a -> b) -> Compare_F c -> (a -> c) -> [a] -> [a] -> [a] Source #
merge_set_by :: (a -> a -> Ordering) -> [[a]] -> [a] Source #
Merge list of sorted lists given comparison function. Note that
this is not equal to mergeAll
.
merge_set :: Ord a => [[a]] -> [a] Source #
merge_set_by
of compare
.
merge_set [[1,3,5,7,9],[2,4,6,8],[10]] == [1..10]
merge_by_resolve :: (a -> a -> a) -> Compare_F a -> [a] -> [a] -> [a] Source #
merge_by
variant that joins (resolves) equal elements.
let {left p _ = p ;right _ q = q ;cmp = compare `on` fst ;p = zip [1,3,5] "abc" ;q = zip [1,2,3] "ABC" ;left_r = [(1,'a'),(2,'B'),(3,'b'),(5,'c')] ;right_r = [(1,'A'),(2,'B'),(3,'C'),(5,'c')]} in merge_by_resolve left cmp p q == left_r && merge_by_resolve right cmp p q == right_r
find_non_ascending :: (a -> a -> Ordering) -> [a] -> Maybe (a, a) Source #
First non-ascending pair of elements.
is_ascending_by :: (a -> a -> Ordering) -> [a] -> Bool Source #
is_ascending :: Ord a => [a] -> Bool Source #
elem_ordered :: Ord t => t -> [t] -> Bool Source #
elemIndex_ordered :: Ord t => t -> [t] -> Maybe Int Source #
Variant of elemIndex
that operates on a sorted list, halting.
16 `elemIndex_ordered` [1,3 ..] == Nothing 16 `elemIndex_ordered` [0,1,4,9,16,25,36,49,64,81,100] == Just 4
zip_with_kr :: (a -> b -> c) -> [a] -> [b] -> ([c], [b]) Source #
Keep right variant of zipWith
, where unused rhs values are returned.
zip_with_kr (,) [1..3] ['a'..'e'] == ([(1,'a'),(2,'b'),(3,'c')],"de")
zip_with_perhaps_rhs :: (a -> b -> Either c c) -> (a -> c) -> [a] -> [b] -> [c] Source #
fill_gaps_ascending :: (Enum n, Ord n) => t -> (n, n) -> [(n, t)] -> [(n, t)] Source #
Fill gaps in a sorted association list, range is inclusive at both ends.
let r = [(1,'a'),(2,'x'),(3,'x'),(4,'x'),(5,'b'),(6,'x'),(7,'c'),(8,'x'),(9,'x')] in fill_gaps_ascending' 'x' (1,9) (zip [1,5,7] "abc") == r
fill_gaps_ascending' :: (Num n, Enum n, Ord n) => t -> (n, n) -> [(n, t)] -> [(n, t)] Source #
Direct definition.
Bimap
bimap1 :: (t -> u) -> (t, t) -> (u, u) Source #
Apply f to both elements of a two-tuple, ie. bimap
f f.
pad_right :: a -> Int -> [a] -> [a] Source #
Append k to the right of l until result has n places.
map (pad_right '0' 2 . return) ['0' .. '9'] pad_right '0' 12 "1101" == "110100000000" map (pad_right ' '3) ["S","E-L"] == ["S ","E-L"]
pad_left :: a -> Int -> [a] -> [a] Source #
Append k to the left of l until result has n places.
map (pad_left '0' 2 . return) ['0' .. '9']
Embedding
embedding :: Eq t => ([t], [t]) -> Either [Int] [Int] Source #
Locate first (leftmost) embedding of q in p.
Return partial indices for failure at Left
.
embedding ("embedding","ming") == Right [1,6,7,8] embedding ("embedding","mind") == Left [1,6,7]
embedding_err :: Eq t => ([t], [t]) -> [Int] Source #
is_embedding :: Eq t => [t] -> [t] -> Bool Source #
Does q occur in sequence, though not necessarily adjacently, in p.
is_embedding [1 .. 9] [1,3,7] == True is_embedding "embedding" "ming" == True is_embedding "embedding" "mind" == False
all_embeddings_m :: (Eq t, MonadLogic m) => [t] -> [t] -> m [Int] Source #
all_embeddings :: Eq t => [t] -> [t] -> [[Int]] Source #
Enumerate indices for all embeddings of q in p.
all_embeddings "all_embeddings" "leg" == [[1,4,12],[1,7,12],[2,4,12],[2,7,12]]
Un-list
unlist1_err :: [t] -> t Source #
Erroring variant.
Traversable
adopt_shape :: Traversable t => (a -> b -> c) -> [b] -> t a -> t c Source #
Replace elements at Traversable
with result of joining with elements from list.
let t = Node 0 [Node 1 [Node 2 [],Node 3 []],Node 4 []] putStrLn $ drawTree (fmap show t) let u = (adopt_shape (\_ x -> x) "abcde" t) putStrLn $ drawTree (fmap return u)
adopt_shape_m :: Traversable t => (a -> b -> c) -> [b] -> t (Maybe a) -> t (Maybe c) Source #
Variant of adopt_shape
that considers only Just
elements at Traversable
.
let {s = "a(b(cd)ef)ghi" ;t = group_tree (begin_end_cmp_eq '(' ')') s} in adopt_shape_m (,) [1..13] t
Tree
group_tree :: (a -> Bool, a -> Bool) -> [a] -> Tree (Maybe a) Source #
Given an Ordering
predicate where LT
opens a group, GT
closes a group, and EQ
continues current group, construct tree
from list.
let {l = "a {b {c d} e f} g h i" ;t = group_tree ((==) '{',(==) '}') l} in catMaybes (flatten t) == l
let {d = putStrLn . drawTree . fmap show} in d (group_tree ((==) '(',(==) ')') "a(b(cd)ef)ghi")
Indexing
remove_ix :: Int -> [a] -> [a] Source #
Remove element at index.
remove_ix 5 "remove" == "remov" remove_ix 5 "short" == undefined
operate_ixs :: Bool -> [Int] -> [a] -> [a] Source #
select_ixs :: [Int] -> [a] -> [a] Source #
remove_ixs :: [Int] -> [a] -> [a] Source #
replace_ix :: (a -> a) -> Int -> [a] -> [a] Source #
Replace element at i in p by application of f.
replace_ix negate 1 [1..3] == [1,-2,3]