hmt-0.14: Haskell Music Theory

Safe HaskellSafe-Inferred

Music.Theory.List

Contents

Description

Shared list functions.

Synopsis

Documentation

bracket :: (a, a) -> [a] -> [a]Source

Bracket sequence with left and right values.

 bracket ('<','>') "1,2,3" == "<1,2,3>"

genericRotate_left :: Integral i => i -> [a] -> [a]Source

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

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

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

All rotations.

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

genericAdj2 :: Integral n => n -> [t] -> [(t, t)]Source

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

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

Append first element to end of list.

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

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

adj2 . close.

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

interleave :: [b] -> [b] -> [b]Source

Interleave elements of p and q.

 interleave [1..3] [4..6] == [1,4,2,5,3,6]

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

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

Association lists

collate :: Ord a => [(a, b)] -> [(a, [b])]Source

Collate values of equal keys at assoc list.

 collate [(1,'a'),(2,'b'),(1,'c')] == [(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 a => a -> [a] -> [a]Source

Intervals to values, zero is n.

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

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

Integrate, ie. pitch class segment to interval sequence.

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

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

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

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

is_superset :: Eq a => [a] -> [a] -> BoolSource

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

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

subsequence :: Eq a => [a] -> [a] -> BoolSource

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

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

elem_index_unique :: Eq a => a -> [a] -> IntSource

Variant of elemIndices that requires e to be unique in p.

 elem_index_unique 'a' "abcda" == undefined

find_bounds :: (t -> s -> Ordering) -> [(t, t)] -> s -> Maybe (t, t)Source

Find adjacent elements of list that bound element under given comparator.

 let f = find_bounds compare (adj [1..5])
 in map f [1,3.5,5] == [Just (1,2),Just (3,4),Nothing]

dropRight :: Int -> [a] -> [a]Source

Variant of drop from right of list.

 dropRight 1 [1..9] == [1..8]

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

group_just :: [Maybe a] -> [[Maybe a]]Source

mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]Source

Given a comparison function, merge two ascending lists.

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

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

merge_set :: Ord a => [[a]] -> [a]Source

merge a set of ordered sequences.

 merge_set [[1,3..9],[2,4..8],[10]] == [1..10]