Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
List functions.
- bracket :: (a, a) -> [a] -> [a]
- bracket_l :: ([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]]
- genericAdj2 :: Integral n => n -> [t] -> [(t, t)]
- adj2 :: Int -> [t] -> [(t, t)]
- close :: [a] -> [a]
- adj2_cyclic :: Int -> [t] -> [(t, t)]
- interleave :: [b] -> [b] -> [b]
- interleave_continue :: [a] -> [a] -> [a]
- interleave_rotations :: Int -> Int -> [b] -> [b]
- histogram :: (Ord a, Integral i) => [a] -> [(a, i)]
- 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]]
- collate_on :: (Eq k, Ord k) => (a -> k) -> (a -> v) -> [a] -> [(k, [v])]
- collate :: Ord a => [(a, b)] -> [(a, [b])]
- with_key :: k -> [v] -> [(k, v)]
- dx_d :: Num a => a -> [a] -> [a]
- dx_d' :: Num t => t -> [t] -> (t, [t])
- 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
- find_bounds' :: Bool -> (t -> s -> Ordering) -> [(t, t)] -> s -> Maybe (t, t)
- find_bounds :: Bool -> (t -> s -> Ordering) -> [t] -> s -> Maybe (t, t)
- dropRight :: Int -> [a] -> [a]
- dropWhileRight :: (a -> Bool) -> [a] -> [a]
- at_head :: (a -> b) -> (a -> b) -> [a] -> [b]
- at_last :: (a -> b) -> (a -> b) -> [a] -> [b]
- separate_last :: [a] -> ([a], a)
- indicate_repetitions :: Eq a => [a] -> [Maybe a]
- adjacent_groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
- group_just :: [Maybe a] -> [[Maybe a]]
- 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
- ordering_invert :: Ordering -> Ordering
- 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]
- merge_by :: Compare_F a -> [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]
- bimap1 :: (t -> u) -> (t, t) -> (u, u)
Documentation
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:>"
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]
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)] adj2 2 [1..4] == [(1,2),(3,4)] adj2 3 [1..5] == [(1,2),(4,5)]
adj2_cyclic :: Int -> [t] -> [(t, t)] Source
interleave :: [b] -> [b] -> [b] 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_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]
histogram :: (Ord a, Integral i) => [a] -> [(a, i)] Source
Count occurences of elements in list.
histogram "hohoh" == [('h',3),('o',2)]
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]]
Association lists
collate_on :: (Eq k, Ord k) => (a -> k) -> (a -> v) -> [a] -> [(k, [v])] Source
Given accesors for key and value collate input.
let r = [('A',"a"),('B',"bd"),('C',"ce"),('D',"f")] in collate_on fst snd (zip "ABCBCD" "abcdef")
collate :: Ord a => [(a, b)] -> [(a, [b])] Source
collate_on
of fst
and snd
.
collate (zip [1,2,1] "abc") == [(1,"ac"),(2,"b")]
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 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 :: Num a => [a] -> [a] Source
Integrate, 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_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
find_bounds' :: 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
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"
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], a) Source
Separate list into an initial list and a last element tuple.
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']
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_just :: [Maybe a] -> [[Maybe a]] Source
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
ordering_invert :: Ordering -> Ordering Source
Invert Ordering
.
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
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