-- | /Bosendorfer/ piano sample library based auditioner.
module Sound.SC3.Auditor.PF where

import System.FilePath {- filepath -}

import qualified Music.Theory.Pitch as T {- hmt -}
import qualified Music.Theory.Time.Seq as T {- hmt -}
import Sound.OSC {- hosc -}
import Sound.SC3 {- hsc3 -}

import qualified Sound.SC3.Auditor as A
import qualified Sound.SC3.Auditor.Smplr as A

-- * Bosendorfer

pf_dir :: FilePath
pf_dir = "/home/rohan/data/audio/instr/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 -> A.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 :: T.Tseq Time [(T.OctPC,A.Amplitude)] -> T.Tseq Time A.Chord
for_pf = map (A.to_p (bosendorfer_octpc_to_index . fst,snd))

--pf_from_midi_wseq =

note_names :: [String]
note_names = ["C", "C#", "D", "D#", "E", "F"
             ,"F#", "G", "G#", "A", "A#", "B"]

-- > length file_names == 84
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

-- | Generate set of 'OSC' messages to load /Bosendorfer/ sample
-- library.
bosendorfer_set_osc :: [Int] -> FilePath -> Int -> [Message]
bosendorfer_set_osc ch d b0 = map (bosendorfer_osc ch d) (zip file_names [b0..])

-- | Variant of 'bosendorfer_set_osc' to load required subset of library.
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

-- | Send 'OSC' set given by 'bosendorfer_set_osc' to @scsynth@ at
-- 'Transport'.
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)

-- > withSC3 (mapM_ sendBundle (pf_init "008" [0,1] 0))
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)])]

{-
let d = "/home/rohan/data/audio/instr/bosendorfer/008/"
bosendorfer_set_osc [0,1] d 0
withSC3 (au_load_bosendorfer_set [0,1] d 0)
withSC3 (async (A.instr_osc 2))
withSC3 (send (s_new "s" (-1) AddToTail 1 [("b", 60-24)]))
-}