-- | /Bosendorfer/ piano sample library based auditioner. module Sound.SC3.Auditor.PF where import qualified Music.Theory.Pitch as T {- hmt -} import Sound.OSC {- hosc -} import Sound.SC3 {- hsc3 -} import Sound.SC3.Auditor import System.FilePath {- filepath -} -- * Bosendorfer -- | 'Derive_Index' function for /Bosendorfer/ sample set. The offset -- from buffer number to midi note number, adjusted for by this -- function, is @24@. bosendorfer_octpc_to_index :: T.OctPC -> Index bosendorfer_octpc_to_index (o,pc) = fromIntegral (o * 12 + pc + 12 - 24) -- | Convert set of 'T.OctPC' based 'P' to 'PP' with appropriate -- 'Derive_Index' function. for_pf :: [(Start_Time,[(T.OctPC,Amplitude)])] -> PP for_pf = map (to_p (bosendorfer_octpc_to_index.fst,snd)) note_names :: [String] note_names = ["C", "C#", "D", "D#", "E", "F" ,"F#", "G", "G#", "A", "A#", "B"] file_names :: [String] file_names = [(n ++ show o) <.> "aif" | o <- [1::Int .. 7], n <- note_names] bosendorfer_osc :: FilePath -> (String, Int) -> Message bosendorfer_osc d (fn,i) = b_allocRead i (d fn) 0 0 -- | Generate set of 'OSC' messages to load /Bosendorfer/ sample -- library. bosendorfer_set_osc :: FilePath -> [Message] bosendorfer_set_osc d = map (bosendorfer_osc d) (zip file_names [0..]) -- | Variant of 'bosendorfer_set_osc' to load required subset of library. bosendorfer_subset_osc :: FilePath -> Sample_Loader bosendorfer_subset_osc d ix = let nm = filter ((`elem` ix) . snd) (zip file_names [0..]) in map (bosendorfer_osc d) nm -- | Send 'OSC' set given by 'bosendorfer_set_osc' to @scsynth@ at -- 'Transport'. au_load_bosendorfer_set :: Transport m => FilePath -> m () au_load_bosendorfer_set d = mapM_ async (bosendorfer_set_osc d) {- let d = "/home/rohan/disk/proudhon/data/bosendorfer/008/" bosendorfer_set_osc d withSC3 (au_load_bosendorfer_set d) withSC3 (au_load_instr 2) withSC3 (\fd -> send fd (s_new "s" (-1) AddToTail 1 [("b", 60-24)])) -}