{-# Language ScopedTypeVariables, InstanceSigs, FlexibleInstances, UndecidableInstances, CPP #-}
-- | Rendering of Csound files and playing the music in real time.
--
-- How are we going to get the sound out of Haskell code?
-- Instruments are ready and we have written all the scores for them.
-- Now, it's time to use the rendering functions. We can render haskell expressions
-- to Csound code. A rendering function takes a value that represents a sound (it's a tuple of signals)
-- and produces a string with Csound code. It can take a value that represents
-- the flags for the csound compiler and global settings ('Csound.Options').
-- Then we can save this string to file and convert it to sound with csound compiler
--
-- > csound -o music.wav music.csd
--
-- Or we can play it in real time with -odac flag. It sends the sound directly to
-- soundcard. It's usefull when we are using midi or tweek the parameters in real time
-- with sliders or knobs.
--
-- > csound -odac music.csd
--
-- The main function of this module is 'Csound.IO.renderCsdBy'. Other function are nothing but
-- wrappers that produce the Csound code and make something useful with it (saving to file,
-- playing with specific player or in real time).
module Csound.IO (
    -- * Rendering
    RenderCsd(..),
    CsdArity(..),
    renderCsd,
    writeCsd, writeCsdBy,
    writeSnd, writeSndBy,

    -- * Playing the sound
    playCsd, playCsdBy,
    mplayer, mplayerBy, totem, totemBy,

    -- * Live performance
    dac, dacBy, vdac, vdacBy,

    -- * Render and run
    csd, csdBy,

    -- * Save user options
    saveUserOptions,

    -- * Render and run with cabbage
    runCabbage, runCabbageBy,

    -- * Aliases for type inference
    -- | Sometimes the type class @RenderCsd@ is too whide for us.
    -- It cn be hard to use in the interpreter without explicit signatures.
    -- There are functions to help the type inference.
    -- ** For processing inputs
    onCard1, onCard2, onCard4, onCard6, onCard8,

    -- * Config with command line arguments
    -- | With the functions we can add global config parameters to the rendered file.
    -- We can supply different parameters with @--omacro@ flag.
    --
    -- An example:
    --
    -- > dac $ osc (sig $ readMacrosDouble "FREQ" 440)
    --
    -- Here we define frequency as a global parameter. It's available by name @"FREQ"@.
    -- If we run the program with no flags it would play the default 440 Hz. But we can change that like this:
    --
    -- > csound tmp.csd --omacro:FREQ=330
    --
    -- We can update the macro-arguments with flag @--omacro:NAME=VALUE@.
    readMacrosString, readMacrosDouble, readMacrosInt
) where

--import Control.Concurrent
import Control.Monad

import Data.Text qualified as Text
import System.Process
import System.Directory
import System.FilePath
import qualified Control.Exception as E

import Data.Proxy
import Data.Default
import Csound.Typed
import Csound.Control.Gui

import Csound.Options(setSilent, setDac, setAdc, setDacBy, setAdcBy, setCabbage)
import Temporal.Class(Harmony(..))

render :: Sigs a => Options -> SE a -> IO String
render :: forall a. Sigs a => Options -> SE a -> IO FilePath
render = Options -> SE a -> IO FilePath
forall a. Sigs a => Options -> SE a -> IO FilePath
renderOutBy

render_ :: Options -> SE () -> IO String
render_ :: Options -> SE () -> IO FilePath
render_ = Options -> SE () -> IO FilePath
renderOutBy_

data CsdArity = CsdArity
  { CsdArity -> Int
csdArity'inputs  :: Int
  , CsdArity -> Int
csdArity'outputs :: Int
  } deriving (Int -> CsdArity -> ShowS
[CsdArity] -> ShowS
CsdArity -> FilePath
(Int -> CsdArity -> ShowS)
-> (CsdArity -> FilePath) -> ([CsdArity] -> ShowS) -> Show CsdArity
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CsdArity -> ShowS
showsPrec :: Int -> CsdArity -> ShowS
$cshow :: CsdArity -> FilePath
show :: CsdArity -> FilePath
$cshowList :: [CsdArity] -> ShowS
showList :: [CsdArity] -> ShowS
Show, CsdArity -> CsdArity -> Bool
(CsdArity -> CsdArity -> Bool)
-> (CsdArity -> CsdArity -> Bool) -> Eq CsdArity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CsdArity -> CsdArity -> Bool
== :: CsdArity -> CsdArity -> Bool
$c/= :: CsdArity -> CsdArity -> Bool
/= :: CsdArity -> CsdArity -> Bool
Eq)

class RenderCsd a where
    renderCsdBy :: Options -> a -> IO String
    csdArity :: Proxy a -> CsdArity

hasInputs :: RenderCsd a => Proxy a -> Bool
hasInputs :: forall a. RenderCsd a => Proxy a -> Bool
hasInputs = ( Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Int -> Bool) -> (Proxy a -> Int) -> Proxy a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CsdArity -> Int
csdArity'inputs (CsdArity -> Int) -> (Proxy a -> CsdArity) -> Proxy a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy a -> CsdArity
forall a. RenderCsd a => Proxy a -> CsdArity
csdArity

hasOutputs :: RenderCsd a => Proxy a -> Bool
hasOutputs :: forall a. RenderCsd a => Proxy a -> Bool
hasOutputs = ( Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Int -> Bool) -> (Proxy a -> Int) -> Proxy a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CsdArity -> Int
csdArity'outputs (CsdArity -> Int) -> (Proxy a -> CsdArity) -> Proxy a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy a -> CsdArity
forall a. RenderCsd a => Proxy a -> CsdArity
csdArity

instance {-# OVERLAPPING #-} RenderCsd (SE ()) where
    renderCsdBy :: Options -> SE () -> IO FilePath
renderCsdBy = Options -> SE () -> IO FilePath
render_
    csdArity :: Proxy (SE ()) -> CsdArity
csdArity Proxy (SE ())
_ = Int -> Int -> CsdArity
CsdArity Int
0 Int
0

#if __GLASGOW_HASKELL__ >= 710
instance {-# OVERLAPPABLE #-} forall a. Sigs a => RenderCsd a where
  renderCsdBy :: Options -> a -> IO FilePath
renderCsdBy Options
opt a
a = Options -> SE a -> IO FilePath
forall a. Sigs a => Options -> SE a -> IO FilePath
render Options
opt (a -> SE a
forall a. a -> SE a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a)
  csdArity :: Proxy a -> CsdArity
csdArity Proxy a
_ = Int -> Int -> CsdArity
CsdArity Int
0 (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))

instance {-# OVERLAPPABLE #-} forall a. Sigs a => RenderCsd (SE a) where
  renderCsdBy :: Options -> SE a -> IO FilePath
renderCsdBy Options
opt SE a
a = Options -> SE a -> IO FilePath
forall a. Sigs a => Options -> SE a -> IO FilePath
render Options
opt SE a
a
  csdArity :: Proxy (SE a) -> CsdArity
csdArity Proxy (SE a)
_ = Int -> Int -> CsdArity
CsdArity Int
0 (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))

instance {-# OVERLAPPABLE #-} forall a. Sigs a => RenderCsd (Source a) where
  renderCsdBy :: Options -> Source a -> IO FilePath
renderCsdBy Options
opt Source a
a = Options -> SE a -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
opt (Source a -> SE a
forall a. Source a -> SE a
fromSource Source a
a)
  csdArity :: Proxy (Source a) -> CsdArity
csdArity Proxy (Source a)
_ = Int -> Int -> CsdArity
CsdArity Int
0 (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))

instance {-# OVERLAPPABLE #-} forall a. Sigs a => RenderCsd (Source (SE a)) where
  renderCsdBy :: Options -> Source (SE a) -> IO FilePath
renderCsdBy Options
opt Source (SE a)
a = Options -> SE a -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
opt (Source (SE a) -> SE a
forall a. Source (SE a) -> SE a
fromSourceSE Source (SE a)
a)
  csdArity :: Proxy (Source (SE a)) -> CsdArity
csdArity Proxy (Source (SE a))
_ = Int -> Int -> CsdArity
CsdArity Int
0 (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))

instance {-# OVERLAPPABLE #-} forall a. Sigs a => RenderCsd (Sco (Mix a)) where
  renderCsdBy :: Options -> Sco (Mix a) -> IO FilePath
renderCsdBy Options
opt Sco (Mix a)
a = Options -> a -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
opt (Sco (Mix a) -> a
forall a. Sigs a => Sco (Mix a) -> a
mix Sco (Mix a)
a)
  csdArity :: Proxy (Sco (Mix a)) -> CsdArity
csdArity Proxy (Sco (Mix a))
_ = Int -> Int -> CsdArity
CsdArity Int
0 (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))

instance {-# OVERLAPPABLE #-} forall a. Sigs a => RenderCsd [Sco (Mix a)] where
  renderCsdBy :: Options -> [Sco (Mix a)] -> IO FilePath
renderCsdBy Options
opt [Sco (Mix a)]
a = Options -> a -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
opt (Sco (Mix a) -> a
forall a. Sigs a => Sco (Mix a) -> a
mix (Sco (Mix a) -> a) -> Sco (Mix a) -> a
forall a b. (a -> b) -> a -> b
$ [Sco (Mix a)] -> Sco (Mix a)
forall a. Harmony a => [a] -> a
har [Sco (Mix a)]
a)
  csdArity :: Proxy [Sco (Mix a)] -> CsdArity
csdArity Proxy [Sco (Mix a)]
_ = Int -> Int -> CsdArity
CsdArity Int
0 (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a -> Int) -> Proxy a -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))

#endif

instance {-# OVERLAPPABLE #-} forall a b. (Sigs a, Sigs b) => RenderCsd (a -> b) where
    renderCsdBy :: Options -> (a -> b) -> IO FilePath
renderCsdBy Options
opt a -> b
f = Options -> (a -> SE b) -> IO FilePath
forall a b.
(Sigs a, Sigs b) =>
Options -> (a -> SE b) -> IO FilePath
renderEffBy Options
opt (b -> SE b
forall a. a -> SE a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> SE b) -> (a -> b) -> a -> SE b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)
    csdArity :: Proxy (a -> b) -> CsdArity
csdArity Proxy (a -> b)
_ = Int -> Int -> CsdArity
CsdArity (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) (Proxy b -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b))

instance {-# OVERLAPPABLE #-} forall a b. (Sigs a, Sigs b) => RenderCsd (a -> SE b) where
    renderCsdBy :: Options -> (a -> SE b) -> IO FilePath
renderCsdBy Options
opt a -> SE b
f = Options -> (a -> SE b) -> IO FilePath
forall a b.
(Sigs a, Sigs b) =>
Options -> (a -> SE b) -> IO FilePath
renderEffBy Options
opt a -> SE b
f
    csdArity :: Proxy (a -> SE b) -> CsdArity
csdArity Proxy (a -> SE b)
_ = Int -> Int -> CsdArity
CsdArity (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) (Proxy b -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b))

instance {-# OVERLAPPABLE #-} forall a b. (Sigs a, Sigs b) => RenderCsd (a -> Source b) where
    renderCsdBy :: Options -> (a -> Source b) -> IO FilePath
renderCsdBy Options
opt a -> Source b
f = Options -> (a -> SE b) -> IO FilePath
forall a b.
(Sigs a, Sigs b) =>
Options -> (a -> SE b) -> IO FilePath
renderEffBy Options
opt (Source b -> SE b
forall a. Source a -> SE a
fromSource (Source b -> SE b) -> (a -> Source b) -> a -> SE b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Source b
f)
    csdArity :: Proxy (a -> Source b) -> CsdArity
csdArity Proxy (a -> Source b)
_ = Int -> Int -> CsdArity
CsdArity (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) (Proxy b -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b))
instance forall a b. (Sigs a, Sigs b) => RenderCsd (a -> Source (SE b)) where
    renderCsdBy :: Options -> (a -> Source (SE b)) -> IO FilePath
renderCsdBy Options
opt a -> Source (SE b)
f = Options -> (a -> SE b) -> IO FilePath
forall a b.
(Sigs a, Sigs b) =>
Options -> (a -> SE b) -> IO FilePath
renderEffBy Options
opt (Source (SE b) -> SE b
forall a. Source (SE a) -> SE a
fromSourceSE (Source (SE b) -> SE b) -> (a -> Source (SE b)) -> a -> SE b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Source (SE b)
f)
    csdArity :: Proxy (a -> Source (SE b)) -> CsdArity
csdArity Proxy (a -> Source (SE b))
_ = Int -> Int -> CsdArity
CsdArity (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) (Proxy b -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b))

instance {-# OVERLAPPING #-} forall a. (Sigs a) => RenderCsd (a -> Source (SE Sig2)) where
    renderCsdBy :: Options -> (a -> Source (SE Sig2)) -> IO FilePath
renderCsdBy Options
opt a -> Source (SE Sig2)
f = Options -> (a -> SE Sig2) -> IO FilePath
forall a b.
(Sigs a, Sigs b) =>
Options -> (a -> SE b) -> IO FilePath
renderEffBy Options
opt (Source (SE Sig2) -> SE Sig2
forall a. Source (SE a) -> SE a
fromSourceSE (Source (SE Sig2) -> SE Sig2)
-> (a -> Source (SE Sig2)) -> a -> SE Sig2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Source (SE Sig2)
f)
    csdArity :: Proxy (a -> Source (SE Sig2)) -> CsdArity
csdArity Proxy (a -> Source (SE Sig2))
_ = Int -> Int -> CsdArity
CsdArity (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) (Proxy Sig2 -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy Sig2
forall {k} (t :: k). Proxy t
Proxy :: Proxy Sig2))

instance {-# OVERLAPPING #-} RenderCsd (Source ()) where
    renderCsdBy :: Options -> Source () -> IO FilePath
renderCsdBy Options
opt Source ()
src = Options -> SE () -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
opt (SE () -> IO FilePath) -> SE () -> IO FilePath
forall a b. (a -> b) -> a -> b
$ do
        (Gui
ui, ()
_) <- Source ()
src
        Gui -> SE ()
panel Gui
ui
    csdArity :: Proxy (Source ()) -> CsdArity
csdArity Proxy (Source ())
_ = Int -> Int -> CsdArity
CsdArity Int
0 Int
0

instance {-# OVERLAPPING #-} RenderCsd (Source (SE ())) where
    renderCsdBy :: Options -> Source (SE ()) -> IO FilePath
renderCsdBy Options
opt Source (SE ())
src = Options -> Source () -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
opt (Source (SE ()) -> Source ()
forall a. Source (SE a) -> Source a
joinSource Source (SE ())
src)
    csdArity :: Proxy (Source (SE ())) -> CsdArity
csdArity Proxy (Source (SE ()))
_ = Int -> Int -> CsdArity
CsdArity Int
0 Int
0

-- | Renders Csound file.
renderCsd :: RenderCsd a => a -> IO String
renderCsd :: forall a. RenderCsd a => a -> IO FilePath
renderCsd = Options -> a -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
forall a. Default a => a
def

getTmpFile :: IO FilePath
getTmpFile :: IO FilePath
getTmpFile = (FilePath -> ShowS
</> FilePath
"tmp.csd") ShowS -> IO FilePath -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath
getTemporaryDirectory

-- | Render Csound file and save it to the give file.
writeCsd :: RenderCsd a => FilePath -> a -> IO ()
writeCsd :: forall a. RenderCsd a => FilePath -> a -> IO ()
writeCsd FilePath
file a
a = FilePath -> FilePath -> IO ()
writeFile FilePath
file (FilePath -> IO ()) -> IO FilePath -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< a -> IO FilePath
forall a. RenderCsd a => a -> IO FilePath
renderCsd a
a

-- | Render Csound file with options and save it to the give file.
writeCsdBy :: RenderCsd a => Options -> FilePath -> a -> IO ()
writeCsdBy :: forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeCsdBy Options
opt FilePath
file a
a = FilePath -> FilePath -> IO ()
writeFile FilePath
file (FilePath -> IO ()) -> IO FilePath -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Options -> a -> IO FilePath
forall a. RenderCsd a => Options -> a -> IO FilePath
renderCsdBy Options
opt a
a

-- | Render Csound file and save result sound to the wav-file.
writeSnd :: RenderCsd a => FilePath -> a -> IO ()
writeSnd :: forall a. RenderCsd a => FilePath -> a -> IO ()
writeSnd = Options -> FilePath -> a -> IO ()
forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeSndBy Options
forall a. Default a => a
def

-- | Render Csound file with options and save result sound to the wav-file.
writeSndBy :: RenderCsd a => Options -> FilePath -> a -> IO ()
writeSndBy :: forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeSndBy Options
opt FilePath
file a
a = do
    FilePath
fileCsd <- IO FilePath
getTmpFile
    Options -> FilePath -> a -> IO ()
forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeCsdBy Options
opt FilePath
fileCsd a
a
    IO () -> FilePath -> IO ()
runWithUserInterrupt (Options -> IO ()
postSetup Options
opt) (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords [FilePath
"csound -o", FilePath
file, FilePath
fileCsd, Options -> FilePath
logTrace Options
opt]

logTrace :: Options -> String
logTrace :: Options -> FilePath
logTrace Options
opt
  | Options -> Bool
csdNeedTrace Options
opt = FilePath
""
  | Bool
otherwise        = FilePath
"--logfile=null"

-- | Renders Csound file, saves it to the given file, renders with csound command and plays it with the given program.
--
-- > playCsd program file csd
--
-- Produces files @file.csd@ (with 'Csound.Render.Mix.renderCsd') and @file.wav@ (with @csound@) and then invokes:
--
-- > program "file.wav"
playCsd :: (RenderCsd a) => (String -> IO ()) -> String -> a -> IO ()
playCsd :: forall a.
RenderCsd a =>
(FilePath -> IO ()) -> FilePath -> a -> IO ()
playCsd = Options -> (FilePath -> IO ()) -> FilePath -> a -> IO ()
forall a.
RenderCsd a =>
Options -> (FilePath -> IO ()) -> FilePath -> a -> IO ()
playCsdBy Options
forall a. Default a => a
def

-- | Works just like 'Csound.Render.Mix.playCsd' but you can supply csound options.
playCsdBy :: (RenderCsd a) => Options -> (String -> IO ()) -> String -> a -> IO ()
playCsdBy :: forall a.
RenderCsd a =>
Options -> (FilePath -> IO ()) -> FilePath -> a -> IO ()
playCsdBy Options
opt FilePath -> IO ()
player FilePath
file a
a = do
    Options -> FilePath -> a -> IO ()
forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeCsdBy Options
opt FilePath
fileCsd a
a
    IO () -> FilePath -> IO ()
runWithUserInterrupt (Options -> IO ()
postSetup Options
opt) (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords [FilePath
"csound -o", FilePath
fileWav, FilePath
fileCsd, Options -> FilePath
logTrace Options
opt]
    FilePath -> IO ()
player FilePath
fileWav
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    where fileCsd :: FilePath
fileCsd = FilePath
file FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
".csd"
          fileWav :: FilePath
fileWav = FilePath
file FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
".wav"

simplePlayCsdBy :: (RenderCsd a) => Options -> String -> String -> a -> IO ()
simplePlayCsdBy :: forall a.
RenderCsd a =>
Options -> FilePath -> FilePath -> a -> IO ()
simplePlayCsdBy Options
opt FilePath
player = Options -> (FilePath -> IO ()) -> FilePath -> a -> IO ()
forall a.
RenderCsd a =>
Options -> (FilePath -> IO ()) -> FilePath -> a -> IO ()
playCsdBy Options
opt FilePath -> IO ()
phi
    where phi :: FilePath -> IO ()
phi FilePath
file = do
            IO () -> FilePath -> IO ()
runWithUserInterrupt (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords [FilePath
player, FilePath
file]

-- | Renders csound code to file @tmp.csd@ with flags set to @-odac@, @-iadc@ and @-Ma@
-- (sound output goes to soundcard in real time).
dac :: (RenderCsd a) => a -> IO ()
dac :: forall a. RenderCsd a => a -> IO ()
dac = Options -> a -> IO ()
forall a. RenderCsd a => Options -> a -> IO ()
dacBy Options
forall a. Default a => a
def

-- | 'Csound.Base.dac' with options.
dacBy :: forall a. (RenderCsd a) => Options -> a -> IO ()
dacBy :: forall a. RenderCsd a => Options -> a -> IO ()
dacBy Options
opt' a
a = do
    FilePath
fileCsd <- IO FilePath
getTmpFile
    Options -> FilePath -> a -> IO ()
forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeCsdBy Options
opt FilePath
fileCsd a
a
    IO () -> FilePath -> IO ()
runWithUserInterrupt (Options -> IO ()
postSetup Options
opt') (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords [FilePath
"csound", FilePath
fileCsd, Options -> FilePath
logTrace Options
opt']
    where
      opt :: Options
opt = [Options] -> Options
forall a. Monoid a => [a] -> a
mconcat [Options
opt', Options
withDac, Options
withAdc]

      withDac :: Options
withDac
        | Options -> Bool
hasJackConnections Options
opt'       = Text -> Options
setDacBy Text
"null"
        | Proxy a -> Bool
forall a. RenderCsd a => Proxy a -> Bool
hasOutputs (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a) = Options
setDac
        | Bool
otherwise                     = Options
forall a. Monoid a => a
mempty

      withAdc :: Options
withAdc
        | Options -> Bool
hasJackConnections Options
opt'      = Text -> Options
setAdcBy Text
"null"
        | Proxy a -> Bool
forall a. RenderCsd a => Proxy a -> Bool
hasInputs (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a) = Options
setAdc
        | Bool
otherwise                    = Options
forall a. Monoid a => a
mempty

-- | Output to dac with virtual midi keyboard.
vdac :: (RenderCsd a) => a -> IO ()
vdac :: forall a. RenderCsd a => a -> IO ()
vdac = Options -> a -> IO ()
forall a. RenderCsd a => Options -> a -> IO ()
dacBy (Options -> Options
setVirtual Options
forall a. Default a => a
def)

-- | Output to dac with virtual midi keyboard with specified options.
vdacBy :: (RenderCsd a) => Options -> a -> IO ()
vdacBy :: forall a. RenderCsd a => Options -> a -> IO ()
vdacBy Options
opt = Options -> a -> IO ()
forall a. RenderCsd a => Options -> a -> IO ()
dacBy (Options -> Options
setVirtual Options
opt)

setVirtual :: Options -> Options
setVirtual :: Options -> Options
setVirtual Options
a = Options
a { csdFlags = (csdFlags a) { rtmidi = Just VirtualMidi, midiRT = m { midiDevice = Just "0" } } }
    where m :: MidiRT
m = Flags -> MidiRT
midiRT (Flags -> MidiRT) -> Flags -> MidiRT
forall a b. (a -> b) -> a -> b
$ Options -> Flags
csdFlags Options
a

-- | Renders to file @tmp.csd@ in temporary directory and invokes the csound on it.
csd :: (RenderCsd a) => a -> IO ()
csd :: forall a. RenderCsd a => a -> IO ()
csd = Options -> a -> IO ()
forall a. RenderCsd a => Options -> a -> IO ()
csdBy Options
setSilent

-- | Renders to file @tmp.csd@ in temporary directory and invokes the csound on it.
csdBy :: (RenderCsd a) => Options -> a -> IO ()
csdBy :: forall a. RenderCsd a => Options -> a -> IO ()
csdBy Options
options a
a = do
    FilePath
fileCsd <- IO FilePath
getTmpFile
    Options -> FilePath -> a -> IO ()
forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeCsdBy (Options
setSilent Options -> Options -> Options
forall a. Monoid a => a -> a -> a
`mappend` Options
options) FilePath
fileCsd a
a
    IO () -> FilePath -> IO ()
runWithUserInterrupt (Options -> IO ()
postSetup Options
options) (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords [FilePath
"csound", FilePath
fileCsd, Options -> FilePath
logTrace Options
options]

postSetup :: Options -> IO ()
postSetup :: Options -> IO ()
postSetup Options
opt = Options -> IO ()
jackConnect Options
opt

jackConnect :: Options -> IO ()
jackConnect :: Options -> IO ()
jackConnect Options
opt
  | Just [(Text, Text)]
conns <- Options -> Maybe [(Text, Text)]
csdJackConnect Options
opt = case [(Text, Text)]
conns of
                                         [] -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
                                         [(Text, Text)]
_  -> IO ProcessHandle -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ProcessHandle -> IO ()) -> IO ProcessHandle -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ProcessHandle
runCommand (FilePath -> IO ProcessHandle) -> FilePath -> IO ProcessHandle
forall a b. (a -> b) -> a -> b
$ Text -> FilePath
Text.unpack (Text -> FilePath) -> Text -> FilePath
forall a b. (a -> b) -> a -> b
$ [(Text, Text)] -> Text
jackCmd [(Text, Text)]
conns
  | Bool
otherwise                        = () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
  where
    addSleep :: Text -> Text
addSleep = (Text
"sleep 0.1; " Text -> Text -> Text
forall a. Monoid a => a -> a -> a
`mappend` )

    jackCmd :: [(Text, Text)] -> Text
jackCmd = Text -> Text
addSleep (Text -> Text)
-> ([(Text, Text)] -> Text) -> [(Text, Text)] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
Text.intercalate Text
";" ([Text] -> Text)
-> ([(Text, Text)] -> [Text]) -> [(Text, Text)] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Text) -> Text
jackConn
    jackConn :: (Text, Text) -> Text
jackConn (Text
port1, Text
port2) = [Text] -> Text
Text.unwords [Text
"jack_connect", Text
port1, Text
port2]

hasJackConnections :: Options -> Bool
hasJackConnections :: Options -> Bool
hasJackConnections Options
opt
  | Just [(Text, Text)]
conns <- Options -> Maybe [(Text, Text)]
csdJackConnect Options
opt = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [(Text, Text)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Text, Text)]
conns
  | Bool
otherwise                        = Bool
False

----------------------------------------------------------
-- players

-- | Renders to tmp.csd and tmp.wav and plays with mplayer.
mplayer :: (RenderCsd a) => a -> IO ()
mplayer :: forall a. RenderCsd a => a -> IO ()
mplayer = Options -> a -> IO ()
forall a. RenderCsd a => Options -> a -> IO ()
mplayerBy Options
forall a. Default a => a
def

-- | Renders to tmp.csd and tmp.wav and plays with mplayer.
mplayerBy :: (RenderCsd a) => Options -> a -> IO ()
mplayerBy :: forall a. RenderCsd a => Options -> a -> IO ()
mplayerBy Options
opt = Options -> FilePath -> FilePath -> a -> IO ()
forall a.
RenderCsd a =>
Options -> FilePath -> FilePath -> a -> IO ()
simplePlayCsdBy Options
opt FilePath
"mplayer" FilePath
"tmp"

-- | Renders to tmp.csd and tmp.wav and plays with totem player.
totem :: (RenderCsd a) => a -> IO ()
totem :: forall a. RenderCsd a => a -> IO ()
totem = Options -> a -> IO ()
forall a. RenderCsd a => Options -> a -> IO ()
totemBy Options
forall a. Default a => a
def

-- | Renders to tmp.csd and tmp.wav and plays with totem player.
totemBy :: (RenderCsd a) => Options -> a -> IO ()
totemBy :: forall a. RenderCsd a => Options -> a -> IO ()
totemBy Options
opt = Options -> FilePath -> FilePath -> a -> IO ()
forall a.
RenderCsd a =>
Options -> FilePath -> FilePath -> a -> IO ()
simplePlayCsdBy Options
opt FilePath
"totem" FilePath
"tmp"

----------------------------------------------------------
-- handle user interrupts

runWithUserInterrupt :: IO () -> String -> IO ()
runWithUserInterrupt :: IO () -> FilePath -> IO ()
runWithUserInterrupt IO ()
setup FilePath
cmd = do
    ProcessHandle
pid <- FilePath -> IO ProcessHandle
runCommand FilePath
cmd
    IO ()
setup
    IO () -> (AsyncException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid IO ExitCode -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (ProcessHandle -> AsyncException -> IO ()
onUserInterrupt ProcessHandle
pid)
    where
        onUserInterrupt :: ProcessHandle -> E.AsyncException -> IO ()
        onUserInterrupt :: ProcessHandle -> AsyncException -> IO ()
onUserInterrupt ProcessHandle
pid AsyncException
x = case AsyncException
x of
            AsyncException
E.UserInterrupt -> ProcessHandle -> IO ()
terminateProcess ProcessHandle
pid
            AsyncException
e               -> AsyncException -> IO ()
forall a e. Exception e => e -> a
E.throw AsyncException
e

----------------------------------------------------------

-- | Runs the csound files with cabbage engine.
-- It invokes the Cabbage command line utility and setts all default cabbage flags.
runCabbage :: (RenderCsd a) => a -> IO ()
runCabbage :: forall a. RenderCsd a => a -> IO ()
runCabbage = Options -> a -> IO ()
forall a. RenderCsd a => Options -> a -> IO ()
runCabbageBy Options
forall a. Default a => a
def

-- | Runs the csound files with cabbage engine with user defined options.
-- It invokes the Cabbage command line utility and setts all default cabbage flags.
runCabbageBy :: (RenderCsd a) => Options -> a -> IO ()
runCabbageBy :: forall a. RenderCsd a => Options -> a -> IO ()
runCabbageBy Options
opt' a
a = do
    FilePath
fileCsd <- IO FilePath
getTmpFile
    Options -> FilePath -> a -> IO ()
forall a. RenderCsd a => Options -> FilePath -> a -> IO ()
writeCsdBy Options
opt FilePath
fileCsd a
a
    IO () -> FilePath -> IO ()
runWithUserInterrupt (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords [FilePath
"Cabbage", FilePath
fileCsd]
    where opt :: Options
opt = Options
opt' Options -> Options -> Options
forall a. Monoid a => a -> a -> a
`mappend` Options
setCabbage

------------------------------

-- | Alias to process inputs of single input audio-card.
onCard1 :: (Sig -> a) -> (Sig -> a)
onCard1 :: forall a. (Sig -> a) -> Sig -> a
onCard1= (Sig -> a) -> Sig -> a
forall a. a -> a
id

-- | Alias to process inputs of stereo input audio-card.
onCard2 :: (Sig2 -> a) -> (Sig2 -> a)
onCard2 :: forall a. (Sig2 -> a) -> Sig2 -> a
onCard2= (Sig2 -> a) -> Sig2 -> a
forall a. a -> a
id

-- | Alias to process inputs of audio-card with 4 inputs.
onCard4 :: (Sig4 -> a) -> (Sig4 -> a)
onCard4 :: forall a. (Sig4 -> a) -> Sig4 -> a
onCard4= (Sig4 -> a) -> Sig4 -> a
forall a. a -> a
id

-- | Alias to process inputs of audio-card with 6 inputs.
onCard6 :: (Sig6 -> a) -> (Sig6 -> a)
onCard6 :: forall a. (Sig6 -> a) -> Sig6 -> a
onCard6= (Sig6 -> a) -> Sig6 -> a
forall a. a -> a
id

-- | Alias to process inputs of audio-card with 8 inputs.
onCard8 :: (Sig8 -> a) -> (Sig8 -> a)
onCard8 :: forall a. (Sig8 -> a) -> Sig8 -> a
onCard8= (Sig8 -> a) -> Sig8 -> a
forall a. a -> a
id


#if __GLASGOW_HASKELL__ < 710

-- Sig
setArity n a = CsdArity 0 n

instance RenderCsd Sig                  where { renderCsdBy opt a = render opt (return a)             , csdArity = setArity 1 }
instance RenderCsd (SE Sig)             where { renderCsdBy opt a = render opt a }                    , csdArity = setArity 1 }
instance RenderCsd (Source Sig)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)    , csdArity = setArity 1 }
instance RenderCsd (Source (SE Sig))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a)  , csdArity = setArity 1 }

-- Sig2

instance RenderCsd Sig2                  where { renderCsdBy opt a = render opt (return a)            , csdArity = setArity 2 }
instance RenderCsd (SE Sig2)             where { renderCsdBy opt a = render opt a                     , csdArity = setArity 2 }
instance RenderCsd (Source Sig2)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)   , csdArity = setArity 2 }
instance RenderCsd (Source (SE Sig2))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a) , csdArity = setArity 2 }

-- Sig3

instance RenderCsd Sig3                  where { renderCsdBy opt a = render opt (return a)            , csdArity = setArity 3 }
instance RenderCsd (SE Sig3)             where { renderCsdBy opt a = render opt a                     , csdArity = setArity 3 }
instance RenderCsd (Source Sig3)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)   , csdArity = setArity 3 }
instance RenderCsd (Source (SE Sig3))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a) , csdArity = setArity 3 }

-- Sig4

instance RenderCsd Sig4                  where { renderCsdBy opt a = render opt (return a)            , csdArity = setArity 4 }
instance RenderCsd (SE Sig4)             where { renderCsdBy opt a = render opt a                     , csdArity = setArity 4 }
instance RenderCsd (Source Sig4)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)   , csdArity = setArity 4 }
instance RenderCsd (Source (SE Sig4))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a) , csdArity = setArity 4 }

-- Sig5

instance RenderCsd Sig5                  where { renderCsdBy opt a = render opt (return a)            , csdArity = setArity 5 }
instance RenderCsd (SE Sig5)             where { renderCsdBy opt a = render opt a                     , csdArity = setArity 5 }
instance RenderCsd (Source Sig5)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)   , csdArity = setArity 5 }
instance RenderCsd (Source (SE Sig5))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a) , csdArity = setArity 5 }

-- Sig6

instance RenderCsd Sig6                  where { renderCsdBy opt a = render opt (return a)            , csdArity = setArity 6 }
instance RenderCsd (SE Sig6)             where { renderCsdBy opt a = render opt a                     , csdArity = setArity 6 }
instance RenderCsd (Source Sig6)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)   , csdArity = setArity 6 }
instance RenderCsd (Source (SE Sig6))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a) , csdArity = setArity 6 }

-- Sig7

instance RenderCsd Sig7                  where { renderCsdBy opt a = render opt (return a)            , csdArity = setArity 7 }
instance RenderCsd (SE Sig7)             where { renderCsdBy opt a = render opt a                     , csdArity = setArity 7 }
instance RenderCsd (Source Sig7)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)   , csdArity = setArity 7 }
instance RenderCsd (Source (SE Sig7))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a) , csdArity = setArity 7 }


-- Sig8

instance RenderCsd Sig8                  where { renderCsdBy opt a = render opt (return a)            , csdArity = setArity 8 }
instance RenderCsd (SE Sig8)             where { renderCsdBy opt a = render opt a                     , csdArity = setArity 8 }
instance RenderCsd (Source Sig8)         where { renderCsdBy opt a = renderCsdBy opt (fromSource a)   , csdArity = setArity 8 }
instance RenderCsd (Source (SE Sig8))    where { renderCsdBy opt a = renderCsdBy opt (fromSourceSE a) , csdArity = setArity 8 }


instance RenderCsd (Sco (Mix Sig))       where { renderCsdBy opt a = renderCsdBy opt $ mix a , csdArity = setArity 1 }
instance RenderCsd (Sco (Mix Sig2))      where { renderCsdBy opt a = renderCsdBy opt $ mix a , csdArity = setArity 2 }
instance RenderCsd (Sco (Mix Sig3))      where { renderCsdBy opt a = renderCsdBy opt $ mix a , csdArity = setArity 3 }
instance RenderCsd (Sco (Mix Sig4))      where { renderCsdBy opt a = renderCsdBy opt $ mix a , csdArity = setArity 4 }
instance RenderCsd (Sco (Mix Sig5))      where { renderCsdBy opt a = renderCsdBy opt $ mix a , csdArity = setArity 5 }

instance RenderCsd [Sco (Mix Sig)]       where { renderCsdBy opt a = renderCsdBy opt $ mix $ har a , csdArity = setArity 1 }
instance RenderCsd [Sco (Mix Sig2)]      where { renderCsdBy opt a = renderCsdBy opt $ mix $ har a , csdArity = setArity 2 }
instance RenderCsd [Sco (Mix Sig3)]      where { renderCsdBy opt a = renderCsdBy opt $ mix $ har a , csdArity = setArity 3 }
instance RenderCsd [Sco (Mix Sig4)]      where { renderCsdBy opt a = renderCsdBy opt $ mix $ har a , csdArity = setArity 4 }
instance RenderCsd [Sco (Mix Sig5)]      where { renderCsdBy opt a = renderCsdBy opt $ mix $ har a , csdArity = setArity 5 }

#endif