Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Tuning theory
Synopsis
- fmidi_to_cps_k0 :: Floating a => (a, a) -> a -> a
- fmidi_to_cps_f0 :: Floating a => a -> a -> a
- fmidi_to_cps :: Floating a => a -> a
- midi_to_cps_k0 :: (Integral i, Floating f) => (f, f) -> i -> f
- midi_to_cps :: (Integral i, Floating f) => i -> f
- cents_to_fratio :: Floating a => a -> a
- fratio_to_cents :: (Real r, Floating n) => r -> n
- cps_shift_cents :: Floating a => a -> a -> a
- cps_difference_cents :: (Real r, Fractional r, Floating n) => r -> r -> n
- oct_diff_to_ratio :: Integral a => Ratio a -> Int -> Ratio a
- ratio_to_pc :: Int -> Rational -> Int
- fold_ratio_to_octave_nonrec :: (Ord n, Fractional n) => n -> n
- fold_ratio_to_octave_err :: (Ord n, Fractional n) => n -> n
- fold_ratio_to_octave :: (Ord n, Fractional n) => n -> Maybe n
- ratio_interval_class_by :: (Ord t, Integral i) => (Ratio i -> t) -> Ratio i -> Ratio i
- ratio_interval_class :: Integral i => Ratio i -> Ratio i
- type Approximate_Ratio = Double
- approximate_ratio :: Rational -> Approximate_Ratio
- type Cents = Double
- type Cents_I = Int
- approximate_ratio_to_cents :: Approximate_Ratio -> Cents
- ratio_to_cents :: Integral i => Ratio i -> Cents
- reconstructed_ratio :: Double -> Cents -> Rational
- syntonic_comma :: Rational
- pythagorean_comma :: Rational
- mercators_comma :: Rational
- twelve_tone_equal_temperament_comma :: (Floating a, Eq a) => a
- cents_et12_diff :: Integral n => n -> n
- fcents_et12_diff :: Real n => n -> n
- cents_interval_class :: Integral a => a -> a
- fcents_interval_class :: Real a => a -> a
- cents_diff_pp :: (Num a, Ord a, Show a) => a -> String
- cents_diff_br :: (Num a, Ord a, Show a) => (String, String) -> a -> String
- cents_diff_text :: (Num a, Ord a, Show a) => a -> String
- cents_diff_md :: (Num a, Ord a, Show a) => a -> String
- cents_diff_html :: (Num a, Ord a, Show a) => a -> String
- type Savarts = Double
- fratio_to_savarts :: Floating a => a -> a
- savarts_to_fratio :: Floating a => a -> a
- savarts_to_cents :: Floating a => a -> a
- cents_to_savarts :: Floating a => a -> a
Math/Floating
fmidi_to_cps_k0 :: Floating a => (a, a) -> a -> a Source #
Fractional midi note number to cycles per second, given (k0,f0) pair.
fmidi_to_cps_k0 (60,256) 69 == 430.5389646099018
fmidi_to_cps_f0 :: Floating a => a -> a -> a Source #
fmidi_to_cps_k0
with k0 of 69.
fmidi_to_cps_f0 440 60 == 261.6255653005986
fmidi_to_cps :: Floating a => a -> a Source #
fmidi_to_cps_k0
(69,440)
map fmidi_to_cps [69,69.1] == [440.0,442.5488940698553]
midi_to_cps_k0 :: (Integral i, Floating f) => (f, f) -> i -> f Source #
Midi note number to cycles per second, given frequency of ISO A4.
midi_to_cps :: (Integral i, Floating f) => i -> f Source #
midi_to_cps_k0
(69,440).
map (round . midi_to_cps) [59,60,69] == [247,262,440]
cents_to_fratio :: Floating a => a -> a Source #
Convert from interval in cents to frequency ratio.
map cents_to_fratio [0,701.9550008653874,1200] == [1,3/2,2] map cents_to_fratio [-1800,1800] -- three octaves about zero
fratio_to_cents :: (Real r, Floating n) => r -> n Source #
Convert from a Floating
ratio to cents.
let r = [0,498,702,1200] map (round . fratio_to_cents) [1,4/3,3/2,2] == r
cps_shift_cents :: Floating a => a -> a -> a Source #
Frequency n cents from f.
import Music.Theory.Pitch {- hmt -} 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.
map (round . cps_difference_cents 440) [412,415,octpc_to_cps (5,2)] == [-114,-101,500]
let abs_dif i j = abs (i - j) cps_difference_cents 440 (fmidi_to_cps 69.1) `abs_dif` 10 < 1e9
Math/Ratio
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]
ratio_to_pc :: Int -> Rational -> Int Source #
ratio_to_cents
rounded to nearest multiple of 100, modulo 12.
map (ratio_to_pc 0) [1,4/3,3/2,2] == [0,5,7,0]
fold_ratio_to_octave_nonrec :: (Ord n, Fractional n) => n -> n Source #
fold_ratio_to_octave_err :: (Ord n, Fractional n) => n -> n Source #
fold_ratio_to_octave :: (Ord n, Fractional n) => n -> Maybe n Source #
In n is greater than zero, fold_ratio_to_octave_err
, else Nothing
.
map fold_ratio_to_octave [0,1] == [Nothing,Just 1]
ratio_interval_class_by :: (Ord t, Integral i) => (Ratio i -> t) -> 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 and select the minima at the cmp_f.
map (ratio_interval_class_by id) [3/2,5/4] == [4/3,5/4]
ratio_interval_class :: Integral i => Ratio i -> Ratio i Source #
ratio_interval_class_by
ratio_nd_sum
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]
Types
type Approximate_Ratio = Double Source #
An approximation of a ratio.
approximate_ratio :: Rational -> Approximate_Ratio Source #
Type specialised fromRational
.
A real valued division of a semi-tone into one hundred parts, and
hence of the octave into 1200
parts.
approximate_ratio_to_cents :: Approximate_Ratio -> Cents Source #
Type specialised fratio_to_cents
.
ratio_to_cents :: Integral i => Ratio i -> Cents Source #
approximate_ratio_to_cents
.
approximate_ratio
.
import Data.Ratio {- base -} map (\n -> (n,round (ratio_to_cents (fold_ratio_to_octave_err (n % 1))))) [1..21]
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
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
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] 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]] map cents_interval_class [1200,1250 .. 2400] == r
fcents_interval_class :: Real a => a -> a Source #
Fractional form of cents_interval_class
.
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
).
Savart
type Savarts = Double Source #
Felix Savart (1791-1841), the ratio of 10:1 is assigned a value of 1000 savarts.
fratio_to_savarts :: Floating a => a -> a Source #
Ratio to savarts.
fratio_to_savarts 10 == 1000 fratio_to_savarts 2 == 301.02999566398114
savarts_to_fratio :: Floating a => a -> a Source #
Savarts to ratio.
savarts_to_fratio 1000 == 10 savarts_to_fratio 301.02999566398118 == 2
savarts_to_cents :: Floating a => a -> a Source #
Savarts to cents.
savarts_to_cents 1 == 3.9863137138648352
cents_to_savarts :: Floating a => a -> a Source #
Cents to savarts.
cents_to_savarts 3.9863137138648352 == 1 cents_to_savarts 1200 == ratio_to_savarts 2