module Sound.SC3.Auditor.PF where
import System.FilePath
import qualified Music.Theory.Pitch as T
import qualified Music.Theory.Time.Seq as T
import Sound.OSC
import Sound.SC3
import qualified Sound.SC3.Auditor as A
import qualified Sound.SC3.Auditor.Smplr as A
pf_dir :: FilePath
pf_dir = "/home/rohan/data/audio/instr/bosendorfer/"
bosendorfer_octpc_to_index :: T.OctPC -> A.Index
bosendorfer_octpc_to_index (o,pc) = fromIntegral (o * 12 + pc + 12 24)
for_pf :: T.Tseq Time [(T.OctPC,A.Amplitude)] -> T.Tseq Time A.Chord
for_pf = map (A.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 :: [Int] -> FilePath -> (String,Int) -> Message
bosendorfer_osc ch d (fn,i) = b_allocReadChannel i (d </> fn) 0 0 ch
bosendorfer_set_osc :: [Int] -> FilePath -> Int -> [Message]
bosendorfer_set_osc ch d b0 = map (bosendorfer_osc ch d) (zip file_names [b0..])
bosendorfer_subset_osc :: [Int] -> FilePath -> Int -> A.Sample_Loader
bosendorfer_subset_osc ch d b0 ix =
let nm = filter ((`elem` ix) . snd) (zip file_names [b0..])
in map (bosendorfer_osc ch d) nm
au_load_bosendorfer_set :: Transport m => [Int] -> FilePath -> Int -> m ()
au_load_bosendorfer_set ch d b0 = mapM_ async (bosendorfer_set_osc ch d b0)
pf_init :: String -> [Int] -> Int -> [Bundle]
pf_init ly ch b0 =
let f = bundle 0 . return
sy = A.smplr_recv_all_msg
ld = bosendorfer_set_osc ch (pf_dir </> ly) b0
in map f sy ++ map f ld ++ [f (g_new [(1,AddToTail,0)])]