{-# LANGUAGE DataKinds, ExtendedDefaultRules #-}
import Vivid
wobble = sd (0 ::I "note") $ do
s <- 50 ~* sinOsc (freq_ 10) ? KR
freq <- midiCPS (V::V "note") ~+ s
s1 <- sinOsc (freq_ freq)
s2 <- 0.1 ~* s1
out 0 [s2, s2]
main = do
s <- synth wobble ()
let notes = take 12 $
[ x | x <- [38..]
, (x `mod` 12) `elem` [0,3,5]
]
forM_ (cycle notes) $ \note -> do
set s (toI note ::I "note")
wait 0.2
{-# LANGUAGE DataKinds, ExtendedDefaultRules #-} import Vivid tone = sd (0::I "note") $ do a <- lfTri (freq_ 0.2) ? KR ~* 0.5 ~+ 0.5 freq <- lag (in_ $ midiCPS (V::V "note"), lagSecs_ 1.25) ? KR b <- 0.1 ~* varSaw (freq_ freq, width_ a) out 0 [b, b] main = do s <- synth tone (45::I "note") forever $ forM_ [45, 57, 64, 55] $ \freq -> do set s (freq :: I "note") wait 2.5
These answers mainly come from questions asked on the mailing list. If you've got a question not answered here, ask there!
Server.supernova;
s.options.numBuffers = 1024 * 16;
s.waitForBoot{
Routine{
include("Vowel");
include("SuperDirt");
2.wait;
~dirt = SuperDirt.start;
5.wait;
postln(~dirt.soundLibrary);
// These are your SynthDefs.
// You can make as many as you want,
// and you can name them whatever you want.
// Just make sure to give them the arguments
// that your Haskell SynthDefs will have:
SynthDef(\foo1, {|out=0, freq=440| Out.ar(out, DC.ar(0)) }).add;
SynthDef(\foo2, {|out=0, freq=440| Out.ar(out, DC.ar(0)) }).add;
~dirt.soundLibrary.addSynth(\foo1);
~dirt.soundLibrary.addSynth(\foo2);
"done".postln;
}.play
}
sclang boot.scd
d1 $ sound "~ bd*2"
d3 $ s "hh*8" # gain "[1 0.8]*4"
:set -XDataKinds
import Vivid
-- Use C-c C-e in emacs to eval the whole definition:
s' :: SynthDef '["out", "freq"]
s' = sdNamed "foo1" (0::I "out", 440::I "freq") $ do
env <- percGen none ~* 0.5
s <- sinOsc (freq_ (V::V "freq")) ~* env
out (V::V "out") [s,s]
defineSD $ s'
d2 $ s "foo1*8 " # note "[1 3 2 5]*2 " # gain "1.2 0.8"
If you want a I "foo"
but all you've got is a Double
or Int
or even a I "bar"
(any Real number), you can convert it with the toI
function.
Here's an example:
a = 5 :: Double
b = toI a :: I "foo"
c = 5 :: I "bar"
d = toI c :: I "foo"
Here's how you might use it in a performance:
{-# LANGUAGE DataKinds, ExtendedDefaultRules #-}
import Vivid
myNums :: [Double]
myNums = [1..10]
sd0 = undefined :: SynthDef '["freq"]
sd1 = undefined :: SynthDef '["amp"]
main = do
s0 <- synth sd0 ()
s1 <- synth sd1 ()
forM_ myNums $ \n -> do
set s0 (toI n :: I "freq")
set s1 (toI n :: I "amp")
mySong = do
fork $ do
wait 1
s1 <- synth foo ()
wait 1
free s
s2 <- synth bar ()
wait 1.5
free s2
It has the type:
mySong :: VividAction m => m ()
If you call mySong
in GHCi, it will be a IO ()
action and the timing will be handled by Haskell. It won't be sample-accurate. But, if you call doScheduledIn 0.2 mySong
the timing will be sample-accurate, scheduled on SC's server (0.2 seconds from now). There's also doScheduledAt
which - with getTime
and addSecs
- gives us the absolute-time version.
In addition, if you call:
writeNRT "foo.wav" mySong
the song will be rendered (much) faster than real time to the file, also sample-accurate. ("NRT" stands for non-realtime)
Sometimes it can be helpful to plug a synth into another one, as if we were plugging an electric guitar into a distortion pedal, which is in turn plugged into an amplifier.
Here's a simple example of creating an effect which clips its input (a very simple distortion), and then plugging a simple sinOsc synth into it:
{-# LANGUAGE DataKinds, ExtendedDefaultRules #-}
import Vivid
-- An audio bus number (see below). For this example, an arbitrary choice:
busNum = 23
--A simple effect:
effect :: SynthDef '["in", "out"]
effect = sd (23 ::I "in", 0 ::I "out") $ do
i <- aIn (bus_ (V::V "in"))
s <- clip2 0.1 i
out' [s,s]
-- A simple sound that we want to feed into the effect:
origin :: SynthDef '["out"]
origin = sd (0 ::I "out") $ do
s <- sinOsc (freq_ 440)
out' [s]
main :: IO ()
main = do
putStrLn "First, with no effects:"
-- By default, "out" is 0, which goes to audio out (e.g. our headphones)
x <- synth origin ()
wait 1
free x
putStrLn "Now with an effect:"
fx <- synth effect (toI busNum :: I "in")
-- When we're not feeding one synth into another one, we usually don't care
-- what order synths get processed. But when we do, input comes before output:
x <- synthBefore fx origin (toI busNum ::I "out")
wait 1
free fx
free x
From the SuperCollider docs (in Reference/Server-Architecture.schelp):
"Synths send audio signals to each other via a single global array of audio buses. Audio buses are indexed by integers beginning with zero. Using buses rather than connecting synths to each other directly allows synths to connect themselves to the community of other synths without having to know anything about them specifically. The lowest numbered buses get written to the audio hardware outputs."
In other words, when we output to hardware, we say e.g. "out 0", and when we write to an audio bus for an effect, we write to a higher number (e.g. "out 23" unless you have 23 hardware outputs!), but the process is the same.