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

[Skip to Readme]

Downloads

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, 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 2020-12-16T07:55:29Z
Distributions
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 10274 total (64 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 2020-12-16 [all 1 reports]

Readme for vivid-0.5.1.0

[back to package description]

Vivid - music and sound synthesis in Haskell

Example usage:

{-# LANGUAGE DataKinds #-}

import Vivid

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]

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

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 "/tmp/song.wav" playSong