------------------------------------------------------------------------------ -- Synths.hs -- created: Sun Sep 2 00:39:11 JST 2012 ------------------------------------------------------------------------------ module Sound.Conductive.Synths where import Control.Concurrent import Control.Monad import Data.List import Data.Map import Data.Maybe import Sound.Conductive.ConductiveBaseData import Sound.Conductive.MusicalEnvironment import Sound.Conductive.Pitch import Sound.Conductive.Scale import Sound.OpenSoundControl import Sound.SC3 import Sound.SC3.ID import System.Random hiding (next) pingDef :: IO OSC pingDef = let f = control IR "f" 440 d = control IR "d" 1 p = envPerc 0.01 d e = envGen KR 1 0.1 0 1 RemoveSynth p o = out 0 (sinOsc AR (mce [f,f*1.005]) 0 * e) i fd = do async fd (d_recv (synthdef "ping2" o)) in withSC3 i ping :: Double -> Double -> IO () ping freq dur = let ps = [("f",freq) ,("d",dur) ] in withSC3 (\fd -> send fd (s_new "ping2" (-1) AddToTail 1 ps)) ------------------------------------------------------------------------------ -- trying a method for defining synths defineSynth :: UGen -> String -> IO OSC defineSynth func synthName = withSC3 i where o = out 0 func i fd = do async fd (d_recv (synthdef synthName o)) playSynth :: [(String, Double)] -> String -> IO () playSynth ps synthName = withSC3 (\fd -> send fd (s_new synthName (-1) AddToTail 1 ps)) pingDef2 :: IO OSC pingDef2 = defineSynth (sinOsc AR (mce [(midiCPS f),(midiCPS $ f*1.005)]) 0 * e) "ping2" where f = control IR "f" 440 d = control IR "d" 1 p = envPerc 0.01 d e = envGen KR 1 0.1 0 1 RemoveSynth p ping2 :: Double -> Double -> IO () ping2 freq dur = playSynth ps "ping2" where ps = [("f",freq) ,("d",dur) ] pmTestDef :: IO OSC pmTestDef = defineSynth (pmOsc AR f (mf * 10000) (pm * 10000) 0 * a * e) "pmTest" where att = control IR "att" 0.05 cf = control IR "f" 60 a = control IR "a" 0.5 d = control IR "d" 1 mf = control IR "mf" 0 pm'= control IR "pm" 0 pm = line KR 0 pm' 9 DoNothing p = envPerc att d e = envGen KR 1 (1*a) 0 1 RemoveSynth p f = mce [(midiCPS cf),(midiCPS cf)*1.005] pmTest :: Double -> Double -> Double -> Double -> Double -> Double -> IO () pmTest attack freq amp modFreq modAmp dur = playSynth ps "pmTest" where ps = [("att",attack) ,("f",freq) ,("a",amp) ,("mf",modFreq) ,("pm",modAmp) ,("d",dur) ] rudeBassDef :: IO OSC rudeBassDef = defineSynth sumSynths "rudeBass" where att = control IR "att" 0.05 cf = midiCPS $ control IR "f" 60 a = control IR "a" 0.5 d = control IR "d" 1 mf = control IR "mfscalar" 0 m = line KR cf (cf * mf) d DoNothing p = envPerc att d e = envGen KR 1 (1 * a) 0 1 RemoveSynth p flavorBass = syncSaw AR (mce [cf,cf*1.01] ) m * 0.1 * e sinSubBass = (sinOsc AR (mce [(cf * 0.5),(cf * 1.005 * 0.5)]) 0 * e) ff = mouseX KR 2 (cf*50) Exponential 0.1 sumSynths = lpf (flavorBass + sinSubBass) ff rudeBass :: Double -> Double -> Double -> Double -> Double -> IO () rudeBass attack freq amp modS dur = playSynth ps "rudeBass" where ps = [("att",attack) ,("f",freq) ,("a",amp) ,("mfscalar",modS) ,("d",dur) ]