module Main where -- module SuperColliderMIDI where import Sound.OpenSoundControl import Sound.SC3 as SC3 import Sound.SC3.UGen.Noise.Base as Noise import qualified Sound.ALSA.Sequencer as AlsaMidi import qualified Sound.MIDI.Message.Channel as ChannelMsg import qualified Sound.MIDI.Message.Channel.Voice as VoiceMsg import Data.List (lookup) import Data.Maybe (mapMaybe, fromMaybe, ) sound :: UGen sound = out 0 (delayN (0.2 * rlpf (Noise.whiteNoise (UGenId 0) AR * Control KR "Volume" 1) (Control KR "Frequency" 400) (Control KR "Resonance" 0.005)) 0 (MCE [0, Control KR "Phase" 0])) controlChange :: String -> (Double -> Double) -> Int -> IO () controlChange ctrlName f value = let cValue = f (fromIntegral value / 127) in print (ctrlName, cValue) >> withSC3 (\fd -> send fd (n_set (-1) [(ctrlName, cValue)])) main :: IO () main = do withSC3 reset audition sound putStrLn "turn the wheels ..." AlsaMidi.withEvents "midinoise" "midinoise-listen" $ \ ll -> putStrLn "use 'pmidi -l' to find out the ports from where controller values can be received" >> putStrLn "and connect the source with this program using 'aconnect'" >> mapM_ (\mev -> case mev of ChannelMsg.Cons _chan (ChannelMsg.Voice ev) -> case ev of VoiceMsg.Control ctrl value -> fromMaybe (return ()) $ lookup ctrl $ (VoiceMsg.mainVolumeMSB, controlChange "Volume" id value) : (VoiceMsg.footControlMSB, controlChange "Frequency" (\x -> 200 * 4 ** x) value) : (VoiceMsg.breathControlMSB, controlChange "Resonance" (\x -> 1 / 1000 ** x) value) : (VoiceMsg.modulationMSB, controlChange "Phase" (0.002*) value) : [] _ -> return () _ -> return ()) (mapMaybe AlsaMidi.eventToChannelMsg ll)