hmt-0.16: Haskell Music Theory

Safe HaskellNone
LanguageHaskell98

Music.Theory.Contour.Polansky_1992

Contents

Description

Polansky, Larry and Bassein, Richard "Possible and Impossible Melody: Some Formal Aspects of Contour" Journal of Music Theory 36/2, 1992 (pp.259-284) (http://www.jstor.org/pss/843933)

Synopsis

Indices

adjacent_indices :: Integral i => i -> [(i, i)] Source #

Construct set of n - 1 adjacent indices, left right order.

adjacent_indices 5 == [(0,1),(1,2),(2,3),(3,4)]

all_indices :: Integral i => i -> [(i, i)] Source #

All (i,j) indices, in half matrix order.

all_indices 4 == [(0,1),(0,2),(0,3),(1,2),(1,3),(2,3)]

Matrix

type Matrix a = [[a]] Source #

A list notation for matrices.

matrix_f :: (a -> a -> b) -> [a] -> Matrix b Source #

Apply f to construct Matrix from sequence.

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

contour_matrix :: Ord a => [a] -> Matrix Ordering Source #

Construct matrix_f with compare (p.263).

contour_matrix [1..3] == [[EQ,LT,LT],[GT,EQ,LT],[GT,GT,EQ]]

Half matrix

half_matrix_f :: (a -> a -> b) -> [a] -> Matrix b Source #

Half Matrix of contour given comparison function f.

half_matrix_f (flip (-)) [2,10,6,7] == [[8,4,5],[-4,-3],[1]]
half_matrix_f (flip (-)) [5,0,3,2] == [[-5,-2,-3],[3,2],[-1]]
half_matrix_f compare [5,0,3,2] == [[GT,GT,GT],[LT,LT],[GT]]

Contour description

contour_description :: Ord a => [a] -> Contour_Description Source #

Construct Contour_Description of contour (p.264).

let c = [[3,2,4,1],[3,2,1,4]]
in map (show.contour_description) c == ["202 02 2","220 20 0"]

contour_description_ix :: Contour_Description -> (Int, Int) -> Ordering Source #

Ordering from ith to jth element of sequence described at d.

contour_description_ix (contour_description "abdc") (0,3) == LT

uniform :: Contour_Description -> Bool Source #

True if contour is all descending, equal or ascending.

let c = ["abc","bbb","cba"]
in map (uniform.contour_description) c == [True,True,True]

no_equalities :: Contour_Description -> Bool Source #

True if contour does not containt any EQ elements.

let c = ["abc","bbb","cba"]
map (no_equalities.contour_description) c == [True,False,True]

all_contours :: Int -> [Contour_Description] Source #

Set of all contour descriptions.

map (length.all_contours) [3,4,5] == [27,729,59049]

implication :: (Ordering, Ordering) -> Maybe Ordering Source #

A sequence of orderings (i,j) and (j,k) may imply ordering for (i,k).

map implication [(LT,EQ),(EQ,EQ),(EQ,GT)] == [Just LT,Just EQ,Just GT]

violations :: Contour_Description -> [(Int, Int, Int, Ordering)] Source #

List of all violations at a Contour_Description (p.266).

possible_contours :: Int -> [Contour_Description] Source #

All possible contour descriptions

map (length.possible_contours) [3,4,5] == [13,75,541]

impossible_contours :: Int -> [Contour_Description] Source #

All impossible contour descriptions

map (length.impossible_contours) [3,4,5] == [14,654,58508]

contour_description_lm :: Integral a => a -> a Source #

Calculate number of contours of indicated degree (p.263).

map contour_description_lm [2..7] == [1,3,6,10,15,21]
let r = [3,27,729,59049,14348907]
in map (\n -> 3 ^ n) (map contour_description_lm [2..6]) == r

contour_truncate :: Contour_Description -> Int -> Contour_Description Source #

Truncate a Contour_Description to have at most n elements.

let c = contour_description [3,2,4,1]
in contour_truncate c 3 == contour_description [3,2,4]

contour_is_prefix_of :: Contour_Description -> Contour_Description -> Bool Source #

Is Contour_Description p a prefix of q.

let {c = contour_description [3,2,4,1]
    ;d = contour_description [3,2,4]}
in d `contour_is_prefix_of` c == True

contour_eq_at :: Contour_Description -> Contour_Description -> Int -> Bool Source #

Are Contour_Descriptions p and q equal at column n.

let {c = contour_description [3,2,4,1,5]
    ;d = contour_description [3,2,4,1]}
in map (contour_eq_at c d) [0..4] == [True,True,True,True,False]

Contour drawing

draw_contour :: Integral i => Contour_Description -> [i] Source #

Derive an Integral contour that would be described by Contour_Description. Diverges for impossible contours.

draw_contour (contour_description "abdc") == [0,1,3,2]

contour_description_invert :: Contour_Description -> Contour_Description Source #

Invert Contour_Description.

let c = contour_description "abdc"
in draw_contour (contour_description_invert c) == [3,2,0,1]

Construction

type Build_f st e = st -> Maybe (e, st) Source #

Function to perhaps generate an element and a new state from an initial state. This is the function provided to unfoldr.

type Conforms_f e = Int -> [e] -> Bool Source #

Function to test is a partial sequence conforms to the target sequence.

build_f_n :: Build_f st e -> Build_f (Int, st) e Source #

Transform a Build_f to produce at most n elements.

let f i = Just (i,succ i)
in unfoldr (build_f_n f) (5,'a') == "abcde"

build_sequence :: Int -> Build_f st e -> Conforms_f e -> Int -> st -> (Maybe [e], st) Source #

Attempt to construct a sequence of n elements given a Build_f to generate possible elements, a Conforms_f that the result sequence must conform to at each step, an Int to specify the maximum number of elements to generate when searching for a solution, and an initial state.

let {b_f i = Just (i,i+1)
    ;c_f i x = odd (sum x `div` i)}
in build_sequence 6 b_f c_f 20 0 == (Just [1,2,6,11,15,19],20)

build_contour :: Ord e => Build_f st e -> Contour_Description -> Int -> st -> (Maybe [e], st) Source #

Attempt to construct a sequence that has a specified contour. The arguments are a Build_f to generate possible elements, a Contour_Description that the result sequence must conform to, an Int to specify the maximum number of elements to generate when searching for a solution, and an initial state.

import System.Random
let {f = Just . randomR ('a','z')
    ;c = contour_description "atdez"
    ;st = mkStdGen 2347}
in fst (build_contour f c 1024 st) == Just "nvruy"

build_contour_retry :: Ord e => Build_f st e -> Contour_Description -> Int -> Int -> st -> (Maybe [e], st) Source #

A variant on build_contour that retries a specified number of times using the final state of the failed attempt as the state for the next try.

let {f = Just . randomR ('a','z')
    ;c = contour_description "atdezjh"
    ;st = mkStdGen 2347}
in fst (build_contour_retry f c 64 8 st) == Just "nystzvu"

build_contour_set :: Ord e => Build_f st e -> Contour_Description -> Int -> Int -> st -> [[e]] Source #

A variant on build_contour_retry that returns the set of all sequences constructed.

let {f = Just . randomR ('a','z')
    ;c = contour_description "atdezjh"
    ;st = mkStdGen 2347}
in length (build_contour_set f c 64 64 st) == 60

build_contour_set_nodup :: Ord e => Build_f st e -> Contour_Description -> Int -> Int -> st -> [[e]] Source #

Variant of build_contour_set that halts when an generated sequence is a duplicate of an already generated sequence.

let {f = randomR ('a','f')
    ;c = contour_description "cafe"
    ;st = mkStdGen 2346836
    ;r = build_contour_set_nodup f c 64 64 st}
in filter ("c" `isPrefixOf`) r == ["cafe","cbed","caed"]

Examples

ex_1 :: [Rational] Source #

Example from p.262 (quarter-note durations)

ex_1 == [2,3/2,1/2,1,2]
compare_adjacent ex_1 == [GT,GT,LT,LT]
show (contour_half_matrix ex_1) == "2221 220 00 0"
draw_contour (contour_description ex_1) == [3,2,0,1,3]
let d = contour_description_invert (contour_description ex_1)
in (show d,is_possible d) == ("0001 002 22 2",True)

ex_2 :: [Integer] Source #

Example on p.265 (pitch)

ex_2 == [0,5,3]
show (contour_description ex_2) == "00 2"

ex_3 :: [Integer] Source #

Example on p.265 (pitch)

ex_3 == [12,7,6,7,8,7]
show (contour_description ex_3) == "22222 2101 000 01 2"
contour_description_ix (contour_description ex_3) (0,5) == GT
is_possible (contour_description ex_3) == True

ex_4 :: Contour_Description Source #

Example on p.266 (impossible)

show ex_4 == "2221 220 00 1"
is_possible ex_4 == False
violations ex_4 == [(0,3,4,GT),(1,3,4,GT)]