A Vivid Christmas Carol

This is a Literate Haskell file; you can view the source here


{-# LANGUAGE DataKinds, ExtendedDefaultRules #-}
import Vivid

Don’t let the LANGUAGE pragmas scare you – if you’re an average Vivid user you can just pop these two lines at the top of your file and you’re ready to go.

Up and Running

You’ll need vivid (at least version 0.5.1) and SuperCollider.

Boot the SuperCollider server (either on the command line or by hitting Ctrl-b/Command-b in the SC IDE), then load this file into GHCi.

Making a Sound

In Vivid / SuperCollider, you make sounds by creating Synths. Synths are created using Synth Definitions, or SynthDefs.

We’ll use a SynthDef adapted from one on sccode.org, which is a great place to explore what’s possible with SuperCollider.

At first we’ll just look at the type signature – we’ll explore the definition later:


bell :: SynthDef '["note", "t60", "pitchy", "amp", "gate"]

This type signature might look a little unusual, but you can learn it by using it. Basically we’re saying that "note", "t60", etc are arguments to the SynthDef, almost like arguments to a function.


firstSound :: IO ()
firstSound = do
   _ <- synth bell (60 ::I "note", 6 ::I "t60", 4 ::I "pitchy")
   pure ()

If everything’s set up, that should sound like this:

So it’s like we’re passing 60 as the "note" argument to bell, 6 for "t60", etc. The arguments can come in any order, and notice that not all the ones bell supports are required: they’re all optional because they all have default values.

(You can remember “I” as “initial value”)

Time

synth is a normal Haskell function, so we can use our Haskell powers to create abstractions:


playNote :: VividAction m => I "note" -> m ()
playNote note = do
   _ <- synth bell (note ::I "note", 9 ::I "t60", 1 ::I "pitchy")
   pure ()

silentNightStart :: VividAction m => m ()
silentNightStart = do
   playNote 60
   wait (3/4)
   playNote 62
   wait (1/4)
   playNote 60
   wait (1/2)
   playNote 57
   wait (3/2)

Which sounds like:

wait just waits a given number of seconds.

We’ve switched from IO () to a more general type signature. This isn’t required but it lets us do a lot of cool things, which we’ll learn more about below.

We changed a few parameters, and even though they’re both bells they sound fairly different.

Another thing to notice is that we throw away the result of synth. If we held onto it, we could use it to stop and restart the running Synth, change its parameters while it was running, and more.

Okay so how is this bell sound actually defined?

The SynthDef


bell = sd (1 ::I "note", 1 ::I "t60", 1 ::I "pitchy", 0.1 ::I "amp", 1 ::I "gate") $ do

Here’s the first line of our SynthDef. If you squint, it’s a little like the left hand side of a function.

sd is short for SynthDef.

1, 1, 1, 0.1, and 1 are the default values for the SynthDef arguments.

In other words, if the above were a function in a language with default arguments, it might look like:

bell (fs = 1, t60 = 1, pitchy = 1, amp = 0.1, gate = 1) = …


   exciter <- whiteNoise
      ~* percGen (attackSecs_ 0.001, releaseSecs_ 0.05, doneAction_ 0, gate_ (V::V "gate"))
      ~* 0.25

~* is just multiplication for signals. It’s a "*" plus a little sound wave “~”. There are similar operators ~+, ~-, ~/, etc.

whiteNoise and percGen are Unit Generators or UGens. These are the things which actually create sounds. SynthDefs are graphs of UGens.

attackSecs_ and releaseSecs_ are a way of having named arguments for the UGens (in this case, for percGen).

percGen creates an envelope, a way of shaping sound. We’ll see (and explain) “V::V” again below.


   let freqs = [1, 2, 2.803, 3.871, 5.074, 7.81, 10.948, 14.421]
       amps = [1, 0.044, 0.891, 0.0891, 0.794, 0.1, 0.281, 0.079]
   ringTimes <- mapM (~* (V::V "t60")) [1, 0.205, 1, 0.196, 0.339, 0.047, 0.058, 0.047]

V::V "t60" is the way we reference the current value of the I "t60" argument above. You can remember “V” as “value of”


   let klankArgs = zip3 freqs amps ringTimes

   sig <- klank (in_ exciter, freqScale_ $ midiCPS (V::V "note") ~* (V::V "pitchy")) klankArgs

klank is a bit complicated as far as UGens go, but whenever you have questions there’s plenty of documentation.

midiCPS takes a nice-to-work-with 0-127 MIDI note number and converts it to cycles per second, which is what’s usually needed for frequencies in UGens.


   sig <- freeVerb (in_ sig)
   sig <- sig ~* (V::V "amp")

People in the SuperCollider world use the “s = foo ; s = bar(s)” etc idiom of continually redefining a single variable name. This can be pretty useful, e.g. when you want to comment out part of a filter chain.


   detectSilence (in_ sig, amp_ 0.001, time_ 0.5, doneAction_ 2)

If the bell has stopped ringing, remove the Synth.


   out 0 [sig, sig]

And voila, send it out to the speakers! If you’re listening with two speakers (like with headphones), the left speaker is the first element of the array, the right is the second. If you’ve got an 8-speaker surround sound setup, no problem: just make the list longer!

All Together Now

Let’s abstract out playing and waiting:


playNotesWithWaits :: VividAction m => [(I "note", Rational)] -> m ()
playNotesWithWaits notesNWaits =
   forM_ notesNWaits $ \(note, waitAmt) -> do
      playNote note
      wait waitAmt

silentNight :: VividAction m => m ()
silentNight = do
   replicateM_ 2 $ do
      silentNightStart
   let part2 = [(67, 1), (67, 1/2), (64, 3/2), (65, 1), (65, 1/2), (60, 3/2)]
       part3 = [(62, 1), (62, 1/2), (65, 3/4), (64, 1/4), (62, 1/2), (60, 3/4), (62, 1/4), (60, 1/2), (57, 3/2)]
       part4 = [(67, 1), (67, 1/2), (70, 3/4), (67, 1/4), (64, 1/2), (65, 3/2), (69, 3/2)]
       part5 = [(65, 1/2), (60, 1/2), (57, 1/2), (60, 3/4), (58, 1/4), (55, 1/2), (53, 2)]
   playNotesWithWaits $
         part2
      ++ part3
      ++ part3
      ++ part4
      ++ part5

While we played this in GHCi, using IO (), there are other ways to use VividActions. One way is to use doScheduledIn and doScheduledAt to have precise musical timing. Another way is to write to a file, using Non-Real Time (NRT) mode. This is how easy it was to write out the final audio file for this blog post:


writeFinal = writeNRT "silent-night.flac" silentNight

And here’s how it sounds:

Next Steps

If you want to swim further out into the sea of Vivid, here are a few more things to try

However and whatever you celebrate, wishing you a happy holiday season and an incredible New Year!