hmt-0.14: Haskell Music Theory

Safe HaskellSafe-Inferred

Music.Theory.Meter.Barlow_1987

Description

Clarence Barlow. "Two Essays on Theory". Computer Music Journal, 11(1):44-60, 1987. Translated by Henning Lohner.

Synopsis

Documentation

traceShow :: a -> b -> bSource

at :: Integral n => [a] -> n -> aSource

One indexed variant of genericIndex.

 map (at [11..13]) [1..3] == [11,12,13]

at' :: (Num a, Show a, Integral n, Show n, Show m) => m -> [a] -> n -> aSource

Variant of at with boundary rules and specified error message.

 map (at' 'x' [11..13]) [0..4] == [1,11,12,13,1]
 at' 'x' [0] 3 == undefined

mod' :: (Integral a, Show a) => a -> a -> aSource

Variant of mod with input constraints.

 mod' (-1) 2 == 1

type R = DoubleSource

Alias for Double (quieten compiler).

to_r :: (Integral n, Show n) => n -> RSource

Specialised variant of fromIntegral.

div' :: (Integral a, Show a) => String -> a -> a -> aSource

Variant on div with input constraints.

type Stratification t = [t]Source

A stratification is a tree of integral subdivisions.

indispensibilities :: (Integral n, Show n) => Stratification n -> [n]Source

Indispensibilities from stratification.

 indispensibilities [3,2,2] == [11,0,6,3,9,1,7,4,10,2,8,5]
 indispensibilities [2,3,2] == [11,0,6,2,8,4,10,1,7,3,9,5]
 indispensibilities [2,2,3] == [11,0,4,8,2,6,10,1,5,9,3,7]
 indispensibilities [3,5] == [14,0,9,3,6,12,1,10,4,7,13,2,11,5,8]

lower_psi :: (Integral a, Show a) => Stratification a -> a -> a -> aSource

The indispensibility measure (ψ).

 map (lower_psi [2] 1) [1..2] == [1,0]
 map (lower_psi [3] 1) [1..3] == [2,0,1]
 map (lower_psi [2,2] 2) [1..4] == [3,0,2,1]
 map (lower_psi [5] 1) [1..5] == [4,0,3,1,2]
 map (lower_psi [3,2] 2) [1..6] == [5,0,3,1,4,2]
 map (lower_psi [2,3] 2) [1..6] == [5,0,2,4,1,3]

reverse_primes :: (Integral n, Show n) => n -> [n]Source

The first nth primes, reversed.

 reverse_primes 14 == [43,41,37,31,29,23,19,17,13,11,7,5,3,2]

prime_stratification :: (Integral n, Show n) => n -> Stratification nSource

Generate prime stratification for n.

 map prime_stratification [2,3,5,7,11] == [[2],[3],[5],[7],[11]]
 map prime_stratification [6,8,9,12] == [[3,2],[2,2,2],[3,3],[3,2,2]]
 map prime_stratification [22,10,4,1] == [[11,2],[5,2],[2,2],[]]
 map prime_stratification [18,16,12] == [[3,3,2],[2,2,2,2],[3,2,2]]

upper_psi :: (Integral a, Show a) => a -> a -> aSource

Fundamental indispensibilities for prime numbers (Ψ).

 map (upper_psi 2) [1..2] == [1,0]
 map (upper_psi 3) [1..3] == [2,0,1]
 map (upper_psi 5) [1..5] == [4,0,3,1,2]
 map (upper_psi 7) [1..7] == [6,0,4,2,5,1,3]
 map (upper_psi 11) [1..11] == [10,0,6,4,9,1,7,3,8,2,5]
 map (upper_psi 13) [1..13] == [12,0,7,4,10,1,8,5,11,2,9,3,6]

thinning_table :: (Integral n, Show n) => Stratification n -> [[Bool]]Source

Table such that each subsequent row deletes the least indispensibile pulse.

 thinning_table [3,2] == [[True,True,True,True,True,True]
                         ,[True,False,True,True,True,True]
                         ,[True,False,True,False,True,True]
                         ,[True,False,True,False,True,False]
                         ,[True,False,False,False,True,False]
                         ,[True,False,False,False,False,False]]

thinning_table_pp :: (Integral n, Show n) => Stratification n -> StringSource

Trivial pretty printer for thinning_table.

 putStrLn (thinning_table_pp [3,2])
 putStrLn (thinning_table_pp [2,3])
 ******   ******
 *.****   *.****
 *.*.**   *.**.*
 *.*.*.   *..*.*
 *...*.   *..*..
 *.....   *.....

relative_to_length :: (Real a, Fractional b) => [a] -> [b]Source

Scale values against length of list minus one.

 relative_to_length [0..5] == [0.0,0.2,0.4,0.6,0.8,1.0]

relative_indispensibilities :: (Integral n, Show n) => Stratification n -> [R]Source

Variant of indispensibilities that scales value to lie in (0,1).

relative_indispensibilities [3,2] == [1,0,0.6,0.2,0.8,0.4]

align_meters :: (t -> [b]) -> t -> t -> [(b, b)]Source

Align two meters (given as stratifications) to least common multiple of their degrees. The indispensibilities function is given as an argument so that it may be relative if required. This generates Table 7 (p.58).

 let r = [(5,5),(0,0),(2,3),(4,1),(1,4),(3,2)]
 in align_meters indispensibilities [2,3] [3,2] == r
 let r = [(1,1),(0,0),(0.4,0.6),(0.8,0.2),(0.2,0.8),(0.6,0.4)]
 in align_meters relative_indispensibilities [2,3] [3,2] == r
 align_meters indispensibilities [2,2,3] [3,5]
 align_meters relative_indispensibilities [2,2,3] [3,5]

type S_MM t = ([t], t)Source

Type pairing a stratification and a tempo.

whole_div :: Integral a => a -> a -> aSource

Variant of div that requires mod be 0.

whole_quot :: Integral a => a -> a -> aSource

Variant of quot that requires rem be 0.

prolong_stratifications :: (Integral n, Show n) => S_MM n -> S_MM n -> ([n], [n])Source

Rule to prolong stratification of two S_MM values such that pulse at the deeper level are aligned. (Paragraph 2, p.58)

 let x = ([2,2,2],1)
 in prolong_stratifications x x == (fst x,fst x)
 let r = ([2,5,3,3,2],[3,2,5,5])
 in prolong_stratifications ([2,5],50) ([3,2],60) == r
 prolong_stratifications ([2,2,3],5) ([3,5],4) == ([2,2,3],[3,5])

mean :: Fractional a => [a] -> aSource

Arithmetic mean (average) of a list.

 mean [0..5] == 2.5

square :: Num a => a -> aSource

Square of n.

 square 5 == 25

align_s_mm :: (Integral n, Show n) => ([n] -> [t]) -> S_MM n -> S_MM n -> [(t, t)]Source

Composition of prolong_stratifications and align_meters.

 align_s_mm indispensibilities ([2,2,3],5) ([3,5],4)

upper_psi' :: (Integral a, Show a) => a -> a -> aSource

An attempt at Equation 5 of the CMJ paper. When n is h-1 the output is incorrect (it is the product of the correct values for n at h-1 and h).

 map (upper_psi' 5) [1..5] /= [4,0,3,1,2]
 map (upper_psi' 7) [1..7] /= [6,0,4,2,5,1,3]
 map (upper_psi' 11) [1..11] /= [10,0,6,4,9,1,7,3,8,2,5]
 map (upper_psi' 13) [1..13] /= [12,0,7,4,10,1,8,5,11,2,9,3,6]

mps_limit :: Floating a => a -> aSource

The MPS limit equation given on p.58.

 mps_limit 3 == 21 + 7/9

mean_square_product :: Fractional n => [(n, n)] -> nSource

The square of the product of the input sequence is summed, then divided by the square of the sequence length.

 mean_square_product [(0,0),(1,1),(2,2),(3,3)] == 6.125
 mean_square_product [(2,3),(4,5)] == (6^2 + 20^2) / 2^2

metrical_affinity :: (Integral n, Show n) => [n] -> n -> [n] -> n -> RSource

An incorrect attempt at the description in paragraph two of p.58 of the CMJ paper.

 let p ~= q = abs (p - q) < 1e-4
 metrical_affinity [2,3] 1 [3,2] 1 ~= 0.0324
 metrical_affinity [2,2,3] 20 [3,5] 16 ~= 0.0028

metrical_affinity' :: (Integral t, Show t) => [t] -> t -> [t] -> t -> RSource

An incorrect attempt at Equation 6 of the CMJ paper, see omega_z.

 let p ~= q = abs (p - q) < 1e-4
 metrical_affinity' [2,2,2] 1 [2,2,2] 1 ~= 1.06735
 metrical_affinity' [2,2,2] 1 [2,2,3] 1 ~= 0.57185
 metrical_affinity' [2,2,2] 1 [2,3,2] 1 ~= 0.48575
 metrical_affinity' [2,2,2] 1 [3,2,2] 1 ~= 0.45872
 metrical_affinity' [3,2,2] 3 [2,2,3] 2 ~= 0.10282