vivid: Sound synthesis with SuperCollider

[ audio, library, music, sound ] [ Propose Tags ]

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

Modules

[Last Documentation]

  • Vivid
    • Vivid.Actions
      • Vivid.Actions.Class
      • Vivid.Actions.IO
      • Vivid.Actions.NRT
      • Vivid.Actions.Scheduled
    • Vivid.ByteBeat
    • Vivid.Envelopes
    • Vivid.NoPlugins
    • OSC
      • Vivid.OSC.Bundles
    • Vivid.Randomness
    • Vivid.SCServer
      • Vivid.SCServer.Connection
      • Vivid.SCServer.State
      • Vivid.SCServer.Types
    • Vivid.SynthDef
      • Vivid.SynthDef.FromUA
      • Vivid.SynthDef.ToSig
      • Vivid.SynthDef.Types
      • Vivid.SynthDef.TypesafeArgs
    • 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
        • Vivid.UGens.Filters.BEQSuite
        • Vivid.UGens.Filters.Linear
        • Vivid.UGens.Filters.Nonlinear
        • Vivid.UGens.Filters.Pitch
      • Generators
        • Vivid.UGens.Generators.Chaotic
        • Vivid.UGens.Generators.Deterministic
        • Vivid.UGens.Generators.Granular
        • Vivid.UGens.Generators.SingleValue
        • Vivid.UGens.Generators.Stochastic
      • 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

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

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 (info)
Dependencies base (>3 && <5), binary, bytestring, containers, directory, filepath (>=1.0), hashable (>=1.2.0.6), MonadRandom, mtl, network, process, random (>=1.1 && <1.2), 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
Revised Revision 1 made by TomMurphy at 2020-10-02T17:25:40Z
Category Audio, Music, Sound
Uploaded by TomMurphy at 2018-11-10T21:18:52Z
Distributions
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 10330 total (58 in the last 30 days)
Rating 2.5 (votes: 3) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2018-11-10 [all 3 reports]