tl;dr https://klank.dev && https://discourse.klank.dev
I just launched klank.dev! It's a browser-based audio sandbox that uses PureScript as its input language.
Below is a small tutorial using my favorite coding technique: copy and paste. For each example below:
- Copy and paste the entire snippet into the klank.dev editor after deleting whatever gunk was there before.
- Press
k
thenENTER
to compile. - Press
p
thenENTER
to play. - Press
s
thenENTER
to stop.
Use Firefox! 🦊 + 🎧 = 💪
Hello klank
A simple sine wave.
module Klank.Dev where
import Prelude
import Data.Typelevel.Num (D1)
import FRP.Behavior (Behavior)
import FRP.Behavior.Audio (AudioUnit, gain', runInBrowser, sinOsc, speaker')
import Type.Klank.Dev (Klank, klank)
scene :: Number -> Behavior (AudioUnit D1)
scene = const $ pure (speaker' (gain' 0.2 $ sinOsc 220.0))
main :: Klank
main = klank { run = runInBrowser scene }
Two's company
Double the sine waves, double the fun.
module Klank.Dev where
import Prelude
import Data.Typelevel.Num (D1)
import Data.List ((:), List(..))
import Data.NonEmpty ((:|))
import FRP.Behavior (Behavior)
import FRP.Behavior.Audio (AudioUnit, gain', runInBrowser, sinOsc, speaker)
import Type.Klank.Dev (Klank, klank)
scene :: Number -> Behavior (AudioUnit D1)
scene = const $ pure (speaker
((gain' 0.2 $ sinOsc 220.0)
:| (gain' 0.1 $ sinOsc 330.0)
: Nil))
main :: Klank
main = klank { run = runInBrowser scene }
Sampler
Atari speech 🤖
module Klank.Dev where
import Prelude
import Effect.Class(liftEffect)
import Effect.Aff(Aff, launchAff_)
import Control.Promise(toAffE)
import Data.List ((:), List(..))
import Data.NonEmpty ((:|))
import Effect.Class(liftEffect)
import Foreign.Object as O
import Data.Traversable(sequence)
import Data.Typelevel.Num (D1)
import FRP.Behavior (Behavior)
import Data.Vec((+>), empty)
import Type.Klank.Dev(Klank, klank, affable)
import FRP.Behavior.Audio (AudioUnit,
decodeAudioDataFromUri,
BrowserAudioTrack, gain', gain, makeAudioTrack, play, loopBuf,
runInBrowser, makePeriodicWave, sinOsc, speaker, BrowserAudioBuffer, CanvasInfo)
import Math (pi, sin)
vol = 1.4
scene :: Number -> Behavior (AudioUnit D1)
scene time = let
rad = pi * time
in
pure $ speaker ((gain' (0.3 * vol) (loopBuf "atar" (1.0 + 0.1 * sin rad) 0.0 0.0) )
:| (gain' (0.15 * vol)
(loopBuf "atar"
(1.5 + 0.1 * sin (2.0 * rad))
(0.1 + 0.1 * sin rad)
(0.5 + 0.25 * sin (2.0 * rad))))
: (gain' (0.3 * vol) (loopBuf "atar" 0.25 0.0 0.0) )
: Nil)
buffers ctx _ = affable $ sequence (
O.singleton "atar"
$ toAffE (decodeAudioDataFromUri ctx "https://freesound.org/data/previews/100/100981_1234256-lq.mp3"))
main :: Klank
main = klank {
run = runInBrowser scene,
buffers = buffers
}
Fake cricket
Click the 🖱️ while this is playing 😁
module Klank.Dev where
import Prelude
import Data.List ((:), List(..))
import Data.NonEmpty ((:|))
import Data.Typelevel.Num (D1, D2)
import Foreign.Object as O
import Data.Vec((+>), empty)
import Effect.Class(liftEffect)
import Data.Set(isEmpty)
import FRP.Behavior (Behavior)
import FRP.Behavior.Audio (AudioUnit, gain',
runInBrowser_, dup1, panner, merger,
sinOsc, play, speaker,
makeAudioTrack)
import Math (pi, sin)
import Type.Klank.Dev(Klank, klank, affable)
import FRP.Behavior.Mouse (buttons)
import FRP.Event.Mouse (Mouse, getMouse)
scene :: Mouse -> Number -> Behavior (AudioUnit D2)
scene mouse time = f time <$> click
where
f s cl =
let
rad = pi * s
in
dup1
( (gain' (if cl then 0.01 else 0.0) $ sinOsc (1830.0 + (20.0 * sin (0.2 * rad))))
+ (gain' (if cl then 0.01 else 0.0) $ sinOsc (1840.0 + (if cl then 50.0 else 0.0)))
) \mono ->
speaker
$ ( (panner rad (merger (mono +> mono +> empty)))
:| (gain' 0.5 $ (play "forest"))
: Nil
)
click :: Behavior Boolean
click = map (not <<< isEmpty) $ buttons mouse
tracks _ = affable (do
forest <- liftEffect $ makeAudioTrack "https://freesound.org/data/previews/530/530415_1648170-lq.mp3"
pure $ O.singleton "forest" forest)
enableMicrophone = true
main :: Klank
main = klank {
run = runInBrowser_ do
mouse <- getMouse
pure $ scene mouse
, tracks = tracks
}
Modulating voice
This one uses your microphone, so please only run it with headphones!
module Klank.Dev where
import Prelude
import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..))
import Data.Typelevel.Num (D1)
import FRP.Behavior (Behavior)
import FRP.Behavior.Audio (AudioUnit, g'add, g'bandpass, g'delay, g'gain, graph, microphone, runInBrowser, speaker')
import Math (pi, sin)
import Record.Extra (SLProxy(..), SNil)
import Type.Data.Graph (type (:/))
import Type.Klank.Dev (Klank, klank)
scene :: Number -> Behavior (AudioUnit D1)
scene time =
pure
$ speaker'
( graph
{ aggregators:
{ out: Tuple g'add (SLProxy :: SLProxy ("combine" :/ SNil))
, combine: Tuple g'add (SLProxy :: SLProxy ("gain" :/ "mic" :/ SNil))
, gain: Tuple (g'gain 0.9) (SLProxy :: SLProxy ("del" :/ SNil))
}
, processors:
{ del: Tuple (g'delay (0.7 + 0.45 * sin (0.25 * time * pi))) (SProxy :: SProxy "filt")
, filt: Tuple (g'bandpass 440.0 1.0) (SProxy :: SProxy "combine")
}
, generators:
{ mic: microphone
}
}
)
main :: Klank
main =
klank
{ enableMicrophone = true
, run = runInBrowser scene
}
For more info...
I'm slowly but surely adding examples and documentation to discourse.klank.dev. A good place to start is here. If anything's broken, it's my fault. Please file a bug report on the discourse using the Site feedback tag.
THANK YOU for checking out klank.dev, I hope you have fun, and please share what you make!
Top comments (2)
This is awesome! Great educational materials to build up computational thinking. Keep up the good work!
Thanks Jonny! I hope you enjoy klank, and if you feel like sharing, please post a couple klanks on the newly-minted discourse!