hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Tuning

Contents

Description

Tuning theory

Synopsis

Types

type Approximate_Ratio = Double Source #

An approximation of a ratio.

type Cents = Double Source #

A real valued division of a semi-tone into one hundred parts, and hence of the octave into 1200 parts.

data Tuning Source #

A tuning specified Either as a sequence of exact ratios, or as a sequence of possibly inexact Cents.

In both cases, the values are given in relation to the first degree of the scale, which for ratios is 1 and for cents 0.

Instances

tn_divisions :: Tuning -> Int Source #

Divisions of octave.

tn_divisions (equal_temperament 12) == 12

tn_ratios :: Tuning -> Maybe [Rational] Source #

Maybe exact ratios of Tuning.

tn_cents :: Tuning -> [Cents] Source #

Possibly inexact Cents of tuning.

tn_cents_i :: Integral i => Tuning -> [i] Source #

map round . cents.

tn_cents_octave :: Tuning -> [Cents] Source #

Variant of cents that includes octave at right.

cents_to_ratio :: Floating a => a -> a Source #

Convert from interval in cents to frequency ratio.

map cents_to_ratio [0,701.9550008653874,1200] == [1,3/2,2]

tn_approximate_ratios_cyclic :: Tuning -> [Approximate_Ratio] Source #

Cyclic form, taking into consideration octave_ratio.

recur_n :: Integral n => n -> (t -> t) -> t -> t Source #

Iterate the function f n times, the inital value is x.

recur_n 5 (* 2) 1 == 32
take (5 + 1) (iterate (* 2) 1) == [1,2,4,8,16,32]

oct_diff_to_ratio :: Integral a => Ratio a -> Int -> Ratio a Source #

Convert a (signed) number of octaves difference of given ratio to a ratio.

map (oct_diff_to_ratio 2) [-3 .. 3] == [1/8,1/4,1/2,1,2,4,8]
map (oct_diff_to_ratio (9/8)) [-3 .. 3] == [512/729,64/81,8/9,1/1,9/8,81/64,729/512]

tn_ratios_lookup :: Tuning -> Int -> Maybe Rational Source #

Lookup function that allows both negative & multiple octave indices.

let map_zip f l = zip l (map f l)
map_zip (tn_ratios_lookup werckmeister_vi) [-24 .. 24]

tn_approximate_ratios_lookup :: Tuning -> Int -> Approximate_Ratio Source #

Lookup function that allows both negative & multiple octave indices.

map_zip (tn_approximate_ratios_lookup werckmeister_v) [-24 .. 24]

tn_reconstructed_ratios :: Double -> Tuning -> Maybe [Rational] Source #

Maybe exact ratios reconstructed from possibly inexact Cents of Tuning.

:l Music.Theory.Tuning.Werckmeister
let r = [1,17/16,9/8,13/11,5/4,4/3,7/5,3/2,11/7,5/3,16/9,15/8]
tn_reconstructed_ratios 1e-2 werckmeister_iii == Just r

fratio_to_cents :: (Real r, Floating n) => r -> n Source #

Convert from a Floating ratio to cents.

let r = [0,498,702,1200]
in map (round . fratio_to_cents) [1,4/3,3/2,2] == r

ratio_to_cents :: Integral i => Ratio i -> Cents Source #

approximate_ratio_to_cents . approximate_ratio.

map (\n -> (n,round (ratio_to_cents (fold_ratio_to_octave_err (n % 1))))) [1..21]

reconstructed_ratio :: Double -> Cents -> Rational Source #

Construct an exact Rational that approximates Cents to within epsilon.

map (reconstructed_ratio 1e-5) [0,700,1200] == [1,442/295,2]
ratio_to_cents (442/295) == 699.9976981706735

cps_shift_cents :: Floating a => a -> a -> a Source #

Frequency n cents from f.

import Music.Theory.Pitch
map (cps_shift_cents 440) [-100,100] == map octpc_to_cps [(4,8),(4,10)]

cps_difference_cents :: (Real r, Fractional r, Floating n) => r -> r -> n Source #

Interval in cents from p to q, ie. ratio_to_cents of p / q.

cps_difference_cents 440 (octpc_to_cps (5,2)) == 500
let abs_dif i j = abs (i - j)
in cps_difference_cents 440 (fmidi_to_cps 69.1) `abs_dif` 10 < 1e9

Commas

syntonic_comma :: Rational Source #

The Syntonic comma.

syntonic_comma == 81/80

pythagorean_comma :: Rational Source #

The Pythagorean comma.

pythagorean_comma == 3^12 / 2^19

mercators_comma :: Rational Source #

Mercators comma.

mercators_comma == 3^53 / 2^84

nth_root :: (Floating a, Eq a) => a -> a -> a Source #

Calculate nth root of x.

12 `nth_root` 2 == twelve_tone_equal_temperament_comma

twelve_tone_equal_temperament_comma :: (Floating a, Eq a) => a Source #

12-tone equal temperament comma (ie. 12th root of 2).

twelve_tone_equal_temperament_comma == 1.0594630943592953

Equal temperaments

equal_temperament :: Integral n => n -> Tuning Source #

Make n division equal temperament.

equal_temperament_12 :: Tuning Source #

12-tone equal temperament.

cents equal_temperament_12 == [0,100..1100]

equal_temperament_19 :: Tuning Source #

19-tone equal temperament.

equal_temperament_31 :: Tuning Source #

31-tone equal temperament.

equal_temperament_53 :: Tuning Source #

53-tone equal temperament.

equal_temperament_72 :: Tuning Source #

72-tone equal temperament.

let r = [0,17,33,50,67,83,100]
in take 7 (map round (cents equal_temperament_72)) == r

equal_temperament_96 :: Tuning Source #

96-tone equal temperament.

Harmonic series

harmonic_series :: Integer -> Rational -> Tuning Source #

Harmonic series to nth partial, with indicated octave.

harmonic_series 17 2

harmonic_series_cps :: (Num t, Enum t) => t -> [t] Source #

Harmonic series on n.

harmonic_series_cps_n :: (Num a, Enum a) => Int -> a -> [a] Source #

n elements of harmonic_series_cps.

let r = [55,110,165,220,275,330,385,440,495,550,605,660,715,770,825,880,935]
in harmonic_series_cps_n 17 55 == r

subharmonic_series_cps :: (Fractional t, Enum t) => t -> [t] Source #

Sub-harmonic series on n.

subharmonic_series_cps_n :: (Fractional t, Enum t) => Int -> t -> [t] Source #

n elements of harmonic_series_cps.

let r = [1760,880,587,440,352,293,251,220,196,176,160,147,135,126,117,110,104]
in map round (subharmonic_series_cps_n 17 1760) == r

partial :: (Num a, Enum a) => a -> Int -> a Source #

nth partial of f1, ie. one indexed.

map (partial 55) [1,5,3] == [55,275,165]

fold_ratio_to_octave_err :: Integral i => Ratio i -> Ratio i Source #

Error if input is less than or equal to zero.

map fold_ratio_to_octave_err [2/3,3/4] == [4/3,3/2]

fold_ratio_to_octave :: Integral i => Ratio i -> Maybe (Ratio i) Source #

Fold ratio until within an octave, ie. 1 < n <= 2.

map fold_ratio_to_octave [0,1] == [Nothing,Just 1]

ratio_nd_sum :: Num a => Ratio a -> a Source #

Sun of numerator & denominator.

min_by :: Ord a => (t -> a) -> t -> t -> t Source #

ratio_interval_class :: Integral i => Ratio i -> Ratio i Source #

The interval between two pitches p and q given as ratio multipliers of a fundamental is q / p. The classes over such intervals consider the fold_ratio_to_octave of both p to q and q to p.

map ratio_interval_class [2/3,3/2,3/4,4/3] == [3/2,3/2,3/2,3/2]
map ratio_interval_class [7/6,12/7] == [7/6,7/6]

harmonic_series_cps_derived :: (Ord a, Fractional a, Enum a) => Int -> a -> [a] Source #

Derivative harmonic series, based on kth partial of f1.

import Music.Theory.Pitch
let {r = [52,103,155,206,258,309,361,412,464,515,567,618,670,721,773]
    ;d = harmonic_series_cps_derived 5 (octpc_to_cps (1,4))}
in map round (take 15 d) == r

harmonic_series_folded_r :: Integer -> [Rational] Source #

Harmonic series to nth harmonic (folded, duplicated removed).

harmonic_series_folded_r 17 == [1,17/16,9/8,5/4,11/8,3/2,13/8,7/4,15/8]
let r = [0,105,204,386,551,702,841,969,1088]
in map (round . ratio_to_cents) (harmonic_series_folded_r 17) == r

harmonic_series_folded_21 :: Tuning Source #

12-tone tuning of first 21 elements of the harmonic series.

cents_i harmonic_series_folded_21 == [0,105,204,298,386,471,551,702,841,969,1088]
divisions harmonic_series_folded_21 == 11

Cents

cents_et12_diff :: Integral n => n -> n Source #

Give cents difference from nearest 12ET tone.

let r = [50,-49,-2,0,2,49,50]
in map cents_et12_diff [650,651,698,700,702,749,750] == r

fcents_et12_diff :: Real n => n -> n Source #

Fractional form of cents_et12_diff.

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

The class of cents intervals has range (0,600).

map cents_interval_class [50,1150,1250] == [50,50,50]
let r = concat [[0,50 .. 550],[600],[550,500 .. 0]]
in map cents_interval_class [1200,1250 .. 2400] == r

fcents_interval_class :: Real a => a -> a Source #

Fractional form of cents_interval_class.

cents_diff_pp :: (Num a, Ord a, Show a) => a -> String Source #

Always include the sign, elide 0.

cents_diff_br :: (Num a, Ord a, Show a) => (String, String) -> a -> String Source #

Given brackets, print cents difference.

cents_diff_text :: (Num a, Ord a, Show a) => a -> String Source #

cents_diff_br with parentheses.

map cents_diff_text [-1,0,1] == ["(-1)","","(+1)"]

cents_diff_md :: (Num a, Ord a, Show a) => a -> String Source #

cents_diff_br with markdown superscript (^).

cents_diff_html :: (Num a, Ord a, Show a) => a -> String Source #

cents_diff_br with HTML superscript (sup).

Midi

type Midi_Tuning_F = Int -> Midi_Detune Source #

(n -> dt). Function from midi note number n to Midi_Detune dt. The incoming note number is the key pressed, which may be distant from the note sounded.

type Sparse_Midi_Tuning_F = Int -> Maybe Midi_Detune Source #

Variant for tunings that are incomplete.

type Sparse_Midi_Tuning_ST_F st = st -> Int -> (st, Maybe Midi_Detune) Source #

Variant for sparse tunings that require state.

type D12_Midi_Tuning = (Tuning, Cents, Int) Source #

(t,c,k) where t=tuning (must have 12 divisions of octave), c=cents deviation (ie. constant detune offset), k=midi offset (ie. value to be added to incoming midi note number).

d12_midi_tuning_f :: D12_Midi_Tuning -> Midi_Tuning_F Source #

Midi_Tuning_F for D12_Midi_Tuning.

let f = d12_midi_tuning_f (equal_temperament 12,0,0)
map f [0..127] == zip [0..127] (repeat 0)

type CPS_Midi_Tuning = (Tuning, Double, Int, Int) Source #

(t,f0,k,g) where t=tuning, f0=fundamental frequency, k=midi note number for f0, g=gamut

cps_midi_tuning_f :: CPS_Midi_Tuning -> Sparse_Midi_Tuning_F Source #

Midi_Tuning_F for CPS_Midi_Tuning. The function is sparse, it is only valid for g values from k.

let f = cps_midi_tuning_f (equal_temperament 72,T.midi_to_cps 59,59,72 * 4)
map f [59 .. 59 + 72]

Midi tuning tables.

type MNN_CPS_Table = [(Int, Double)] Source #

Midi-note-number -> CPS table, possibly sparse.

gen_cps_tuning_tbl :: Sparse_Midi_Tuning_F -> MNN_CPS_Table Source #

Generates MNN_CPS_Table given Midi_Tuning_F with keys for all valid MNN.

import Sound.SC3.Plot
plot_p2_ln [map (fmap round) (gen_cps_tuning_tbl f)]

Derived (secondary) tuning table (DTT) lookup.

dtt_lookup :: (Eq k, Num v, Ord v) => [(k, v)] -> [v] -> k -> (Maybe v, Maybe v) Source #

Given an MNN_CPS_Table tbl, a list of CPS c, and a MNN m find the CPS in c that is nearest to the CPS in t for m.

dtt_lookup_err :: (Eq k, Num v, Ord v) => [(k, v)] -> [v] -> k -> (k, v, v) Source #

Require table be non-sparse.

gen_dtt_lookup_tbl :: MNN_CPS_Table -> MNN_CPS_Table -> MNN_CPS_Table Source #

Given two tuning tables generate the dtt table.

Euler-Fokker genus http://www.huygens-fokker.org/microtonality/efg.html

type EFG i = [(i, Int)] Source #

Normal form, value with occurences count (ie. exponent in notation above).

efg_degree :: EFG i -> Int Source #

Degree of EFG, ie. sum of exponents.

efg_degree [(3,3),(7,2)] == 3 + 2

efg_tones :: EFG i -> Int Source #

Number of tones of EFG, ie. product of increment of exponents.

efg_tones [(3,3),(7,2)] == (3 + 1) * (2 + 1)

efg_collate :: Ord i => [i] -> EFG i Source #

Collate a genus given as a multiset into standard form, ie. histogram.

efg_collate [3,3,3,7,7] == [(3,3),(7,2)]

efg_factors :: EFG i -> [([Int], [i])] Source #

Factors of EFG given with co-ordinate of grid location.

efg_factors [(3,3)]
let r = [([0,0],[]),([0,1],[7]),([0,2],[7,7])
        ,([1,0],[3]),([1,1],[3,7]),([1,2],[3,7,7])
        ,([2,0],[3,3]),([2,1],[3,3,7]),([2,2],[3,3,7,7])
        ,([3,0],[3,3,3]),([3,1],[3,3,3,7]),([3,2],[3,3,3,7,7])]
in efg_factors [(3,3),(7,2)] == r

efg_ratios :: Real r => Rational -> EFG r -> [([Int], Rational)] Source #

Ratios of EFG, taking n as the 1:1 ratio, with indices, folded into one octave.

let r = sort $ map snd $ efg_ratios 7 [(3,3),(7,2)]
r == [1/1,9/8,8/7,9/7,21/16,189/128,3/2,27/16,12/7,7/4,27/14,63/32]
map (round . ratio_to_cents) r == [0,204,231,435,471,675,702,906,933,969,1137,1173]

0: 1/1 C 0.000 cents 1: 9/8 D 203.910 cents 2: 8/7 D+ 231.174 cents 3: 9/7 E+ 435.084 cents 4: 21/16 F- 470.781 cents 5: 189/128 G- 674.691 cents 6: 3/2 G 701.955 cents 7: 27/16 A 905.865 cents 8: 12/7 A+ 933.129 cents 9: 7/4 Bb- 968.826 cents 10: 27/14 B+ 1137.039 cents 11: 63/32 C- 1172.736 cents 12: 2/1 C 1200.000 cents

let r' = sort $ map snd $ efg_ratios 5 [(5,2),(7,3)]
r' == [1/1,343/320,35/32,49/40,5/4,343/256,7/5,49/32,8/5,1715/1024,7/4,245/128]
map (round . ratio_to_cents) r' == [0,120,155,351,386,506,583,738,814,893,969,1124]
let r'' = sort $ map snd $ efg_ratios 3 [(3,1),(5,1),(7,1)]
r'' == [1/1,35/32,7/6,5/4,4/3,35/24,5/3,7/4]
map (round . ratio_to_cents) r'' == [0,155,267,386,498,653,884,969]
let c0 = [0,204,231,435,471,675,702,906,933,969,1137,1173,1200]
let c1 = [0,120,155,351,386,506,583,738,814,893,969,1124,1200]
let c2 = [0,155,267,386,498,653,884,969,1200]
let f (c',y) = map (\x -> (x,y,x,y + 10)) c'
map f (zip [c0,c1,c2] [0,20,40])

efg_diagram_set :: (Enum n, Real n) => (Cents -> n, n, n, n) -> [EFG n] -> [(n, n, n, n)] Source #

Generate a line drawing, as a set of (x0,y0,x1,y1) 4-tuples. h=row height, m=distance of vertical mark from row edge, k=distance between rows

let e = [[3,3,3],[3,3,5],[3,5,5],[3,5,7],[3,7,7],[5,5,5],[5,5,7],[3,3,7],[5,7,7],[7,7,7]]
let e = [[3,3,3],[5,5,5],[7,7,7],[3,3,5],[3,5,5],[5,5,7],[5,7,7],[3,7,7],[3,3,7],[3,5,7]]
let e' = map efg_collate e
efg_diagram_set (round,25,4,75) e'