module Music.Theory.Tuning.Table where
import qualified Music.Theory.Diagram.Grid as G
import Music.Theory.List
import Music.Theory.Pitch
import Music.Theory.Pitch.Spelling
import Music.Theory.Tuning
import qualified Text.HTML.Light as H
import Text.Printf
octpc_to_pitch_cps :: (Floating n) => OctPC -> (Pitch,n)
octpc_to_pitch_cps x = (octpc_to_pitch pc_spell_ks x,octpc_to_cps x)
tbl_12et :: [(Pitch,Double)]
tbl_12et =
let z = [(o,pc) | o <- [0..10], pc <- [0..11]]
in map octpc_to_pitch_cps z
tbl_24et :: [(Pitch, Double)]
tbl_24et =
let f x = let p = fmidi_to_pitch pc_spell_ks x
p' = pitch_rewrite_threequarter_alteration p
in (p',fmidi_to_cps x)
in map f [12,12.5 .. 143.5]
bounds_et_table :: Ord s => [(t,s)] -> s -> Maybe ((t,s),(t,s))
bounds_et_table tbl =
let f (_,p) = compare p
in find_bounds f (adj2 1 tbl)
bounds_12et_tone :: Double -> Maybe ((Pitch,Double),(Pitch,Double))
bounds_12et_tone = bounds_et_table tbl_12et
type HS_R = (Double,Pitch,Double,Double,Cents)
nearest_et_table_tone :: [(Pitch,Double)] -> Double -> HS_R
nearest_et_table_tone tbl f =
case bounds_et_table tbl f of
Nothing -> undefined
Just ((lp,lf),(rp,rf)) ->
let ld = f lf
rd = f rf
in if abs ld < abs rd
then (f,lp,lf,ld,to_cents (f/lf))
else (f,rp,rf,rd,to_cents (f/rf))
nearest_12et_tone :: Double -> HS_R
nearest_12et_tone = nearest_et_table_tone tbl_12et
nearest_24et_tone :: Double -> HS_R
nearest_24et_tone = nearest_et_table_tone tbl_24et
ndp :: Int -> Double -> String
ndp = printf "%.*f"
hs_r_cell :: Int -> (Int -> String) -> [HS_R] -> (Int,Int) -> G.Table_Cell
hs_r_cell n nm_f t (i,j) =
let dp = ndp n
(f,p,pf,fd,c) = t !! i
e = case j of
0 -> nm_f i
1 -> dp f
2 -> pitch_pp p
3 -> dp pf
4 -> dp fd
5 -> dp c
_ -> undefined
in ([],[H.cdata e])