hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
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.

Instances

divisions :: Tuning -> Int Source

Divisions of octave.

divisions ditone == 12

ratios :: Tuning -> Maybe [Rational] Source

Maybe exact ratios of Tuning.

cents :: Tuning -> [Cents] Source

Possibly inexact Cents of tuning.

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]

approximate_ratios_cyclic :: Tuning -> [Approximate_Ratio] Source

Cyclic form, taking into consideration octave_ratio.

reconstructed_ratios :: Double -> Tuning -> Maybe [Rational] Source

Maybe exact ratios reconstructed from possibly inexact Cents of Tuning.

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

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.9976981706734

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

Harmonic series

fold_cps_to_octave_of :: (Ord a, Fractional a) => a -> a -> a Source

Raise or lower the frequency q by octaves until it is in the octave starting at p.

fold_cps_to_octave_of 55 392 == 98

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 :: Integral i => Ratio i -> Ratio i Source

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

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

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]

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 :: Integer -> [Rational] Source

Harmonic series to nth harmonic (folded).

harmonic_series_folded 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 17) == r

harmonic_series_folded_c :: Integer -> [Cents] Source

ratio_to_cents variant of harmonic_series_folded.

map round (harmonic_series_folded_c 21) == [0,105,204,298,386,471,551,702,841,969,1088]

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

import Music.Theory.Tuning.Gann
let f = d12_midi_tuning_f (la_monte_young,-74.7,-3)
octpc_to_midi (-1,11) == 11
map (round . midi_detune_to_cps . f) [62,63,69] == [293,298,440]

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

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