module CsoundExpr.Base.Pretty(
        Cs.CsoundFile, Cs.Flags,
        Player, FileName,
        csd, play, playDac)
where


import qualified CsoundExpr.Translator.Cs.CsoundFile as Cs
import CsoundExpr.Translator.Csd
import CsoundExpr.Base.Header
import CsoundExpr.Translator.Types(Dur, SignalOut)

import System
import System.Directory
import qualified System.FilePath as FP 

import Temporal.Media(EventList)

---------------------------------------------------
---------------------------------------------------
-- translator

-- |  Generate csound code
-- 
--   Csound code consists of flags, header section, instruments, 
-- ftables and score. Flags are represeted by @String@. See 
-- "CsoundExpr.Base.Header" for more details on header 
-- section. Instruments, ftables and score are generated from 
-- 'EventList' 'Dur' 'SignalOut'. From list of 'SignalOut' notes list 
-- of instruments is derived. Expression-tree structures of 
-- instruments are different from one another. An instrument 
-- can't be transformed into another one only with substitution 
-- of values in lists of expression-tree. 
--
-- Example (d minor) :
--
-- >import Temporal.Music.Notation.Score
-- >
-- >import CsoundExpr
-- >import CsoundExpr.Opcodes
-- >import CsoundExpr.Base.Pitch
-- > 
-- >flags  = "-o dm.wav"
-- >
-- >setup = instr0 [
-- >        gSr     <=> 44100,
-- >        gKr     <=> 4410,
-- >        gKsmps  <=> 10,
-- >        gNchnls <=> 1]
-- >
-- >header = [setup]
-- >
-- >sinWave = gen10 4096 [1]
-- >
-- >instr :: Irate -> SignalOut
-- >instr x = out $ oscilA [] (num 1000) (cpspch x) sinWave
-- >
-- >sco = fmap instr $ line $ map (note 1) [d, f, a, high d]
-- >
-- >main = print $ csd flags header $ renderScore sco
csd :: Cs.Flags                 -- ^ flags 
    -> Header                   -- ^ header section
    -> EventList Dur SignalOut  -- ^ score section
    -> Cs.CsoundFile            -- ^ csd file
csd = toCsd



type Player   = String
type FileName = String

-- | 'play' writes 'CsoundFile' to file in temporal direcory, 
-- executes csound on it, saves to .wav file, and invokes player
--
-- >play "totem" "./temp" "song" $ csd flags header $ toList scores
play :: Player -> FP.FilePath -> FileName -> Cs.CsoundFile -> IO ExitCode
play playerCode tmpdir tmpfile csoundCode = do
    writeFile fileCsd (show csoundCode)
    system $ csound fileCsd
    system $ player fileWav
	where fileCsd = (tmpdir FP.</> tmpfile ++ ".csd") 
	      fileWav = (tmpdir FP.</> tmpfile ++ ".wav")  	
	      csound  = (("csound -o " ++ fileWav ++ " ") ++ )
	      player  = ((playerCode ++ " ") ++ )

-- | 'playDac' writes 'CsoundFile' to  in temporal direcory, 
-- executes csound on it, and plays online
--
-- >playDac "./temp" "song" $ csd flags header $ toList scores
playDac :: FP.FilePath -> FileName -> Cs.CsoundFile -> IO ExitCode
playDac tmpdir tmpfile csoundCode = do
    writeFile fileCsd (show csoundCode)
    system $ csound fileCsd
	where fileCsd = (tmpdir FP.</> tmpfile ++ ".csd") 
	      csound  = ("csound -odac " ++ )