We'll start our journey with a single note produced by a sine-wave oscillator. When you click , the computer will send instructions to your loudspeaker or headphones to oscillate back and forth in sinusoidal motion. This creates wave-like variations in the air that propagate all the way to your ear. Middle-C, the note below, will cause the air around your ear to vibrate 264 times a second. Our ear clumps these oscillations together as a pattern, and we hear it as a pitch. To learn more about the physics of sound, I highly recommend checking out this amazing interactive article in The Pudding.
module Main where
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
main :: Player
main = player c4
module Main where
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
main :: Player
main = player c4
The player above, as well as all of the players in this article, are editable. For example, try changing the note above from c4
to d4
, aFlat5
, or fSharp1
and see what happens.
Our single note is accompanied by a short program: the minimal amount of information we need to play back the note. The program starts by defining a module. As a convention, we usually call the main module Main
. This is followed by a series of import
statements declaring what types and terms we'll use from other libraries (I'll define "type" and "term" below). Lastly, the actual program called main
exists on two levels: the type-level (its type is Player
) and on the term-level (its terms are player
and c4
). This distinction between, and eventual interplay of, types and terms will be crucial to our reasoning about music and programs.
Programs in PureScript contain two basic units of composition: types and terms. These units form the basis of a play starring three core protagonists: you, a compiler, and a computer. A term points to some chunk of memory on a computer that stores an opaque series of bytes. We give the term a name like c4
or player
to indicate to other readers what it is or does. A type is an assertion to the compiler about how a term can be used in a program. Types have names like Player
. When the compiler receives an assertion in the form of a type, it can either accept the assertion, reject it, or punt until it receives more information. In our program above, the compiler accepts the assertion that player c4
has the type Player
. When all the assertions in a program are accepted, we say a program compiles, and the compiler sends the program off to the computer to do something interesting like render it to your screen, play it through your loudspeakers, or save it for a rainy day.
Let's revisit the program above:
module Main where
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
main :: Player
main = player c4
module Main where
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
main :: Player
main = player c4
It contains one type assertion — that main
is of type Player
— and three terms:
main
, whose type is asserted to be Player
;player
, whose type is defined in Wags.Lib.Learn
as Pitch ((->) Number) -> Player
; andc4
, whose type is defined in Wags.Lib.Learn.Pitch
as Pitch ((->) Number)
.When the compiler compiles the program, it treats every function as an if/then proposition and makes sure that we've provided enough evidence to prove this proposition. In the case above, player
is a proposition saying:
If you give me a
Pitch ((->) Number)
, I'll give you a term of typePlayer
In the program, c4
is evidence to player
(we can also call it an argument to player
or player
's input). Evidence to propositions, or equivalently arguments to functions, act like keys to a lock. The term c4
of type Pitch ((->) Number)
unlocks the proposition Pitch ((->) Number) -> Player
, producing a Player
. Because we have annotated our program main
as Player
, the compiler accepts the program, sends it to your loudspeaker and plays a note. w00t!
The fluidity with which one can switch between the language of logic (proving a proposition with evidence) and programming (applying to a function an argument) is called the Curry-Howard correspondence. Informally, it posits that programs are logical proofs and vice versa. Granted, music is a highly illogical endeavor, so this type of rigorous formalism may seem out of place given the deeply subjective nature of music composition and listening. The point of types here is to provide a set of constraints that accomplish two goals:
In the example above, we listened to our first note c4
by applying the function player
to it. Let's use some more functions to see how far we can push that note.
We'll start by acting on the volume of the note as a function of time. Let's make the note taper down to zero-volume over 5 seconds. To do so, we'll write a function that multiplies time by 0.2 and subtracts it from 1.0, which will smoothly interpolate from 1 to 0 over 5 seconds.
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
fadeOut :: Number -> Number
fadeOut time = if time > 5.0 then 0.0 else 1.0 - (0.2 * time)
main :: Player
main = player (note_ (Volume fadeOut) longest c4)
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
fadeOut :: Number -> Number
fadeOut time = if time > 5.0 then 0.0 else 1.0 - (0.2 * time)
main :: Player
main = player (note_ (Volume fadeOut) longest c4)
An equivalent way to write that would be the following:
module Main where
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Math (calcSlope)
import WAGS.Lib.Tidal.Tidal (betwixt)
fadeOut :: Number -> Number
fadeOut time = betwixt 0.0 1.0 (calcSlope 0.0 1.0 5.0 0.0 time)
main :: Player
main = player (note_ (Volume fadeOut) longest c4)
module Main where
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Math (calcSlope)
import WAGS.Lib.Tidal.Tidal (betwixt)
fadeOut :: Number -> Number
fadeOut time = betwixt 0.0 1.0 (calcSlope 0.0 1.0 5.0 0.0 time)
main :: Player
main = player (note_ (Volume fadeOut) longest c4)
calcSlope
and betwixt
are functions provided by the libraries wags
and wags-lib
, as will be the case of many of the functions we'll encounter along our path. While we'll use these functions for convenience, it's often helpful to write them out by hand for learning purposes. As a challenge throughout this and other articles, after reading the article once, try to write some these functions from scratch and compare them to the library implementations. If you feel that your implementation is better, please make a pull request!
When working with functions of time like calcSlope
, one common convention is to leave time
as the last argument. If we write a function f
of time
that internally calls a function g
of time
, we say that time
is an abstraction over the function g
. Without the time
term, we call the function f
eta-reduced.
f time = g time -- time abstracted over g
f = g -- eta-reduced
This is similar to reducing a term in algebra:
f + 2 = g + 2 -- ...is the same as stating that...
f = g
The idea of abstraction (defining a function) and application (invoking a function) are core to a formal system in mathematical logic called the Lambda Calculus. Developed in the 1930s by Alonzo Church, the Lambda Calculus acts as a syntactic basis for most functional programming languages, including PureScript.
In order to eta-reduce fadeOut
in the example above, we introduce one of the most powerful ideas in functional programming — composition, which we will represent as <<<
. When you compose two functions, you pipe the output of one into the input of another without abstracting the input to either function. If we write h time = f (g time)
, time
is abstracted over g
and (g time)
is abstracted over f
. However, if we write h = f <<< g
, the abstraction is eta-reduced both for g
's input and for f
's input. Let's see that in the example using betwixt
and calcSlope
. The time
term is no longer present - it has been eta-reduced using function composition.
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Math (calcSlope)
import WAGS.Lib.Tidal.Tidal (betwixt)
fadeOut :: Number -> Number
fadeOut = betwixt 0.0 1.0 <<< calcSlope 0.0 1.0 5.0 0.0
main :: Player
main = player (note_ (Volume fadeOut) longest c4)
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Math (calcSlope)
import WAGS.Lib.Tidal.Tidal (betwixt)
fadeOut :: Number -> Number
fadeOut = betwixt 0.0 1.0 <<< calcSlope 0.0 1.0 5.0 0.0
main :: Player
main = player (note_ (Volume fadeOut) longest c4)
Function composition is not just about terser syntax. In fact, the terser syntax — also called point-free syntax — often leads to a golf-like competition to make code as short as possible and, when done too eagerly, unreadable. As we will see in subsequent articles on Profunctors and Free Semigroupoids, composition can be applied to other things besides functions. By working at this higher level of abstraction, we unteather ourselves from functions and think in more general terms about output flowing into input. For me, this type of abstract reasoning is one of the joys of both music and functional programming, making it possible to exploit structural similarities at multiple levels of abstraction.
Let's write another function of time that makes our note step between different volumes in a cyclic fashion. We'll accomplish this using the remainder operator and guards.
module Main where
import Prelude
import Math ((%))
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
guarded :: Number -> Number
guarded t =
let
time = t % 2.0
out
| time < 0.125 = 0.1
| time < 0.25 = 0.0
| time < 0.5 = 0.8
| time < 0.625 = 0.0
| time < 0.875 = 0.8
| time < 1.0 = 0.1
| time < 1.25 = 0.0
| time < 1.5 = 0.5
| time < 1.75 = 0.0
| otherwise = 0.5
in
out
main :: Player
main = player (note_ (Volume guarded) longest c4)
module Main where
import Prelude
import Math ((%))
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
guarded :: Number -> Number
guarded t =
let
time = t % 2.0
out
| time < 0.125 = 0.1
| time < 0.25 = 0.0
| time < 0.5 = 0.8
| time < 0.625 = 0.0
| time < 0.875 = 0.8
| time < 1.0 = 0.1
| time < 1.25 = 0.0
| time < 1.5 = 0.5
| time < 1.75 = 0.0
| otherwise = 0.5
in
out
main :: Player
main = player (note_ (Volume guarded) longest c4)
We can also control the volume with a low-frequency oscilator, or LFO.
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Note (note_)
bending :: Number -> Number
bending = add 0.3 <<< lfo { phase: 0.0, amp: 0.3, freq: 8.0 }
main :: Player
main = player (note_ (Volume bending) longest c4)
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Note (note_)
bending :: Number -> Number
bending = add 0.3 <<< lfo { phase: 0.0, amp: 0.3, freq: 8.0 }
main :: Player
main = player (note_ (Volume bending) longest c4)
The one thing that all of these examples have in common is that they are functions from a Number
to a Number
. As the output of one can be the input of another, we can compose them together. Interestingly, the meanings of the word "composition" in music and functional programming largely overlap. When we compose music, we blend together sounds either in a sequence or simultaneously to crete a larger work. When we compose programs, we blend together functions to create complex control patterns and data flow.
Let's compose three functions together using the purescript operator <<<
. The first one will be our LFO, the second will add an offset, and the third will clip the wave at boundaires.
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Note (note_)
lfoIt :: Number -> Number
lfoIt = lfo { phase: 0.0, amp: 0.3, freq: 8.0 }
offsetIt :: Number -> Number
offsetIt = add 0.5
clipIt :: Number -> Number
clipIt = max 0.4 <<< min 0.6
main :: Player
main = player
$ note_
( Volume $
clipIt
<<< offsetIt
<<< lfoIt
)
longest
c4
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Note (note_)
lfoIt :: Number -> Number
lfoIt = lfo { phase: 0.0, amp: 0.3, freq: 8.0 }
offsetIt :: Number -> Number
offsetIt = add 0.5
clipIt :: Number -> Number
clipIt = max 0.4 <<< min 0.6
main :: Player
main = player
$ note_
( Volume $
clipIt
<<< offsetIt
<<< lfoIt
)
longest
c4
Visually, the result looks something like this:
There's a special term for functions whose input type is the same as the output type. We call these endo functions — endo being a prefix from the Greek ἔνδον (endon) meaning "within, inner, absorbing, or containing." We can chain together compositions of endo-functions to create some pretty jolting sounds.
The beautiful thing about chaining compositions of endo-functions is that you can comment out different functions using two dashes --
to change the result. In the example below, in addition to playing around with the values, try to comment out some functions (add --
) and comment in (remove --
) others.
module Main where
import Prelude
import Math (pi, pow)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Note (note_)
lfo1It :: Number -> Number
lfo1It = lfo { phase: 0.0, amp: 0.3, freq: 4.0 }
lfo2It :: Number -> Number
lfo2It = lfo { phase: pi, amp: 2.0, freq: 8.0 }
lfo3It :: Number -> Number
lfo3It = lfo { phase: pi, amp: 2.0, freq: 16.0 }
squareRootIt :: Number -> Number
squareRootIt = flip pow 0.5
squareIt :: Number -> Number
squareIt = flip pow 0.5
clipIt :: Number -> Number
clipIt = max 0.0 <<< min 1.0
main :: Player
main = player
$ note_
( Volume $
clipIt
<<< lfo3It
<<< squareRootIt
-- <<< lfo2It
<<< squareIt
<<< lfo1It
)
longest
c4
module Main where
import Prelude
import Math (pi, pow)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Note (note_)
lfo1It :: Number -> Number
lfo1It = lfo { phase: 0.0, amp: 0.3, freq: 4.0 }
lfo2It :: Number -> Number
lfo2It = lfo { phase: pi, amp: 2.0, freq: 8.0 }
lfo3It :: Number -> Number
lfo3It = lfo { phase: pi, amp: 2.0, freq: 16.0 }
squareRootIt :: Number -> Number
squareRootIt = flip pow 0.5
squareIt :: Number -> Number
squareIt = flip pow 0.5
clipIt :: Number -> Number
clipIt = max 0.0 <<< min 1.0
main :: Player
main = player
$ note_
( Volume $
clipIt
<<< lfo3It
<<< squareRootIt
-- <<< lfo2It
<<< squareIt
<<< lfo1It
)
longest
c4
In this article series, I will try to keep the pacing of the material more or less consistent. However, at certain points, I will glimpse into the future to show you where we are heading by subtly tweaking an example. I intend to write full articles devoted to functors, applicatives, folds, semigroups and monoids, so consider this a small mise en bouche for the not-too-distant future.
Currently, while we have a way to pipe output into an input via composition, we have no way to blend two results together. For example, if we want to add the result of an LFO to the result of a terraced function, we would write something like (\time -> lfo time + terraced time)
. While this is fine in small doses, it gets tedious if everything is a function of time. Instead, we'd like for time to flow from function to function automatically. In functional programming, there are many ways to do this, including the Reader
pattern and the Behavior
pattern. We'll see both of those in a later article, but what I'd like to show here is how to accomplish this using functors and applicatives.
The example below, we'll write the same function with time
abstracted over the function and without time
abstracted. The "without" version uses functors via the <$>
or map operator and applicative functors via the <*>
or apply operator. You can think of them as "lifting" a computation (in this case, a function of time) into an abstraction. When we "lower" the computation, we get the abstraction over time back. If you substitute variation1
for variation2
, you'll hear no difference.
module Main where
import Prelude
import Math ((%))
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
bending :: Number -> Number
bending = lfo { phase: 0.0, amp: 0.25, freq: 8.0 }
guarded :: Number -> Number
guarded t =
let
time = t % 1.0
out
| time < 0.125 = 0.3
| time < 0.25 = 0.0
| time < 0.5 = 0.6
| time < 0.625 = 0.0
| time < 0.875 = 0.3
| otherwise = 0.0
in
out
version1 :: Number -> Number
version1 time = add (bending time) (guarded time)
version2 :: Number -> Number
version2 = add <$> bending <*> guarded
main :: Player
main = player (note_ (Volume version2) longest c4)
module Main where
import Prelude
import Math ((%))
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
bending :: Number -> Number
bending = lfo { phase: 0.0, amp: 0.25, freq: 8.0 }
guarded :: Number -> Number
guarded t =
let
time = t % 1.0
out
| time < 0.125 = 0.3
| time < 0.25 = 0.0
| time < 0.5 = 0.6
| time < 0.625 = 0.0
| time < 0.875 = 0.3
| otherwise = 0.0
in
out
version1 :: Number -> Number
version1 time = add (bending time) (guarded time)
version2 :: Number -> Number
version2 = add <$> bending <*> guarded
main :: Player
main = player (note_ (Volume version2) longest c4)
Using this technique, you can blend together functions of time using binary operations, functors, applicatives, and function composition. The example below is a small Bolero using all three techniques. Play around with the parameters to see how it changes!
module Main where
import Prelude
import Math (pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
type FofTime = Number -> Number
driver1 :: FofTime
driver1 = lfo { phase: 0.0, amp: 2.0, freq: 1.0 }
freq1 :: FofTime
freq1 = lfo { phase: 0.0, amp: 1.0, freq: 2.0 }
driver2 :: FofTime
driver2 = lfo { phase: 0.0, amp: 1.5, freq: 0.25 }
freq2 :: FofTime
freq2 = lfo { phase: pi, amp: 1.0, freq: 1.0 }
signal :: FofTime
signal = min 1.0 <<< mul 0.6 <<< max 0.0 <<<
(add <$> (freq1 <<< driver1) <*> (freq2 <<< driver2))
main :: Player
main = player (note_ (Volume signal) longest c4)
module Main where
import Prelude
import Math (pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
type FofTime = Number -> Number
driver1 :: FofTime
driver1 = lfo { phase: 0.0, amp: 2.0, freq: 1.0 }
freq1 :: FofTime
freq1 = lfo { phase: 0.0, amp: 1.0, freq: 2.0 }
driver2 :: FofTime
driver2 = lfo { phase: 0.0, amp: 1.5, freq: 0.25 }
freq2 :: FofTime
freq2 = lfo { phase: pi, amp: 1.0, freq: 1.0 }
signal :: FofTime
signal = min 1.0 <<< mul 0.6 <<< max 0.0 <<<
(add <$> (freq1 <<< driver1) <*> (freq2 <<< driver2))
main :: Player
main = player (note_ (Volume signal) longest c4)
In functional programming, rather than applying a function to arguments, we often store arguments in a structure called a free structure and then interpret that structure later. Let's do that with function composition. Rather than applying it directly, we'll store its arguments in a free structure (an Array, also known as a "free monoid") and then interpret it using a simple interpreter called foldl
that applies a function (in this case, <<<
) to the arguments starting from an initial argument. Here, the initial argument is identity
— a function that returns its argument. In the example below, the result is low-fi dither that'll make your car bounce if you crank it to 11!
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Foldable (foldl)
import Math (pi, pow)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
lfo1It :: Number -> Number
lfo1It = lfo { phase: 0.0, amp: 0.3, freq: 4.0 }
lfo2It :: Number -> Number
lfo2It = lfo { phase: pi, amp: 2.0, freq: 8.0 }
lfo3It :: Number -> Number
lfo3It = lfo { phase: pi, amp: 2.0, freq: 16.0 }
squareRootIt :: Number -> Number
squareRootIt = flip pow 0.5
squareIt :: Number -> Number
squareIt = flip pow 0.5
clipIt :: Number -> Number
clipIt = max 0.0 <<< min 1.0
main :: Player
main = player
$ note_
( Volume $
foldl (<<<) identity
[ clipIt
, lfo3It
, squareRootIt
, lfo2It
, squareIt
, lfo1It
]
)
longest
c3
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Foldable (foldl)
import Math (pi, pow)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
lfo1It :: Number -> Number
lfo1It = lfo { phase: 0.0, amp: 0.3, freq: 4.0 }
lfo2It :: Number -> Number
lfo2It = lfo { phase: pi, amp: 2.0, freq: 8.0 }
lfo3It :: Number -> Number
lfo3It = lfo { phase: pi, amp: 2.0, freq: 16.0 }
squareRootIt :: Number -> Number
squareRootIt = flip pow 0.5
squareIt :: Number -> Number
squareIt = flip pow 0.5
clipIt :: Number -> Number
clipIt = max 0.0 <<< min 1.0
main :: Player
main = player
$ note_
( Volume $
foldl (<<<) identity
[ clipIt
, lfo3It
, squareRootIt
, lfo2It
, squareIt
, lfo1It
]
)
longest
c3
The function identity
is my favorite function. It comes up time and time again in functional programming through its central role in Category theory. We'll see it again when we make music using the Yoneda lemma. There are lots of neat tricks you can do with identity, including omitting it enitrely in certain forumlations. In the example below, which sounds exactly like the example above, we exploit the fact that identity is the identity in the set of endo functions (meaning that it is the endofunction that, when composed with an endofunction, will return the original).
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Foldable (fold)
import Data.Monoid.Endo (Endo(..))
import Data.Newtype (unwrap)
import Math (pi, pow)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
lfo1It :: Number -> Number
lfo1It = lfo { phase: 0.0, amp: 0.3, freq: 4.0 }
lfo2It :: Number -> Number
lfo2It = lfo { phase: pi, amp: 2.0, freq: 8.0 }
lfo3It :: Number -> Number
lfo3It = lfo { phase: pi, amp: 2.0, freq: 16.0 }
squareRootIt :: Number -> Number
squareRootIt = flip pow 0.5
squareIt :: Number -> Number
squareIt = flip pow 0.5
clipIt :: Number -> Number
clipIt = max 0.0 <<< min 1.0
main :: Player
main = player
$ note_
( Volume
$ unwrap
$ fold
$ map Endo
[ clipIt
, lfo3It
, squareRootIt
, lfo2It
, squareIt
, lfo1It
]
)
longest
c3
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Foldable (fold)
import Data.Monoid.Endo (Endo(..))
import Data.Newtype (unwrap)
import Math (pi, pow)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
lfo1It :: Number -> Number
lfo1It = lfo { phase: 0.0, amp: 0.3, freq: 4.0 }
lfo2It :: Number -> Number
lfo2It = lfo { phase: pi, amp: 2.0, freq: 8.0 }
lfo3It :: Number -> Number
lfo3It = lfo { phase: pi, amp: 2.0, freq: 16.0 }
squareRootIt :: Number -> Number
squareRootIt = flip pow 0.5
squareIt :: Number -> Number
squareIt = flip pow 0.5
clipIt :: Number -> Number
clipIt = max 0.0 <<< min 1.0
main :: Player
main = player
$ note_
( Volume
$ unwrap
$ fold
$ map Endo
[ clipIt
, lfo3It
, squareRootIt
, lfo2It
, squareIt
, lfo1It
]
)
longest
c3
Armed with our composition skills, we can approach pitch in the same way that we approached volume. Before we do, though, it'd be useful to talk a bit about the scales along which we perceive pitch and volume. While one can be plenty creative without knowing these scales, mastering them makes it easier to anticipate how music will be heard in certain cultural contexts.
In the previous example, when we were linearly changing volume between 0 and 1, the change from 0.0-0.5
was much greater than the change from 0.5-1.0
. Let's confirm that by using the example below. Switch between the functions firstHalf
and secondHalf
to hear the difference.
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Math (calcSlope)
import WAGS.Lib.Tidal.Tidal (betwixt)
firstHalf :: Number -> Number
firstHalf = betwixt 0.0 0.5 <<< calcSlope 0.0 0.0 5.0 0.5
secondHalf :: Number -> Number
secondHalf = betwixt 0.5 1.0 <<< calcSlope 0.0 0.5 5.0 1.0
main :: Player
main = player (note_ (Volume firstHalf) longest c4)
module Main where
import Prelude
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Lib.Learn.Note (note_)
import WAGS.Math (calcSlope)
import WAGS.Lib.Tidal.Tidal (betwixt)
firstHalf :: Number -> Number
firstHalf = betwixt 0.0 0.5 <<< calcSlope 0.0 0.0 5.0 0.5
secondHalf :: Number -> Number
secondHalf = betwixt 0.5 1.0 <<< calcSlope 0.0 0.5 5.0 1.0
main :: Player
main = player (note_ (Volume firstHalf) longest c4)
This is because, when we scale the amplitude of a signal linearly, we hear that change logarithmically. The unit for logarithmic amplitude is the bel, and in almsot all literature on sound, you'll hear folks talking about tenths of bels, or decibels (dB for short). Below is a chart that shows loudness (amplitude ratio) descending from 1 to 0, and the corresponding change in decibels, and how we effectively hear it (the power ratio).
dB | Power ratio | Amplitude ratio |
---|---|---|
0 | 1 | 1 |
−1 | 0 .794 | 0 .891 |
−3 | 0 .501 ≈ 1⁄2 | 0 .708 ≈ √1⁄2 |
−6 | 0 .251 ≈ 1⁄4 | 0 .501 ≈ 1⁄2 |
−10 | 0 .1 | 0 .3162 |
−20 | 0 .01 | 0 .1 |
−30 | 0 .001 | 0 .03162 |
−40 | 0 .0001 | 0 .01 |
−50 | 0 .00001 | 0 .003162 |
−60 | 0 .000001 | 0 .001 |
−70 | 0 .0000001 | 0 .0003162 |
−80 | 0 .00000001 | 0 .0001 |
−90 | 0 .000000001 | 0 .00003162 |
−100 | 0 .0000000001 | 0 .00001 |
We can bring this even closer to human perception using Fletcher-Munson curves, also known as equal-loudness contours. This adds ripples into our logarithmic model that represent the ideosyncracies of human hearing. Many sensible defaults in industry-grade automatic equalization and mastering software are based on these curves.
Pitch also exists on many different scales, and depending on our choice of scale, we can have radically different musical outocmes that are evokative of cultures that span the globe. When we use notes like c4
or aFlat3
, we draw them from a scale called the equally-tempered chromatic scale. This scale became standardized in Europe in the 18th century and is currently the basis of most popular music. The equally-tempered scale is also a logarithmic one: we perceive two pitches to be of the same class when based on powers of 2. For example, most people hear 220.0 (220 * 2 ^ 0
), 440.0 (220 * 2 ^ 1
), 880.0 (220 * 2 ^ 2
) and 1760.0 (220 * 2 ^ 3
) as the same note shifted higher and higher. Let's use that as a point of departure for our first exmaple on pitch.
module Main where
import Prelude
import Math ((%))
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (mezzoForte)
import WAGS.Lib.Learn.Note (note_)
jumpy :: Number -> Number
jumpy t =
let
time = t % 1.0
out
| time < 0.25 = 220.0
| time < 0.5 = 440.0
| time < 0.75 = 880.0
| otherwise = 1760.0
in
out
main :: Player
main = player (note_ mezzoForte longest (Pitch jumpy))
module Main where
import Prelude
import Math ((%))
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Volume (mezzoForte)
import WAGS.Lib.Learn.Note (note_)
jumpy :: Number -> Number
jumpy t =
let
time = t % 1.0
out
| time < 0.25 = 220.0
| time < 0.5 = 440.0
| time < 0.75 = 880.0
| otherwise = 1760.0
in
out
main :: Player
main = player (note_ mezzoForte longest (Pitch jumpy))
All of the same functions we used to control volume can also be used to control the pitch of our single note. In the example below, the same base
function is scaled to appropriate ranges for each parameter. Again, we'll use composition (<<<
) for this.
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Math (pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Math (calcSlope)
type FofTime = Number -> Number
driver1 :: FofTime
driver1 = lfo { phase: 0.0, amp: 2.0, freq: 1.0 }
freq1 :: FofTime
freq1 = lfo { phase: 0.0, amp: 1.0, freq: 2.0 }
driver2 :: FofTime
driver2 = lfo { phase: 0.0, amp: 1.5, freq: 0.25 }
freq2 :: FofTime
freq2 = lfo { phase: pi, amp: 1.0, freq: 1.0 }
base :: FofTime
base = add <$> (freq1 <<< driver1) <*> (freq2 <<< driver2)
vol :: FofTime
vol = min 1.0 <<< mul 0.6 <<< max 0.0 <<< base
pitch :: FofTime
pitch = calcSlope (-1.0) 220.0 1.0 800.0 <<< base
main :: Player
main = player (note_ (Volume vol) longest (Pitch pitch))
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Math (pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
import WAGS.Math (calcSlope)
type FofTime = Number -> Number
driver1 :: FofTime
driver1 = lfo { phase: 0.0, amp: 2.0, freq: 1.0 }
freq1 :: FofTime
freq1 = lfo { phase: 0.0, amp: 1.0, freq: 2.0 }
driver2 :: FofTime
driver2 = lfo { phase: 0.0, amp: 1.5, freq: 0.25 }
freq2 :: FofTime
freq2 = lfo { phase: pi, amp: 1.0, freq: 1.0 }
base :: FofTime
base = add <$> (freq1 <<< driver1) <*> (freq2 <<< driver2)
vol :: FofTime
vol = min 1.0 <<< mul 0.6 <<< max 0.0 <<< base
pitch :: FofTime
pitch = calcSlope (-1.0) 220.0 1.0 800.0 <<< base
main :: Player
main = player (note_ (Volume vol) longest (Pitch pitch))
When working with pitch, it's often useful to use notes from a scale like c4
or d5
. In addition, we can transpose notes by adding intervals. Let's see an example that modulates transposition based on time. Another interesting aspect of this example is that pitch no longer contains a function of time (no more Pitch (\t -> f t)
), but rather a function of time is used to produce a Pitch
(something isomorphic to \t -> Pitch (f t)
). We can distribute time
from the outside to the inside of pitch using the function join
— a function we'll explore deeper when we look at monads.
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Identity (Identity)
import Data.Newtype (unwrap)
import Math ((%), pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = Pitch <<< compose (unwrap <<< unwrap)
beat :: FofTime
beat = max 0.0 <<< lfo { phase: 0.5 * pi, amp: 0.75, freq: 8.0 }
chord :: Number -> Pitch Identity
chord t =
let
time = t % 1.0
out
| time < 0.25 = c4
| time < 0.5 = eFlat4
| time < 0.75 = fSharp4
| otherwise = a4
in
out
transposition :: Number -> Pitch Identity
transposition t =
let
time = t % 6.0
out
| time < 1.0 = minorThird
| time < 2.0 = augmentedFourth
| time < 3.0 = majorSixth
| time < 4.0 = octave
| time < 5.0 = majorSixth
| otherwise = augmentedFourth
in
out
main :: Player
main = player $
note_
(Volume beat)
longest
(toPitch (add <$> chord <*> transposition))
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Identity (Identity)
import Data.Newtype (unwrap)
import Math ((%), pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = Pitch <<< compose (unwrap <<< unwrap)
beat :: FofTime
beat = max 0.0 <<< lfo { phase: 0.5 * pi, amp: 0.75, freq: 8.0 }
chord :: Number -> Pitch Identity
chord t =
let
time = t % 1.0
out
| time < 0.25 = c4
| time < 0.5 = eFlat4
| time < 0.75 = fSharp4
| otherwise = a4
in
out
transposition :: Number -> Pitch Identity
transposition t =
let
time = t % 6.0
out
| time < 1.0 = minorThird
| time < 2.0 = augmentedFourth
| time < 3.0 = majorSixth
| time < 4.0 = octave
| time < 5.0 = majorSixth
| otherwise = augmentedFourth
in
out
main :: Player
main = player $
note_
(Volume beat)
longest
(toPitch (add <$> chord <*> transposition))
Interestingly, we see that when we add an octave to a pitch, this has the effect of multiplying it by 2. This is because Pitch
adheres to a different meaning of add
and mul
than Number
. In functional programming, the behavior of operators like add
and mul
can vary from type to type so long as they follow certain predefined laws. For addition and multiplcation, the laws in question are those of the Semiring. Here is how they're defined in wags-lib
.
cpsToMidi' :: Number -> Number
cpsToMidi' i = (log (i / 440.0) / log 2.0) * 12.0 + 69.0
midiToCps' :: Number -> Number
midiToCps' i = 440.0 * (2.0 `pow` ((i - 69.0) / 12.0))
instance semiringPitch :: Applicative f => Semiring (Pitch f) where
zero = Pitch (pure zero)
one = Pitch (pure one)
add (Pitch a) (Pitch b) = Pitch (midiToCps' <$>
(add <$> (cpsToMidi' <$> a) <*> (cpsToMidi' <$> b)))
mul (Pitch a) (Pitch b) = Pitch (midiToCps' <$>
(mul <$> (cpsToMidi' <$> a) <*> (cpsToMidi' <$> b)))
Are these definitions in fact lawful? Let's test them out in music! In functional programming, when we test laws, we usually use a library called QuickCheck to generate a bunch of random examples, which we'll do here. In each example, we'll hear pairs of notes in series, and if the pairs are always the same, the law holds!
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Array.NonEmpty (fromNonEmpty)
import Data.Function (on)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Identity (Identity)
import Data.Int (toNumber)
import Data.Lens (view, over, _1, _2)
import Data.List (List(..), length, sortBy, (:))
import Data.Newtype (unwrap)
import Data.NonEmpty ((:|))
import Data.Profunctor (dimap)
import Data.Traversable (sequence)
import Data.Tuple.Nested (type (/\), (/\))
import Data.Unfoldable (replicate)
import Math ((%))
import Test.QuickCheck (mkSeed)
import Test.QuickCheck.Gen (Gen, elements, evalGen)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type PitchI = Pitch Identity
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = Pitch <<< compose (unwrap <<< unwrap)
beat :: FofTime
beat = max 0.0 <<< lfo { phase: 0.0, amp: 0.75, freq: 8.0 }
aPitch :: Gen PitchI
aPitch = elements $ fromNonEmpty
$ c0 :| [ cSharp0, d0, eFlat0, e0, f0, fSharp0, g0, aFlat0, a0, bFlat0, b0 ]
law1 :: Gen (PitchI /\ PitchI)
law1 = do
a <- aPitch
b <- aPitch
c <- aPitch
pure $ (a + (b + c)) /\ ((a + b) + c)
bigGuard :: List (Number /\ PitchI) -> PitchI -> Number -> PitchI
bigGuard Nil default _ = default
bigGuard ((a /\ b) : c) default time
| time < a = b
| otherwise = bigGuard c default time
gap = 0.25 :: Number
pitches :: List (Number /\ PitchI)
pitches = sortBy (compare `on` view _1) (left <> right)
where
orig = evalGen
(sequence $ replicate 100 law1)
({ newSeed: mkSeed 0, size: 10 })
mapped x f = map (over _1 x)
$ mapWithIndex
(dimap ((/\) <<< toNumber) ((map <<< map) (view f)) ($))
orig
left = mapped (add gap <<< mul gap <<< mul 2.0) _1
right = mapped (add gap <<< mul gap <<< add 1.0 <<< mul 2.0) _2
main :: Player
main = player
$ note_ (Volume beat) longest
$ toPitch
$ compose (bigGuard pitches c4)
(flip (%) (toNumber (length pitches) * gap))
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Array.NonEmpty (fromNonEmpty)
import Data.Function (on)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Identity (Identity)
import Data.Int (toNumber)
import Data.Lens (view, over, _1, _2)
import Data.List (List(..), length, sortBy, (:))
import Data.Newtype (unwrap)
import Data.NonEmpty ((:|))
import Data.Profunctor (dimap)
import Data.Traversable (sequence)
import Data.Tuple.Nested (type (/\), (/\))
import Data.Unfoldable (replicate)
import Math ((%))
import Test.QuickCheck (mkSeed)
import Test.QuickCheck.Gen (Gen, elements, evalGen)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type PitchI = Pitch Identity
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = Pitch <<< compose (unwrap <<< unwrap)
beat :: FofTime
beat = max 0.0 <<< lfo { phase: 0.0, amp: 0.75, freq: 8.0 }
aPitch :: Gen PitchI
aPitch = elements $ fromNonEmpty
$ c0 :| [ cSharp0, d0, eFlat0, e0, f0, fSharp0, g0, aFlat0, a0, bFlat0, b0 ]
law1 :: Gen (PitchI /\ PitchI)
law1 = do
a <- aPitch
b <- aPitch
c <- aPitch
pure $ (a + (b + c)) /\ ((a + b) + c)
bigGuard :: List (Number /\ PitchI) -> PitchI -> Number -> PitchI
bigGuard Nil default _ = default
bigGuard ((a /\ b) : c) default time
| time < a = b
| otherwise = bigGuard c default time
gap = 0.25 :: Number
pitches :: List (Number /\ PitchI)
pitches = sortBy (compare `on` view _1) (left <> right)
where
orig = evalGen
(sequence $ replicate 100 law1)
({ newSeed: mkSeed 0, size: 10 })
mapped x f = map (over _1 x)
$ mapWithIndex
(dimap ((/\) <<< toNumber) ((map <<< map) (view f)) ($))
orig
left = mapped (add gap <<< mul gap <<< mul 2.0) _1
right = mapped (add gap <<< mul gap <<< add 1.0 <<< mul 2.0) _2
main :: Player
main = player
$ note_ (Volume beat) longest
$ toPitch
$ compose (bigGuard pitches c4)
(flip (%) (toNumber (length pitches) * gap))
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Array.NonEmpty (fromNonEmpty)
import Data.Function (on)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Identity (Identity)
import Data.Int (toNumber)
import Data.Lens (view, over, _1, _2)
import Data.List (List(..), sortBy, length, (:))
import Data.Newtype (unwrap)
import Data.NonEmpty ((:|))
import Data.Profunctor (dimap)
import Data.Traversable (sequence)
import Data.Tuple.Nested (type (/\), (/\))
import Data.Unfoldable (replicate)
import Math ((%))
import Test.QuickCheck (mkSeed)
import Test.QuickCheck.Gen (Gen, elements, evalGen)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type PitchI = Pitch Identity
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = Pitch <<< compose (unwrap <<< unwrap)
beat :: FofTime
beat = max 0.0 <<< lfo { phase: 0.0, amp: 0.75, freq: 8.0 }
aMult :: Gen PitchI
aMult = elements $ fromNonEmpty $ semitone :| [ wholeTone, minorThird, majorThird ]
aPitch :: Gen PitchI
aPitch = elements $ fromNonEmpty
$ c0 :| [ cSharp0, d0, eFlat0, e0, f0, fSharp0, g0, aFlat0, a0, bFlat0, b0 ]
law2 :: Gen (PitchI /\ PitchI)
law2 = do
a <- aMult
b <- aPitch
c <- aPitch
pure $ (a * (b + c)) /\ (a * b + a * c)
bigGuard :: List (Number /\ PitchI) -> PitchI -> Number -> PitchI
bigGuard Nil default _ = default
bigGuard ((a /\ b) : c) default time
| time < a = b
| otherwise = bigGuard c default time
gap = 0.25 :: Number
pitches :: List (Number /\ PitchI)
pitches = sortBy (compare `on` view _1) (left <> right)
where
orig = evalGen
(sequence $ replicate 100 law2)
({ newSeed: mkSeed 0, size: 10 })
mapped x f = map (over _1 x)
$ mapWithIndex
(dimap ((/\) <<< toNumber) ((map <<< map) (view f)) ($))
orig
left = mapped (mul gap <<< mul 2.0) _1
right = mapped (mul gap <<< add 1.0 <<< mul 2.0) _2
main :: Player
main = player
$ note_ (Volume beat) longest
$ toPitch
$ compose (bigGuard pitches c4)
(flip (%) (toNumber (length pitches) * gap))
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Array.NonEmpty (fromNonEmpty)
import Data.Function (on)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Identity (Identity)
import Data.Int (toNumber)
import Data.Lens (view, over, _1, _2)
import Data.List (List(..), sortBy, length, (:))
import Data.Newtype (unwrap)
import Data.NonEmpty ((:|))
import Data.Profunctor (dimap)
import Data.Traversable (sequence)
import Data.Tuple.Nested (type (/\), (/\))
import Data.Unfoldable (replicate)
import Math ((%))
import Test.QuickCheck (mkSeed)
import Test.QuickCheck.Gen (Gen, elements, evalGen)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type PitchI = Pitch Identity
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = Pitch <<< compose (unwrap <<< unwrap)
beat :: FofTime
beat = max 0.0 <<< lfo { phase: 0.0, amp: 0.75, freq: 8.0 }
aMult :: Gen PitchI
aMult = elements $ fromNonEmpty $ semitone :| [ wholeTone, minorThird, majorThird ]
aPitch :: Gen PitchI
aPitch = elements $ fromNonEmpty
$ c0 :| [ cSharp0, d0, eFlat0, e0, f0, fSharp0, g0, aFlat0, a0, bFlat0, b0 ]
law2 :: Gen (PitchI /\ PitchI)
law2 = do
a <- aMult
b <- aPitch
c <- aPitch
pure $ (a * (b + c)) /\ (a * b + a * c)
bigGuard :: List (Number /\ PitchI) -> PitchI -> Number -> PitchI
bigGuard Nil default _ = default
bigGuard ((a /\ b) : c) default time
| time < a = b
| otherwise = bigGuard c default time
gap = 0.25 :: Number
pitches :: List (Number /\ PitchI)
pitches = sortBy (compare `on` view _1) (left <> right)
where
orig = evalGen
(sequence $ replicate 100 law2)
({ newSeed: mkSeed 0, size: 10 })
mapped x f = map (over _1 x)
$ mapWithIndex
(dimap ((/\) <<< toNumber) ((map <<< map) (view f)) ($))
orig
left = mapped (mul gap <<< mul 2.0) _1
right = mapped (mul gap <<< add 1.0 <<< mul 2.0) _2
main :: Player
main = player
$ note_ (Volume beat) longest
$ toPitch
$ compose (bigGuard pitches c4)
(flip (%) (toNumber (length pitches) * gap))
Indeed, we hear that the addition of pitch commutes — a + (b + c) = (a + b) + c
. Furthermore, multiplication distributes: a * (b + c) = a * b + a * c
. The abiltiy to define custom behavior of functions on types based on laws is a core feature of most programming languages in the ML-family, including Haskell, Idris, and of course PureScript
. The fact that a single function operates differently on different types according to an underlying law is a deeply musical idea. It is the essence of a theme or motif: something that can function differently in different contexts while retaining its identity.
Getting less mathy for a bit, here are the first four bars of BWV 846 transcribed using the methods we've covered so far.
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Distributive (distribute)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Identity (Identity)
import Data.Int (toNumber)
import Data.List (List(..), length, (:))
import Data.Newtype (unwrap, wrap)
import Data.Profunctor (lcmap)
import Data.Tuple.Nested (type (/\), (/\))
import Math ((%), pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type PitchI = Pitch Identity
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = wrap <<< unwrap <<< distribute <<< map unwrap
beat :: FofTime
beat = max 0.0 <<< lfo { phase: pi, amp: 0.75, freq: 2.0 / gap }
bigGuard :: List (Number /\ PitchI) -> PitchI -> Number -> PitchI
bigGuard Nil default _ = default
bigGuard ((a /\ b) : c) default time
| time < a = b
| otherwise = bigGuard c default time
gap = 0.3 :: Number
pitches :: List (Number /\ PitchI)
pitches =
mapWithIndex
(lcmap ((/\) <<< add gap <<< mul gap <<< toNumber) ($)) $
c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : c4 : d4 : a4 : d5 : f5 : a4 : d5 : f5 : c4 : d4 : a4 : d5 : f5 : a4 : d5 : f5 : b3 : d4 : g4 : d5 : f5 : g4 : d5 : f5 : b3 : d4 : g4 : d5 : f5 : g4 : d5 : f5 : c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : Nil
main :: Player
main = player
$ note_ (Volume beat) longest
$ toPitch
$ compose (bigGuard pitches c4)
(flip (%) (toNumber (length pitches) * gap))
module Main where
import Prelude
import WAGS.Lib.Learn.Pitch
import Data.Distributive (distribute)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Identity (Identity)
import Data.Int (toNumber)
import Data.List (List(..), length, (:))
import Data.Newtype (unwrap, wrap)
import Data.Profunctor (lcmap)
import Data.Tuple.Nested (type (/\), (/\))
import Math ((%), pi)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Duration (longest)
import WAGS.Lib.Learn.Note (note_)
import WAGS.Lib.Learn.Oscillator (lfo)
import WAGS.Lib.Learn.Volume (Volume(..))
type PitchI = Pitch Identity
type FofTime = Number -> Number
toPitch :: (Number -> Pitch Identity) -> Pitch ((->) Number)
toPitch = wrap <<< unwrap <<< distribute <<< map unwrap
beat :: FofTime
beat = max 0.0 <<< lfo { phase: pi, amp: 0.75, freq: 2.0 / gap }
bigGuard :: List (Number /\ PitchI) -> PitchI -> Number -> PitchI
bigGuard Nil default _ = default
bigGuard ((a /\ b) : c) default time
| time < a = b
| otherwise = bigGuard c default time
gap = 0.3 :: Number
pitches :: List (Number /\ PitchI)
pitches =
mapWithIndex
(lcmap ((/\) <<< add gap <<< mul gap <<< toNumber) ($)) $
c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : c4 : d4 : a4 : d5 : f5 : a4 : d5 : f5 : c4 : d4 : a4 : d5 : f5 : a4 : d5 : f5 : b3 : d4 : g4 : d5 : f5 : g4 : d5 : f5 : b3 : d4 : g4 : d5 : f5 : g4 : d5 : f5 : c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : c4 : e4 : g4 : c5 : e5 : g4 : c5 : e5 : Nil
main :: Player
main = player
$ note_ (Volume beat) longest
$ toPitch
$ compose (bigGuard pitches c4)
(flip (%) (toNumber (length pitches) * gap))
What if, before the mapWithIndex
, you add (map <<< map) (add minorThird) $
?
One of my favorite aspects about both music and functional programming is that anything can be a unit of construction or a subject of deconstruction. Often these two processes can happen at the same time. As a last exercise, and as a glimpse into the future, let's again start with a "single" note that is comprised of six oscillators.
module Main where
import Prelude
import WAGS.Create.Optionals (gain, sinOsc, speaker)
import WAGS.Lib.Learn (player, Player)
fundamental = 220.0 :: Number
main :: Player
main = player
$ speaker
{ o0: gain 0.2 (sinOsc (fundamental * 1.0))
, o1: gain 0.04 (sinOsc (fundamental * 2.0))
, o2: gain 0.15 (sinOsc (fundamental * 3.0))
, o3: gain 0.02 (sinOsc (fundamental * 4.0))
, o4: gain 0.1 (sinOsc (fundamental * 5.0))
, o5: gain 0.01 (sinOsc (fundamental * 6.0))
}
module Main where
import Prelude
import WAGS.Create.Optionals (gain, sinOsc, speaker)
import WAGS.Lib.Learn (player, Player)
fundamental = 220.0 :: Number
main :: Player
main = player
$ speaker
{ o0: gain 0.2 (sinOsc (fundamental * 1.0))
, o1: gain 0.04 (sinOsc (fundamental * 2.0))
, o2: gain 0.15 (sinOsc (fundamental * 3.0))
, o3: gain 0.02 (sinOsc (fundamental * 4.0))
, o4: gain 0.1 (sinOsc (fundamental * 5.0))
, o5: gain 0.01 (sinOsc (fundamental * 6.0))
}
Now, let's undercut the unity of our sound by pulling it apart over time. To do this, we'll again use LFOs, this time to subtly shift the overtones of the pitch.
module Main where
import Prelude
import WAGS.Create.Optionals (gain, sinOsc, speaker)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Oscillator (lfo)
fundamental = 220.0 :: Number
main :: Player
main = player
$ \time -> speaker
{ o0: gain
( 0.2 +
lfo { phase: 0.0, amp: 0.1, freq: 0.2 } time
)
(sinOsc (fundamental * 1.0))
, o1: gain
( 0.04 +
lfo { phase: 0.0, amp: 0.02, freq: 0.3 } time
)
(sinOsc (fundamental * 2.0))
, o2: gain
( 0.15 +
lfo { phase: 0.0, amp: 0.1, freq: 0.4 } time
)
(sinOsc (fundamental * 3.0))
, o3: gain
( 0.05 +
lfo { phase: 0.0, amp: 0.04, freq: 0.5 } time
)
(sinOsc (fundamental * 4.0))
, o4: gain
( 0.1 +
lfo { phase: 0.0, amp: 0.09, freq: 0.6 } time
)
(sinOsc (fundamental * 5.0))
, o5: gain
( 0.03 +
lfo { phase: 0.0, amp: 0.02, freq: 0.7 } time
)
(sinOsc (fundamental * 6.0))
}
module Main where
import Prelude
import WAGS.Create.Optionals (gain, sinOsc, speaker)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Oscillator (lfo)
fundamental = 220.0 :: Number
main :: Player
main = player
$ \time -> speaker
{ o0: gain
( 0.2 +
lfo { phase: 0.0, amp: 0.1, freq: 0.2 } time
)
(sinOsc (fundamental * 1.0))
, o1: gain
( 0.04 +
lfo { phase: 0.0, amp: 0.02, freq: 0.3 } time
)
(sinOsc (fundamental * 2.0))
, o2: gain
( 0.15 +
lfo { phase: 0.0, amp: 0.1, freq: 0.4 } time
)
(sinOsc (fundamental * 3.0))
, o3: gain
( 0.05 +
lfo { phase: 0.0, amp: 0.04, freq: 0.5 } time
)
(sinOsc (fundamental * 4.0))
, o4: gain
( 0.1 +
lfo { phase: 0.0, amp: 0.09, freq: 0.6 } time
)
(sinOsc (fundamental * 5.0))
, o5: gain
( 0.03 +
lfo { phase: 0.0, amp: 0.02, freq: 0.7 } time
)
(sinOsc (fundamental * 6.0))
}
In this section, we learned how to use functions to shape a single note. We saw how we can compose functions to modulate a note's volume and pitch, and we saw how to compose together several notes into one larger note that breaks apart and reforms as we listen to it. I'm pretty sure that the next article will be called The Rhythm and the Functor, so stay tuned for that!
Click here to learn more about working with these examples on the cloud, on Windows, on Mac or on Linux. Click here to learn more about the PureScript programming language, and join the Discord using this link. You'll find me on the
#music
channel 🎶