On Mon, 31 Mar 2008, alex wrote:

> Great stuff Henning, thanks!
>
> I'm planning on using a midi device in a performance on Friday, does
> anyone already have some example code for using this to control
> supercollider patchecs made with Rohan's HSC3, to save me a bit of time?
> If not I'll play around and try to provide this myself...

See attachment and good luck!
{-# options -O2 #-}
module Main where
-- module SuperColliderMIDI where

import System.Cmd (rawSystem)

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.Event as MidiEvent
import qualified Sound.MIDI.File  as MidiFile


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 controlName f value =
   let cValue = f (fromIntegral value / 127)
   in  print (controlName, cValue) >>
       withSC3 (\fd -> send fd (n_set (-1)
           [(controlName, cValue)]))


main = do
   withSC3 reset
   audition sound

   putStrLn "started..."
   AlsaMidi.withMIDIEvents "midinoise" "midinoise-listen" $ \ ll ->
      -- you may have to adapt the port numbers to your setting
      rawSystem "aconnect" ["72:0", "128:0"] >>
      mapM_ (\mev -> case mev of
         MidiFile.MIDIEvent _chan ev ->
            case ev of
               MidiEvent.Control MidiEvent.MainVolumeMSB value ->
                  controlChange "Volume" id value
               MidiEvent.Control MidiEvent.FootControlMSB value ->
                  controlChange "Frequency" (\x -> 200 * 4 ** x) value
               MidiEvent.Control MidiEvent.BreathControlMSB value ->
                  controlChange "Resonance" (\x -> 1 / 1000 ** x) value
               MidiEvent.Control MidiEvent.ModulationMSB value ->
                  controlChange "Phase" (0.002*) value
               _ -> return ()
         _ -> return ())
         ll
_______________________________________________
haskell-art mailing list
haskell-art@lists.lurk.org
http://lists.lurk.org/mailman/listinfo/haskell-art

Reply via email to