hmt-base-0.20: Haskell Music Theory Base
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.List

Description

List functions.

Synopsis

Documentation

slice :: Int -> Int -> [a] -> [a] Source #

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>"

bracket_l :: ([a], [a]) -> [a] -> [a] Source #

Variant where brackets are sequences.

bracket_l ("<:",":>") "1,2,3" == "<:1,2,3:>"

unbracket_el :: [a] -> (Maybe a, [a], Maybe a) Source #

The first & middle & last elements of a list.

map unbracket_el ["","{12}"] == [(Nothing,"",Nothing),(Just '{',"12",Just '}')]

unbracket :: [t] -> Maybe (t, [t], t) Source #

The first & middle & last elements of a list.

map unbracket ["","{12}"] == [Nothing,Just ('{',"12",'}')]

unbracket_err :: [t] -> (t, [t], t) Source #

Erroring variant.

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_when_keeping_left :: (a -> Bool) -> [a] -> [[a]] Source #

Variant of splitWhen that keeps delimiters at left.

split_when_keeping_left (== 'r') "rab rcd re rf r" == ["","rab ","rcd ","re ","rf ","r"]

split_before :: Eq a => a -> [a] -> [[a]] Source #

Split before the indicated element, keeping it at the left of the sub-sequence it begins. split_when_keeping_left of ==

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","")]
split_before 'r' "rab rcd re rf r" == ["","rab ","rcd ","re ","rf ","r"]

split_before_any :: Eq a => [a] -> [a] -> [[a]] Source #

Split before any of the indicated set of delimiters.

split_before_any ",;" ";a,b,c;d;" == ["",";a",",b",",c",";d",";"]

split_on_1 :: Eq t => [t] -> [t] -> Maybe ([t], [t]) Source #

Singleton variant of splitOn.

split_on_1 ":" "graph:layout" == Just ("graph","layout")

split_on_1_err :: Eq t => [t] -> [t] -> ([t], [t]) Source #

Erroring variant.

split1 :: Eq a => a -> [a] -> Maybe ([a], [a]) Source #

Split function that splits only once, ie. a variant of break.

split1 ' ' "three word sentence" == Just ("three","word sentence")

split1_err :: (Eq a, Show a) => a -> [a] -> ([a], [a]) Source #

Erroring variant.

split_into_halves :: [t] -> ([t], [t]) Source #

If length is not even the second "half" is longer.

split_into_halves [] == ([],[])
split_into_halves [1] == ([],[1])
split_into_halves [1 .. 2] == ([1],[2])
split_into_halves [1 .. 8] == ([1,2,3,4],[5,6,7,8])
split_into_halves [1 .. 9] == ([1,2,3,4],[5,6,7,8,9])

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. Therefore negative n rotate right.

rotate 1 [1..3] == [2,3,1]
rotate 8 [1..5] == [4,5,1,2,3]
(rotate (-1) "ABCD",rotate 1 "ABCD") == ("DABC","BCDA")

rotate_r :: Integral n => n -> [a] -> [a] Source #

Rotate right by n places.

rotate_r 8 [1..5] == [3,4,5,1,2]

rotations :: [a] -> [[a]] Source #

All rotations.

rotations [0,1,3] == [[0,1,3],[1,3,0],[3,0,1]]

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_trunc :: 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_trunc 4 1 "adjacent" == ["adja","djac","jace","acen","cent"]
adj_trunc 3 2 "adjacent" == ["adj","jac","cen"]

adj_cyclic_trunc :: Int -> Int -> [a] -> [[a]] Source #

adj_trunc of close by n-1.

adj_cyclic_trunc 3 1 "adjacent" == ["adj","dja","jac","ace","cen","ent","nta","tad"]

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)]

close :: Int -> [a] -> [a] Source #

Append first n-elements to end of list.

close 1 [1..3] == [1,2,3,1]

adj2_cyclic :: Int -> [t] -> [(t, t)] Source #

adj2 . close 1.

adj2_cyclic 1 [1..3] == [(1,2),(2,3),(3,1)]

adj3 :: Int -> [t] -> [(t, t, t)] Source #

Adjacent triples.

adj3 3 [1..6] == [(1,2,3),(4,5,6)]

adj3_cyclic :: Int -> [t] -> [(t, t, t)] Source #

adj3 . close 2.

adj3_cyclic 1 [1..4] == [(1,2,3),(2,3,4),(3,4,1),(4,1,2)]

adj4 :: Int -> [t] -> [(t, t, t, t)] Source #

Adjacent quadruples.

adj4 2 [1..8] == [(1,2,3,4),(3,4,5,6),(5,6,7,8)]
adj4 4 [1..8] == [(1,2,3,4),(5,6,7,8)]

interleave :: [a] -> [a] -> [a] Source #

Interleave elements of p and q. If not of equal length elements are discarded.

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]

rezip :: ([t] -> [u]) -> ([v] -> [w]) -> [(t, v)] -> [(u, w)] Source #

unzip, apply f1 and f2 and zip.

generic_histogram_by :: Integral i => (a -> a -> Bool) -> Maybe (a -> a -> Ordering) -> [a] -> [(a, i)] Source #

Generalised histogram, with equality function for grouping and comparison function for sorting.

histogram_by :: (a -> a -> Bool) -> Maybe (a -> a -> Ordering) -> [a] -> [(a, Int)] Source #

Type specialised generic_histogram_by.

generic_histogram :: (Ord a, Integral i) => [a] -> [(a, i)] Source #

Count occurences of elements in list, histogram_by of == and compare.

histogram :: Ord a => [a] -> [(a, Int)] Source #

Type specialised generic_histogram. Elements will be in ascending order.

map histogram ["","hohoh","yxx"] == [[],[('h',3),('o',2)],[('x',2),('y',1)]]

histogram_join :: Ord a => [(a, Int)] -> [(a, Int)] -> [(a, Int)] Source #

Join two histograms, which must be sorted.

histogram_join (zip "ab" [1,1]) (zip "bc" [1,1]) == zip "abc" [1,2,1]

histogram_merge :: Ord a => [[(a, Int)]] -> [(a, Int)] Source #

foldr of histogram_join.

let f x = zip x (repeat 1) in histogram_merge (map f ["ab","bcd","de"]) == zip "abcde" [1,2,1,2,1]

histogram_fill :: (Ord a, Enum a) => [(a, Int)] -> [(a, Int)] Source #

Given (k,#) histogram where k is enumerable generate filled histogram with 0 for empty k.

histogram_fill (histogram "histogram") == zip ['a'..'t'] [1,0,0,0,0,0,1,1,1,0,0,0,1,0,1,0,0,1,1,1]

histogram_composite :: Ord a => [(a, Int)] -> [(a, Int)] -> [(a, (Int, Int))] Source #

Given two histograms p & q (sorted by key) make composite histogram giving for all keys the counts for (p,q).

r = zip "ABCDE" (zip [4,3,2,1,0] [2,3,4,0,5])
histogram_composite (zip "ABCD" [4,3,2,1]) (zip "ABCE" [2,3,4,5]) == r

histogram_diff :: Ord a => [(a, Int)] -> [(a, Int)] -> [(a, Int)] Source #

Apply - at count of histogram_composite, ie. 0 indicates equal number at p and q, negative indicates more elements at p than q and positive more elements at q than p.

histogram_diff (zip "ABCD" [4,3,2,1]) (zip "ABCE" [2,3,4,5]) == zip "ABCDE" [-2,0,2,-1,5]

duplicates_by :: Ord a => (a -> a -> Bool) -> [a] -> [a] Source #

Elements that appear more than once in the input given equality predicate.

duplicates :: Ord a => [a] -> [a] Source #

duplicates_by of ==.

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 #

foldl1 intersect.

intersect_l [[1,2],[1,2,3],[1,2,3,4]] == [1,2]

union_l :: Eq a => [[a]] -> [a] Source #

foldl1 union.

sort (union_l [[1,3],[2,3],[3]]) == [1,2,3]

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 #

Variant of filter that has a predicate to halt processing, ie. filter of takeWhile.

filter_halt (even . fst) ((< 5) . snd) (zip [1..] [0..])

filter_maybe :: (a -> Bool) -> [a] -> [Maybe a] Source #

Variant of filter that retains Nothing as a placeholder for removed elements.

filter_maybe even [1..4] == [Nothing,Just 2,Nothing,Just 4]

filterInRange :: Ord a => (a, a) -> [a] -> [a] Source #

Select only the elements from the list that lie in the indicated range, which is (inclusive, exclusive).

filterInRange (3, 5) [1, 1.5 .. 9] == [3.0,3.5,4.0,4.5]

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"

strip_prefix :: Eq a => [a] -> [a] -> Maybe [a] Source #

Data.List.stripPrefix, which however hugs doesn't know of.

strip_prefix_err :: Eq t => [t] -> [t] -> [t] Source #

Association lists

group_by_on :: (x -> x -> Bool) -> (t -> x) -> [t] -> [[t]] Source #

Equivalent to groupBy eq on f.

group_by_on (==) snd (zip [0..] "abbc") == [[(0,'a')],[(1,'b'),(2,'b')],[(3,'c')]]

group_on :: Eq x => (a -> x) -> [a] -> [[a]] Source #

group_by_on of ==.

r = [[(1,'a'),(1,'b')],[(2,'c')],[(3,'d'),(3,'e')],[(4,'f')]]
group_on fst (zip [1,1,2,3,3,4] "abcdef") == r

collate_by_on_adjacent :: (k -> k -> Bool) -> (a -> k) -> (a -> v) -> [a] -> [(k, [v])] Source #

Given an equality predicate and accesors for key and value collate adjacent values.

collate_on_adjacent :: Eq k => (a -> k) -> (a -> v) -> [a] -> [(k, [v])] Source #

collate_adjacent :: Eq a => [(a, b)] -> [(a, [b])] Source #

collate_on_adjacent of fst and snd.

collate_adjacent (zip "TDD" "xyz") == [('T',"x"),('D',"yz")]

sort_on :: Ord b => (a -> b) -> [a] -> [a] Source #

Data.List.sortOn, which however hugs doesn't know of.

collate_on :: Ord k => (a -> k) -> (a -> v) -> [a] -> [(k, [v])] Source #

sortOn prior to collate_on_adjacent.

r = [('A',"a"),('B',"bd"),('C',"ce"),('D',"f")]
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)]

assoc_merge :: Eq k => [(k, v)] -> [(k, v)] -> [(k, v)] Source #

Left biased merge of association lists p and q.

assoc_merge [(5,"a"),(3,"b")] [(5,"A"),(7,"C")] == [(5,"a"),(3,"b"),(7,"C")]

ord_map_locate :: Ord k => [(k, v)] -> k -> Maybe (k, v) Source #

Keys are in ascending order, the entry retrieved is the rightmose with a key less than or equal to the key requested. If the key requested is less than the initial key, or the list is empty, returns Nothing.

let m = [(1,'a'),(4,'x'),(4,'b'),(5,'c')]
mapMaybe (ord_map_locate m) [1 .. 6] == [(1,'a'),(1,'a'),(1,'a'),(4,'b'),(5,'c'),(5,'c')]
ord_map_locate m 0 == Nothing

Δ

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 #

Integration with f, ie. apply flip of f between elements of l.

d_dx_by (,) "abcd" == [('b','a'),('c','b'),('d','c')]
d_dx_by (-) [0,2,4,1,0] == [2,2,-3,-1]
d_dx_by (-) [2,3,0,4,1] == [1,-3,4,-3]

d_dx :: Num a => [a] -> [a] Source #

Integrate, d_dx_by -, ie. pitch class segment to interval sequence.

d_dx [5,6,8,11] == [1,2,3]
d_dx [] == []

difference :: Eq a => [a] -> [a] -> [a] Source #

Elements of p not in q.

[1,2,3] `difference` [1,2] == [3]

is_subset :: Eq a => [a] -> [a] -> Bool Source #

Is p a subset of q, ie. is intersect of p and q == p.

map (is_subset [1,2]) [[1],[1,2],[1,2,3]] == [False,True,True]

is_proper_subset :: Eq a => [a] -> [a] -> Bool Source #

Is p a proper subset of q, is_subset and not equal.

map (is_proper_subset [1,2]) [[1],[1,2],[1,2,3]] == [False,False,True]

is_superset :: Eq a => [a] -> [a] -> Bool Source #

Is p a superset of q, ie. flip is_subset.

is_superset [1,2,3] [1,2] == True

subsequence :: Eq a => [a] -> [a] -> Bool Source #

Is p a subsequence of q, ie. synonym for isInfixOf.

subsequence [1,2] [1,2,3] == True

findIndex_err :: (a -> Bool) -> [a] -> Int Source #

Erroring variant of findIndex.

elemIndex_err :: Eq a => a -> [a] -> Int Source #

Erroring variant of elemIndex.

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 and key.

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.

non_empty :: [t] -> Maybe [t] Source #

If l is empty Nothing, else Just l.

lookup_set :: Eq k => k -> [(k, v)] -> Maybe [v] Source #

Variant on filter that selects all matches.

lookup_set 1 (zip [1,2,3,4,1] "abcde") == Just "ae"

lookup_set_err :: Eq k => k -> [(k, v)] -> [v] Source #

Erroring variant.

reverse_lookup :: Eq v => v -> [(k, v)] -> Maybe k Source #

Reverse lookup.

reverse_lookup 'c' [] == Nothing
reverse_lookup 'b' (zip [1..] ['a'..]) == Just 2
lookup 2 (zip [1..] ['a'..]) == Just 'b'

reverse_lookup_err :: Eq v => v -> [(k, v)] -> k Source #

Erroring variant.

find_err :: (t -> Bool) -> [t] -> t Source #

Erroring variant of find.

find_bounds_cmp :: (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 if 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_cmp compare [(0,1),(1,2)]) [-1,0,1,2,3]

decide_nearest_f :: Ord o => Bool -> (p -> o) -> (p, p) -> (x, x) -> x Source #

Decide if value is nearer the left or right value of a range, return fst or snd.

decide_nearest :: (Num o, Ord o) => Bool -> o -> (o, o) -> (x, x) -> x Source #

decide_nearest_f with abs of - as measure.

(decide_nearest True 2 (1,3)) ("left","right") == "left"

find_nearest_by :: (Ord n, Num n) => (t -> n) -> Bool -> [t] -> n -> t Source #

sel_f gets comparison key from t.

find_nearest_err :: (Num n, Ord n) => Bool -> [n] -> n -> n Source #

Find the number that is nearest the requested value in an ascending list of numbers.

map (find_nearest_err True [0,3.5,4,7]) [-1,1,3,5,7,9] == [0,0,3.5,4,7,7]

find_nearest :: (Num n, Ord n) => Bool -> [n] -> n -> Maybe n Source #

find_nearest_err allowing null input list (which returns Nothing)

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.

scl=special-case-last

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"

drop_while_end :: (a -> Bool) -> [a] -> [a] Source #

Data.List.dropWhileEnd, which however hugs doesn't know of.

drop_while_right :: (a -> Bool) -> [a] -> [a] Source #

foldr form of dropWhileRight.

drop_while_right Data.Char.isDigit "A440" == "A"

take_right :: Int -> [a] -> [a] Source #

take from right.

take_right 3 "taking" == "ing"

takeWhileRight :: (a -> Bool) -> [a] -> [a] Source #

takeWhile from right.

takeWhileRight Data.Char.isDigit "A440" == "440"

take_while_right :: (a -> Bool) -> [a] -> [a] Source #

foldr form of takeWhileRight.

take_while_right Data.Char.isDigit "A440" == "440"

maybe_take :: Maybe Int -> [a] -> [a] Source #

Variant of take that allows Nothing to indicate the complete list.

maybe_take (Just 5) [1 .. ] == [1 .. 5]
maybe_take Nothing [1 .. 9] == [1 .. 9]

take_until :: (a -> Bool) -> [a] -> [a] Source #

Take until f is true. This is not the same as not at takeWhile because it keeps the last element. It is an error if the predicate never succeeds.

take_until (== 'd') "tender" == "tend"
takeWhile (not . (== 'd')) "tend" == "ten"
take_until (== 'd') "seven" == undefined

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]

headTail :: [a] -> (a, [a]) Source #

Head and tail of list. Useful to avoid "incomplete-uni-patterns" warnings. It's an error if the list is empty.

firstSecond :: [t] -> (t, t) Source #

First and second elements of list. Useful to avoid "incomplete-uni-patterns" warnings. It's an error if the list has less than two elements.

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 #

groupBy on structure of Maybe, ie. all Just compare equal.

let r = [[Just 1],[Nothing,Nothing],[Just 4,Just 5]]
in group_just [Just 1,Nothing,Nothing,Just 4,Just 5] == r

all_equal :: Eq a => [a] -> Bool Source #

Predicate to determine if all elements of the list are ==.

all_equal "aaa" == True

all_eq :: Eq n => [n] -> Bool Source #

Variant using nub.

nub_on :: Eq b => (a -> b) -> [a] -> [a] Source #

nubBy == on f.

nub_on snd (zip "ABCD" "xxyy") == [('A','x'),('C','y')]

sort_group_on :: Ord b => (a -> b) -> [a] -> [[a]] Source #

group_on of sortOn.

let r = [[('1','a'),('1','c')],[('2','d')],[('3','b'),('3','e')]]
in sort_group_on fst (zip "13123" "abcde") == r

mcons :: Maybe a -> [a] -> [a] Source #

Maybe cons element onto list.

Nothing `mcons` "something" == "something"
Just 's' `mcons` "omething" == "something"

snoc :: a -> [a] -> [a] Source #

Cons onto end of list.

snoc 4 [1,2,3] == [1,2,3,4]

Ordering

type Compare_F a = a -> a -> Ordering Source #

Comparison function type.

two_stage_compare :: Compare_F a -> Compare_F a -> Compare_F a Source #

If f compares EQ, defer to g.

two_stage_compare_on :: (Ord i, Ord j) => (t -> i) -> (t -> j) -> t -> t -> Ordering Source #

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_to_rev :: Ord i => [i] -> [e] -> [e] Source #

flip of sort_to.

sort_to_rev [1,4,2,3,5] "adbce" == "abcde"

sort_by_two_stage_on :: (Ord b, Ord c) => (a -> b) -> (a -> c) -> [a] -> [a] Source #

sort_by_n_stage_on :: Ord b => [a -> b] -> [a] -> [a] Source #

merge_by :: Compare_F a -> [a] -> [a] -> [a] Source #

Given a comparison function, merge two ascending lists. Alias for mergeBy

merge_by compare [1,3,5] [2,4] == [1..5]

merge_on :: Ord x => (a -> x) -> [a] -> [a] -> [a] Source #

merge_by_two_stage :: Ord b => (a -> b) -> Compare_F c -> (a -> c) -> [a] -> [a] -> [a] Source #

merge :: Ord a => [a] -> [a] -> [a] Source #

Alias for merge

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
merge_by_resolve (\x _ -> x) (compare `on` fst) [(0,'A'),(1,'B'),(4,'E')] (zip [1..] "bcd")

asc_seq_left_biased_merge_by :: (a -> a -> Ordering) -> [a] -> [a] -> [a] Source #

Merge two sorted (ascending) sequences. Where elements compare equal, select element from left input.

asc_seq_left_biased_merge_by (compare `on` fst) [(0,'A'),(1,'B'),(4,'E')] (zip [1..] "bcd")

find_adj :: (a -> a -> Bool) -> [a] -> Maybe (a, a) Source #

Find the first two adjacent elements for which f is True.

find_adj (>) [1,2,3,3,2,1] == Just (3,2)
find_adj (>=) [1,2,3,3,2,1] == Just (3,3)

is_ascending :: Ord a => [a] -> Bool Source #

find_adj of >=

filter is_ascending (words "A AA AB ABB ABC ABA") == words "A AB ABC"

is_non_descending :: Ord a => [a] -> Bool Source #

find_adj of >

filter is_non_descending (words "A AA AB ABB ABC ABA") == ["A","AA","AB","ABB","ABC"]

elem_ordered :: Ord t => t -> [t] -> Bool Source #

Variant of elem that operates on a sorted list, halting. This is member.

16 `elem_ordered` [1,3 ..] == False
16 `elem` [1,3 ..] == undefined

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_maybe :: (a -> b -> Maybe c) -> [a] -> [b] -> [c] Source #

zipWith variant equivalent to mapMaybe (ie. catMaybes of zipWith)

zip_with_ext :: t -> u -> (t -> u -> v) -> [t] -> [u] -> [v] Source #

zipWith variant that extends shorter side using given value.

zip_ext :: t -> u -> [t] -> [u] -> [(t, u)] Source #

zip_with_ext of ','

let f = zip_ext 'i' 'j'
f "" "" == []
f "p" "" == zip "p" "j"
f "" "q" == zip "i" "q"
f "pp" "q" == zip "pp" "qj"
f "p" "qq" == zip "pi" "qq"

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 #

A zipWith variant that always consumes an element from the left hand side (lhs), but only consumes an element from the right hand side (rhs) if the zip function is Right and not if Left. There's also a secondary function to continue if the rhs ends before the lhs.

zip_list_with_list_of_list :: [p] -> [[q]] -> [[(p, q)]] Source #

Zip a list with a list of lists. Ordinarily the list has at least as many elements as there are elements at the list of lists. There is also a Traversable form of this called adopt_shape_2_zip_stream.

zip_list_with_list_of_list [1 ..] ["a", "list", "of", "strings"]
zip_list_with_list_of_list [1 .. 9] ["a", "list", "of", "strings"]

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.

minimumBy_or :: t -> (t -> t -> Ordering) -> [t] -> t Source #

Variant with default value for empty input list case.

minmax :: Ord t => [t] -> (t, t) Source #

minimum and maximum in one pass.

minmax "minmax" == ('a','x')

pad_right :: a -> Int -> [a] -> [a] Source #

Append k to the right of l until result has n places. Truncates long input lists.

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_right '!' 3 "truncate" == "tru"

pad_right_err :: t -> Int -> [t] -> [t] Source #

Variant that errors if the input list has more than n places.

map (pad_right_err '!' 3) ["x","xy","xyz","xyz!"]

pad_right_no_truncate :: a -> Int -> [a] -> [a] Source #

Variant that will not truncate long inputs.

pad_right_no_truncate '!' 3 "truncate" == "truncate"

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 #

fromRight of embedding

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

Un-list

unlist1 :: [t] -> Maybe t Source #

Unpack one element list.

unlist1_err :: [t] -> t Source #

Erroring variant.

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"
let t = group_tree ((==) '{',(==) '}') l
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.

map (remove_ix 5) ["remove","removed"] == ["remov","removd"]
remove_ix 5 "short" -- error

delete_at :: (Eq t, Num t) => t -> [a] -> [a] Source #

Delete element at ix from list (c.f. remove_ix, this has a more specific error if index does not exist).

delete_at 3 "deleted" == "delted"
delete_at 8 "deleted" -- error

operate_ixs :: Bool -> [Int] -> [a] -> [a] Source #

Select or remove elements at set of indices.

select_ixs :: [Int] -> [a] -> [a] Source #

Select elements at set of indices.

select_ixs [1,3] "select" == "ee"

remove_ixs :: [Int] -> [a] -> [a] Source #

Remove elements at set of indices.

remove_ixs [1,3,5] "remove" == "rmv"

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]

list_eq_ignoring_indices :: (Eq t, Integral i) => [i] -> [t] -> [t] -> Bool Source #

List equality, ignoring indicated indices.

list_eq_ignoring_indices [3,5] "abcdefg" "abc.e.g" == True

list_set_indices :: (Eq ix, Num ix) => [(ix, t)] -> [t] -> [t] Source #

Edit list to have v at indices k. Replacement assoc-list must be ascending. All replacements must be in range.

list_set_indices [(2,'C'),(4,'E')] "abcdefg" == "abCdEfg"
list_set_indices [] "abcdefg" == "abcdefg"
list_set_indices [(9,'I')] "abcdefg" == undefined

list_set_ix :: (Eq t, Num t) => t -> a -> [a] -> [a] Source #

Variant of list_set_indices with one replacement.

at_cyclic :: [a] -> Int -> a Source #

Cyclic indexing function.

map (at_cyclic "cycle") [0..9] == "cyclecycle"

atFromEnd :: [t] -> Int -> t Source #

Index list from the end, assuming the list is longer than n + 1.

atFromEnd [1 .. 30] 0 == 30 atFromEnd [1..100] 15 == 85