vivid: Sound synthesis with SuperCollider
Music and sound synthesis with SuperCollider.
Example usage (after installing and booting SuperCollider):
{-# LANGUAGE DataKinds, ExtendedDefaultRules #-}
import Vivid
playSong :: VividAction m => m ()
playSong = do
fork $ do
s0 <- synth theSound (36 ::I "note")
wait 1
free s0
s1 <- synth theSound (60 ::I "note")
forM_ [62,66,64] $ \note -> do
wait (1/4)
set s1 (note ::I "note")
wait (1/4)
free s1
theSound :: SynthDef '["note"]
theSound = sd (0 ::I "note") $ do
wobble <- sinOsc (freq_ 5) ? KR ~* 10 ~+ 10
s <- 0.1 ~* sinOsc (freq_ $ midiCPS (V::V "note") ~+ wobble)
out 0 [s,s]
main :: IO ()
main = do
putStrLn "Simplest:"
playSong
putStrLn "With precise timing:"
doScheduledIn 0.1 playSong
wait 1
putStrLn "Written to a file, non-realtime synthesis:"
putStrLn "(Need to quit the running server for NRT)"
quitSCServer
writeNRT "song.wav" playSong
[Skip to Readme]
Modules
[Index] [Quick Jump]
- Vivid
- Vivid.Actions
- Vivid.ByteBeat
- Vivid.Envelopes
- Vivid.GlobalState
- Vivid.NoGlobalState
- Vivid.NoPlugins
- Vivid.NoPluginsNoGlobalState
- OSC
- Vivid.Randomness
- Vivid.SCServer
- Vivid.SynthDef
- Vivid.UGens
- Vivid.UGens.Algebraic
- Vivid.UGens.Analysis
- Vivid.UGens.Args
- Vivid.UGens.Buffer
- Vivid.UGens.Conversion
- Vivid.UGens.Convolution
- Vivid.UGens.Delays
- Vivid.UGens.Demand
- Vivid.UGens.Dynamics
- Vivid.UGens.Envelopes
- Vivid.UGens.Examples
- Vivid.UGens.FFT
- Vivid.UGens.Filters
- Generators
- Vivid.UGens.InOut
- Vivid.UGens.Info
- Vivid.UGens.Maths
- Vivid.UGens.Multichannel
- Vivid.UGens.Random
- Vivid.UGens.Reverbs
- Vivid.UGens.SynthControl
- Vivid.UGens.Triggers
- Vivid.UGens.Undocumented
- Vivid.UGens.UserInteraction
Downloads
- vivid-0.5.2.1.tar.gz [browse] (Cabal source package)
- Package description (as included in the package)
Maintainer's Corner
For package maintainers and hackage trustees
Candidates
- No Candidates
| Versions [RSS] | 0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.3, 0.2.0.0, 0.2.0.1, 0.2.0.2, 0.2.0.3, 0.2.0.4, 0.2.0.5, 0.3.0.0, 0.3.0.1, 0.3.0.2, 0.4.2.0, 0.4.2.1, 0.4.2.2, 0.4.2.3, 0.4.2.4, 0.5.0.0, 0.5.0.1, 0.5.0.2, 0.5.1.0, 0.5.2.0, 0.5.2.1 (info) |
|---|---|
| Dependencies | base (>3 && <5), binary, bytestring, cereal, containers, directory, filepath (>=1.0), hashable (>=1.2.0.6), MonadRandom, mtl, network, process, random (>=1.1), random-shuffle (>=0.0.3), split (>=0.2.0.0), stm, time (>=1.2), transformers (>=0.2.0.0), utf8-string, vivid-osc (>=0.4 && <0.6), vivid-supercollider (>=0.4 && <0.5) [details] |
| License | LicenseRef-GPL |
| Author | Tom Murphy |
| Maintainer | Tom Murphy |
| Category | Audio, Music, Sound |
| Uploaded | by TomMurphy at 2024-10-10T19:26:28Z |
| Distributions | NixOS:0.5.2.1 |
| Reverse Dependencies | 2 direct, 0 indirect [details] |
| Downloads | 11018 total (42 in the last 30 days) |
| Rating | 2.5 (votes: 3) [estimated by Bayesian average] |
| Your Rating | |
| Status | Docs available [build log] Last success reported on 2024-10-10 [all 1 reports] |