Hi 👋

I'm Mike, and I use functional programming to make music and noise.

module Main where

import Prelude

import Data.Lens (traversed, set)
import Data.Newtype (unwrap)
import Data.Tuple.Nested ((/\))
import Foreign.Object as Object
import WAGS.Lib.Learn (Player, player)
import WAGS.Lib.Tidal (tdl)
import WAGS.Lib.Tidal.Types (AFuture)
import WAGS.Lib.Tidal.Tidal (lnr, lnv, make, onTag, parse, s)
import WAGS.Lib.Tidal.Types (BufferUrl(..))

wag :: AFuture
wag =
  make (4.0 * 1.0 * 60.0 / 111.0)
    { earth: s
        """bass:1 msg hh ~ [hh:6 bass:0] msg:2 hh ~ ,
    ~ chin*4 ~ ~ ~ tech:0*2 ~ ~ ,
    ~ ~ hh:2 ~ ~ newnotes [~ newnotes:2] ~  ,
    ~ ~ ~ ~ hh:7 ~ ~ tech:2*4 ,
    ~ ~ ~ ~ ~ ~ ~ chin:1*2 ,
    pad:3"""
    , wind: s
        $ onTag "comp"
            ( set (traversed <<< lnv)
                $ (if _ then 1.0 else 0.0)
                    <<< flip (<) 0.9
                    <<< _.normalizedLittleCycleTime
                    <<< unwrap
            )
        $ onTag "comp"
            ( set (traversed <<< lnr)
                $ add 0.95
                    <<< mul 0.1
                    <<< _.initialEntropy
                    <<< unwrap
            )
        $ parse "wdm:1;comp"
    , sounds: map BufferUrl $ Object.fromFoldable $
        [ "wdm:0" /\ "https://freesound.org/data/previews/332/332741_34095-lq.mp3"
        , "wdm:1" /\ "https://freesound.org/data/previews/332/332740_34095-hq.mp3"
        ]
    }

main :: Player
main = player $ tdl $ wag
module Main where import Prelude import Data.Lens (traversed, set) import Data.Newtype (unwrap) import Data.Tuple.Nested ((/\)) import Foreign.Object as Object import WAGS.Lib.Learn (Player, player) import WAGS.Lib.Tidal (tdl) import WAGS.Lib.Tidal.Types (AFuture) import WAGS.Lib.Tidal.Tidal (lnr, lnv, make, onTag, parse, s) import WAGS.Lib.Tidal.Types (BufferUrl(..)) wag :: AFuture wag = make (4.0 * 1.0 * 60.0 / 111.0) { earth: s """bass:1 msg hh ~ [hh:6 bass:0] msg:2 hh ~ , ~ chin*4 ~ ~ ~ tech:0*2 ~ ~ , ~ ~ hh:2 ~ ~ newnotes [~ newnotes:2] ~ , ~ ~ ~ ~ hh:7 ~ ~ tech:2*4 , ~ ~ ~ ~ ~ ~ ~ chin:1*2 , pad:3""" , wind: s $ onTag "comp" ( set (traversed <<< lnv) $ (if _ then 1.0 else 0.0) <<< flip (<) 0.9 <<< _.normalizedLittleCycleTime <<< unwrap ) $ onTag "comp" ( set (traversed <<< lnr) $ add 0.95 <<< mul 0.1 <<< _.initialEntropy <<< unwrap ) $ parse "wdm:1;comp" , sounds: map BufferUrl $ Object.fromFoldable $ [ "wdm:0" /\ "https://freesound.org/data/previews/332/332741_34095-lq.mp3" , "wdm:1" /\ "https://freesound.org/data/previews/332/332740_34095-hq.mp3" ] } main :: Player main = player $ tdl $ wag

The example above is written in a functional programming language called PureScript. It makes use of several control structures and data-flow patterns that are challenging to recreate in a Digital Audio Workstation, or DAW.

The history of music is full of examples of artists (1) coalescing around, (2) making abundant use of, and (3) ultimately destroying a technology. Western notation and Western harmony have both followed this arc. I believe that the DAW is entering phase 3, and artists are grasping for new means of expression as their traditional tools fail them. Functional programming (or "FP") helps break out of the current dominant paradigm, providing a collection of powerful ideas that allow artists to create radically new work. I hope that, by the end of our time together, you'll feel empowered to use FP in your own artistic creations.

The journey ahead

Over the next few lessons, we'll go over concepts like rhythms, functors, chords, products, improvisation, co-ends, mysticism and dependent types. The goal will be to use music to strengthen our intuition about functional programming and to use functional programming to strengthen our intuition about music.

During this journey, we will frequently make use of our fingers to edit code and our ears to listen. Our basic interface will be an editor pane like the one below. Click or press the button below the code to hear the note c4.

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

In the example you're listening to, c4 is a pitch representing middle-c on a piano. Press and then click on c4 to edit the code. Try changing the c4 to d4, then press again and listen to the difference. What about aFlat4? c5?

Building from here, we can arrive at complex patterns in relatively few lines of code.

module Main where

import Prelude
import WAGS.Lib.Learn.Duration
import WAGS.Lib.Learn.Pitch
import WAGS.Lib.Learn.Volume
import Control.Apply (lift2)
import Control.Comonad (extract)
import Control.Comonad.Cofree (Cofree, deferCofree)
import Control.Comonad.Cofree.Class (unwrapCofree)
import Data.Identity (Identity(..))
import Data.Newtype (unwrap)
import Data.NonEmpty ((:|))
import Data.Tuple.Nested ((/\))
import WAGS.Lib.Cofree (deferCombine)
import WAGS.Lib.Learn (player, Player)
import WAGS.Lib.Learn.Note (Note(..), note_)
import WAGS.Lib.Learn.Tempo (allegro)
import WAGS.Lib.Stream (cycle)

volumes = cycle $ forte :|
  [ mezzoPiano
  , forte
  , mezzoPiano
  , forte
  , mezzoPiano
  , mezzoForte
  ]

pitches = cycle $ c4 :|
  [ g4, f4, eFlat4, bFlat4, d5, eFlat4, bFlat4, d5, f5, d5, bFlat4, eFlat4, f4, g4 ]

rhythms = cycle $ map allegro $ crochet :|
  [ quaver
  , semiquaver
  , quaver
  , semiquaver
  , quaver
  , semiquaver
  ]

zap = deferCombine ($) lift2

notes = note_ `map` volumes `zap` rhythms `zap` pitches

main :: Player
main = player notes
module Main where import Prelude import WAGS.Lib.Learn.Duration import WAGS.Lib.Learn.Pitch import WAGS.Lib.Learn.Volume import Control.Apply (lift2) import Control.Comonad (extract) import Control.Comonad.Cofree (Cofree, deferCofree) import Control.Comonad.Cofree.Class (unwrapCofree) import Data.Identity (Identity(..)) import Data.Newtype (unwrap) import Data.NonEmpty ((:|)) import Data.Tuple.Nested ((/\)) import WAGS.Lib.Cofree (deferCombine) import WAGS.Lib.Learn (player, Player) import WAGS.Lib.Learn.Note (Note(..), note_) import WAGS.Lib.Learn.Tempo (allegro) import WAGS.Lib.Stream (cycle) volumes = cycle $ forte :| [ mezzoPiano , forte , mezzoPiano , forte , mezzoPiano , mezzoForte ] pitches = cycle $ c4 :| [ g4, f4, eFlat4, bFlat4, d5, eFlat4, bFlat4, d5, f5, d5, bFlat4, eFlat4, f4, g4 ] rhythms = cycle $ map allegro $ crochet :| [ quaver , semiquaver , quaver , semiquaver , quaver , semiquaver ] zap = deferCombine ($) lift2 notes = note_ `map` volumes `zap` rhythms `zap` pitches main :: Player main = player notes

In the example above, try adding or removing pitches, rhythms, and dynamics to/from the arrays and listen to what effect that produces.

If you find functional programming intimidating, you're certainly not alone. When I started out on my journey through FP, concepts like the functor and the semigroupoid were so overwhelming that I almost gave up. Music proved to be the path that helped me truly understand functional programming, and inversely, functional programming changed the way I looked at music. As you make your way through these articles, I hope that one domain always reinforces the other, helping you become more creative musicians and programmers.

Lastly, a bit of housekeeping. All you need is a browser to follow along, play the audio examples, and edit them. However, at a certain point, you may want to experiment on your local machine or jam with others on a shared server. At the end of every article, including this one, there will be links to more resources about PureScript, music making in the browser, and functional programming in general.

Next

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 🎶