hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Metric.Buchler_1998

Description

Michael Buchler. "Relative Saturation of Subsets and Interval Cycles as a Means for Determining Set-Class Similarity". PhD thesis, University of Rochester, 1998

Synopsis

Documentation

of_c :: Integral n => n -> [a] -> Bool Source #

Predicate for list with cardinality n.

sc_table_n :: Integral n => n -> [[Z12]] Source #

Set classes of cardinality n.

sc_table_n 2 == [[0,1],[0,2],[0,3],[0,4],[0,5],[0,6]]

icv_minmax :: (Integral n, Integral b) => n -> ([b], [b]) Source #

Minima and maxima of ICV of SCs of cardinality n.

icv_minmax 5 == ([0,0,0,1,0,0],[4,4,4,4,4,2])

data R Source #

Constructors

MIN 
MAX 

Instances

Eq R Source # 

Methods

(==) :: R -> R -> Bool #

(/=) :: R -> R -> Bool #

Show R Source # 

Methods

showsPrec :: Int -> R -> ShowS #

show :: R -> String #

showList :: [R] -> ShowS #

type D n = (R, n) Source #

r_pp :: R -> String Source #

Pretty printer for R.

map r_pp [MIN,MAX] == ["+","-"]

satv_f :: Integral n => ((n, n, n) -> D n) -> [Z12] -> [D n] Source #

SATV element measure with given funtion.

satv_e_pp :: Show i => [D i] -> String Source #

Pretty printer for SATV element.

satv_e_pp (satv_a [0,1,2,6,7,8]) == "<-1,+2,+0,+0,-1,-0>"

type SATV i = ([D i], [D i]) Source #

satv_pp :: Show i => SATV i -> String Source #

Pretty printer for SATV.

satv_a :: Integral i => [Z12] -> [D i] Source #

SATVa measure.

satv_e_pp (satv_a [0,1,2,6,7,8]) == "<-1,+2,+0,+0,-1,-0>"
satv_e_pp (satv_a [0,1,2,3,4]) == "<-0,-1,-2,+0,+0,+0>"

satv_b :: Integral i => [Z12] -> [D i] Source #

SATVb measure.

satv_e_pp (satv_b [0,1,2,6,7,8]) == "<+4,-4,-5,-4,+4,+3>"
satv_e_pp (satv_b [0,1,2,3,4]) == "<+4,+3,+2,-3,-4,-2>"

satv :: Integral i => [Z12] -> SATV i Source #

SATV measure.

satv_pp (satv [0,3,6,9]) == "(<+0,+0,-0,+0,+0,-0>,<-3,-3,+4,-3,-3,+2>)"
satv_pp (satv [0,1,3,4,8]) == "(<-2,+1,-2,-1,-2,+0>,<+2,-3,+2,+2,+2,-2>)"
satv_pp (satv [0,1,2,6,7,8]) == "(<-1,+2,+0,+0,-1,-0>,<+4,-4,-5,-4,+4,+3>)"
satv_pp (satv [0,4]) == "(<+0,+0,+0,-0,+0,+0>,<-1,-1,-1,+1,-1,-1>)"
satv_pp (satv [0,1,3,4,6,9]) == "(<+2,+2,-0,+0,+2,-1>,<-3,-4,+5,-4,-3,+2>)"
satv_pp (satv [0,1,3,6,7,9]) == "(<+2,+2,-1,+0,+2,-0>,<-3,-4,+4,-4,-3,+3>)"
satv_pp (satv [0,1,2,3,6]) == "(<-1,-2,-2,+0,+1,-1>,<+3,+2,+2,-3,-3,+1>)"
satv_pp (satv [0,1,2,3,4,6]) == "(<-1,-2,-2,+0,+1,+1>,<+4,+4,+3,-4,-4,-2>)"
satv_pp (satv [0,1,3,6,8]) == "(<+1,-2,-2,+0,-1,-1>,<-3,+2,+2,-3,+3,+1>)"
satv_pp (satv [0,2,3,5,7,9]) == "(<+1,-2,-2,+0,-1,+1>,<-4,+4,+3,-4,+4,-2>)"

satv_minmax :: SATV i -> ([i], [i]) Source #

SATV reorganised by R.

satv_minmax (satv [0,1,2,6,7,8]) == ([4,2,0,0,4,3],[1,4,5,4,1,0])

abs_dif :: Num a => a -> a -> a Source #

Absolute difference.

satv_n_sum :: Num c => SATV c -> [c] Source #

Sum of numerical components of a and b parts of SATV.

satv_n_sum (satv [0,1,2,6,7,8]) == [5,6,5,4,5,3]
satv_n_sum (satv [0,3,6,9]) = [3,3,4,3,3,2]

satsim :: Integral a => [Z12] -> [Z12] -> Ratio a Source #

SATSIM metric.

satsim [0,1,2,6,7,8] [0,3,6,9] == 25/46
satsim [0,4] [0,1,3,4,6,9] == 25/34
satsim [0,4] [0,1,3,6,7,9] == 25/34
satsim [0,1,2,3,6] [0,1,2,3,4,6] == 1/49
satsim [0,1,3,6,8] [0,2,3,5,7,9] == 1/49
satsim [0,1,2,3,4] [0,1,4,5,7] == 8/21
satsim [0,1,2,3,4] [0,2,4,6,8] == 4/7
satsim [0,1,4,5,7] [0,2,4,6,8] == 4/7

satsim_table :: Integral i => [(([Z12], [Z12]), Ratio i)] Source #

Table of satsim measures for all SC pairs.

length satsim_table == 24310

satsim_table_histogram :: Integral i => [(Ratio i, i)] Source #

Histogram of values at satsim_table.

satsim_table_histogram == T.histogram (map snd satsim_table)