hmt-0.20: Haskell Music Theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.Tuning.Midi

Description

Midi + Tuning

Synopsis

Documentation

type Midi_Tuning_f = Midi -> 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 = Midi -> Maybe Midi_Detune Source #

Variant for tunings that are incomplete.

type Sparse_Midi_Tuning_St_f st = st -> Midi -> (st, Maybe Midi_Detune) Source #

Variant for sparse tunings that require state.

type D12_Midi_Tuning = (Tuning, Cents, Midi) 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, Midi, 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.

import qualified Music.Theory.Pitch as T
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_Fmnn_Table = [(Int, Double)] Source #

midi-note-number -> fractional-midi-note-number table, possibly sparse.

type Mnn_Cps_Table = [(Midi, 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
let f = cps_midi_tuning_f (equal_temperament 12,T.midi_to_cps 0,0,127)
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. In equal distance cases bias left.

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.