module Sound.SC3.Auditor where
import Data.List
import System.FilePath
import qualified Music.Theory.Time.Seq as T
import Sound.OSC
import Sound.SC3
import qualified Sound.SC3.Auditor.Smplr as A
type Amplitude = Double
type Index = Int
type NC = Int
data Note = Note {note_index :: Index
,note_amplitude :: Amplitude}
deriving (Eq,Ord,Show)
type Chord = [Note]
type Sample_Loader = [Index] -> [Message]
type PP = T.Tseq Time Chord
to_p :: (a -> Index,a -> Amplitude) -> (Time,[a]) -> (Time,Chord)
to_p (i,a) (t,x) =
let f e = Note (i e) (a e)
in (t,map f x)
chord_indices :: Chord -> [Index]
chord_indices = map note_index
pp_start_times :: T.Tseq Time Chord -> [Time]
pp_start_times = map fst
pp_chords :: T.Tseq Time Chord -> [Chord]
pp_chords = map snd
pp_duration :: T.Tseq Time Chord -> Time
pp_duration = fst . last
pp_indices :: T.Tseq Time Chord -> [Index]
pp_indices = nub . sort . concatMap (chord_indices . snd)
chd_osc :: Chord -> [Message]
chd_osc =
let f n = s_new "smplr" (1) AddToTail 1 [("bufnum",fromIntegral (note_index n))
,("amp",note_amplitude n)]
in map f
p_osc :: (Time,Chord) -> Bundle
p_osc (t,c) = bundle t (chd_osc c)
pp_nrt :: NC -> Maybe Sample_Loader -> T.Tseq Time Chord -> NRT
pp_nrt nc ld pp =
let b = bundle
ix = pp_indices pp
group_zero = g_new [(1, AddToTail, 0)]
sc_init = let h = b 0 [group_zero,A.smplr_nc_osc nc]
in h : maybe [] (\ld' -> map (b 0 . return) (ld' ix)) ld
sc_end = [b (pp_duration pp + 12) [g_freeAll [1]]]
in NRT (sc_init ++ map p_osc pp ++ sc_end)
pp_nrt_write :: FilePath -> NC -> Sample_Loader -> T.Tseq Time Chord -> IO ()
pp_nrt_write nm nc ld = writeNRT nm . pp_nrt nc (Just ld)
pp_audition :: T.Tseq Time Chord -> IO ()
pp_audition = audition . pp_nrt 2 Nothing
au_loader :: [Int] -> [String] -> Sample_Loader
au_loader ch nm =
let f i = b_allocReadChannel i (nm !! i) 0 0 ch
in map f
au_loader_dir :: [Int] -> FilePath -> [FilePath] -> Sample_Loader
au_loader_dir ch dir nm = let nm' = map (dir </>) nm in au_loader ch nm'