-- | Auditor functions common to all sample libraries.
module Sound.SC3.Auditor where

import Data.List {- base -}
import System.FilePath {- filepath -}

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

import qualified Sound.SC3.Auditor.Smplr as A

-- | Amplitude (linear gain)
type Amplitude = Double

-- | Buffer index.
type Index = Int

-- | Number of channels
type NC = Int

-- | 'Index' and 'Amplitude'
data Note = Note {note_index :: Index
                 ,note_amplitude :: Amplitude}
            deriving (Eq,Ord,Show)

-- | Chord
type Chord = [Note]

-- | Function to generate the set of 'OSC' commands required to load
-- the set of 'Index'ed files.
type Sample_Loader = [Index] -> [Message]

-- | Shorthand
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

-- | Start time of last element (this is not the same as 'tseq_dur').
pp_duration :: T.Tseq Time Chord -> Time
pp_duration = fst . last

-- | The set (unique, sorted) of indices referenced.
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)

-- | Generate 'NRT' given 'NC', 'Sample_Loader' and 'PP'.
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)

-- | Variant of 'pp_osc' that writes @NRT@ score to named file using
-- 'writeNRT'.
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)

-- | 'audition' of 'pp_nrt' (two channels, no loader).
pp_audition :: T.Tseq Time Chord -> IO ()
pp_audition = audition . pp_nrt 2 Nothing

-- * Loader

-- | Given 0-indexed list of channels to read, and an ordered sequence
-- of filenames make 'Sample_Loader'.
au_loader :: [Int] -> [String] -> Sample_Loader
au_loader ch nm =
    let f i = b_allocReadChannel i (nm !! i) 0 0 ch
    in map f

-- | Variant where all files are in the same directory, so given as
-- directory and file list.
au_loader_dir :: [Int] -> FilePath -> [FilePath] -> Sample_Loader
au_loader_dir ch dir nm = let nm' = map (dir </>) nm in au_loader ch nm'