vivid-0.3.0.1: Sound synthesis with SuperCollider

Safe HaskellNone
LanguageHaskell98

Vivid.Actions

Description

Actions. VividAction has 3 instances:

Synopsis

Documentation

synth :: (VividAction m, VarList params, Subset (InnerVars params) args) => SynthDef args -> params -> m (Synth args) Source #

Create a real live music-playing synth from a boring, dead SynthDef.

If you haven't defined the SynthDef on the server, this will do it automatically (Note that this may cause jitters in musical timing)

Given...

>>> let foo = sd () $ out 0 [0.1 ~* whiteNoise]

...you can create a synth with...

>>> synth foo ()

Careful!: The SC server doesn't keep track of your nodes for you, so if you do something like...

>>> s <- synth someSynth ()
>>> s <- synth oops ()           -- 's' is overwritten

...you've got no way to refer to the first synth you've created, and if you want to stop it you have to cmdPeriod

(If you want to interop with SC's language (or other SC clients), use sdNamed and synthNamed)

synthG :: (VividAction m, VarList params) => SynthDef a -> params -> m NodeId Source #

Make a synth, "G"radually typed -- doesn't check that _ is a subset of _ Useful e.g. if you want to send a bunch of args, some of which may be discarded

(Personally I'd recommend not using this function)

>>> let s = undefined :: SynthDef '["ok"]
>>> synth s (4::I "ok", 5::I "throwaway")
>>> <interactive>:
>>> Could not deduce (Elem "ignore" '[]) arising from a use of ‘synth’
>>> synthG s (4::I "ok", 5::I "throwaway")
>>> (works)

synthNamed :: (VividAction m, VarList params) => String -> params -> m (Synth a) Source #

synthNamedG :: (VividAction m, VarList params) => String -> params -> m NodeId Source #

newSynthBefore :: (VividAction m, VarList params, Subset (InnerVars params) args, IsNode node) => node -> SynthDef args -> params -> m (Synth args) Source #

Create a synth just before the target node (see "Order of Execution")

synthBefore :: (VividAction m, VarList params, Subset (InnerVars params) args, IsNode node) => node -> SynthDef args -> params -> m (Synth args) Source #

Alias for newSynthBefore

Create a synth just before the target node (see "Order of Execution")

newSynthAfter :: (VividAction m, VarList params, Subset (InnerVars params) args, IsNode node) => node -> SynthDef args -> params -> m (Synth args) Source #

Create a synth just after the target node (see "Order of Execution")

Create a synth just before the target node (see "Order of Execution")

synthAfter :: (VividAction m, VarList params, Subset (InnerVars params) args, IsNode node) => node -> SynthDef args -> params -> m (Synth args) Source #

Alias for newSynthAfter

Create a synth just before the target node (see "Order of Execution")

newSynthAtHead :: (VividAction m, VarList params, Subset (InnerVars params) args, IsGroup group) => group -> SynthDef args -> params -> m (Synth args) Source #

Create a synth at the head of the target group (see "Order of Execution")

synthHead :: (VividAction m, VarList params, Subset (InnerVars params) args, IsGroup group) => group -> SynthDef args -> params -> m (Synth args) Source #

Alias for newSynthAtHead

Create a synth at the head of the target group (see "Order of Execution")

synthOn :: (VividAction m, VarList params, Subset (InnerVars params) args, IsGroup group) => group -> SynthDef args -> params -> m (Synth args) Source #

Alias for newSynthAtHead

Create a synth at the head of the target group (see "Order of Execution")

newSynthAtTail :: (VividAction m, VarList params, Subset (InnerVars params) args, IsGroup group) => group -> SynthDef args -> params -> m (Synth args) Source #

Create a synth at the tail of the target group (see "Order of Execution")

Create a synth at the head of the target group (see "Order of Execution")

synthTail :: (VividAction m, VarList params, Subset (InnerVars params) args, IsGroup group) => group -> SynthDef args -> params -> m (Synth args) Source #

Alias for newSynthAtTail

Create a synth at the head of the target group (see "Order of Execution")

newGroupBefore :: (IsNode node, VividAction m) => node -> m Group Source #

newGroupAfter :: (IsNode node, VividAction m) => node -> m Group Source #

newGroupAtHead :: (IsGroup group, VividAction m) => group -> m Group Source #

newGroupAtTail :: (IsGroup group, VividAction m) => group -> m Group Source #

set :: (VividAction m, Subset (InnerVars params) sdArgs, VarList params) => Synth sdArgs -> params -> m () Source #

Set the given parameters of a running synth

e.g.

>>> let setTest = sd (0.05 ::I "pan") $ out 0 =<< pan2 (in_ $ 0.1 ~* whiteNoise, pos_ (A::A "pan"))
>>> s <- synth setTest ()
>>> set s (-0.05 ::I "pan")

Any parameters not referred to will be unaffected, and any you specify that don't exist will be (silently) ignored

play :: (VividAction m, MonoOrPoly s) => SDBody' '[] s -> m (Synth '[]) Source #

Given a UGen graph, just start playing it right away.

e.g.

play $ do
   s <- 0.2 ~* lpf (in_ whiteNoise, freq_ 440)
   out 0 [s, s]

The "out" is optional, too -- so you can write

play $ 0.2 ~* lpf (in_ whiteNoise, freq_ 440)

and an "out" will be added, in stereo

free :: VividAction m => Synth a -> m () Source #

Shorter name for freeSynth

freeSynth :: VividAction m => Synth a -> m () Source #

Immediately stop a synth playing

This can create a "clipping" artifact if the sound goes from a high amplitude to 0 in an instant -- you can avoid that with e.g. lag or with an envelope (especially envGate)

release :: (Elem "gate" args, VividAction m) => Synth args -> m () Source #

Assuming your "gate" argument is on an EnvGen or similar, will release the synth over the EnvGen-specified fade time

If you'd like to specify a fade time in the moment, check out releaseIn

releaseIn :: (Elem "gate" args, VividAction m, Real n) => n -> Synth args -> m () Source #

Assumes your "gate" is on an EnvGen or related

Specify a fade time and release

freeBuf :: VividAction m => BufferId -> m () Source #

Synchronous

quitSCServer :: IO () Source #

Stop the SuperCollider server

makeSynth :: (VividAction m, VarList params, IsNode node) => ByteString -> params -> AddAction -> node -> m NodeId Source #