vivid-0.4.2.3: Sound synthesis with SuperCollider

Safe HaskellNone
LanguageHaskell98
Extensions
  • BangPatterns
  • TypeFamilies
  • OverloadedStrings
  • ViewPatterns
  • DataKinds
  • KindSignatures
  • ExplicitNamespaces
  • LambdaCase

Vivid.SynthDef

Contents

Description

Synth Definitions in SuperCollider are how you define the way synths should sound -- you describe parameters and a graph of sound generators, add them to the server with defineSD, and then create instances of the Synth Definition (called "synths"), which each play separately. You can set parameters of the synth at any time while they're playing

Usually, you shouldn't be making SynthDefs explicitly -- there's a state monad SDBody which lets you construct synthdefs like so:

  test :: SynthDef
  test = sd (0 ::I "note") $ do
     s <- 0.1 ~* sinOsc (freq_ $ midiCPS (V::V "note"))
     out 0 [s, s]
  

You then optionally explicitly send the synth definition to the SC server with

>>> defineSD test

You then create a synth from the synthdef like:

>>> s <- synth test (45 ::I "note")

This returns a NodeId which is a reference to the synth, which you can use to e.g. change the params of the running synth with e.g.

>>> set s (38 ::I "note")

Then you can free it (stop its playing) with

>>> free s

(If you want interop with SClang, use "sdNamed" and "synthNamed")

Synopsis

Synth actions

Synth Definition Construction

data SynthDef (args :: [Symbol]) Source #

Internal representation of Synth Definitions. Usually, use sd instead of making these by hand.

This representation (especially _sdUGens) might change in the future.

Constructors

SynthDef 
Instances
Show (SynthDef args) Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

showsPrec :: Int -> SynthDef args -> ShowS #

show :: SynthDef args -> String #

showList :: [SynthDef args] -> ShowS #

Hashable (SynthDef a) Source #

This is the hash of the UGen graph and params, but not the name! So (re)naming a SynthDef will not change its hash.

Instance details

Defined in Vivid.SynthDef

Methods

hashWithSalt :: Int -> SynthDef a -> Int #

hash :: SynthDef a -> Int #

a ~ args => ToSig (SDBody' a Signal) args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: SDBody' a Signal -> SDBody' args Signal Source #

data UGen Source #

Representation of Unit Generators. You usually won't be creating these by hand, but instead using things from the library in UGens

Instances
Eq UGen Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

(==) :: UGen -> UGen -> Bool #

(/=) :: UGen -> UGen -> Bool #

Show UGen Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

showsPrec :: Int -> UGen -> ShowS #

show :: UGen -> String #

showList :: [UGen] -> ShowS #

addMonoUGen :: UGen -> SDBody' args Signal Source #

Add a unit generator with one output

addPolyUGen :: UGen -> SDBody' args [Signal] Source #

Polyphonic -- returns a list of Signals. In the future this might be a tuple instead of a list

class ToSig s (args :: [Symbol]) where Source #

Methods

toSig :: s -> SDBody' args Signal Source #

Instances
ToSig Double args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: Double -> SDBody' args Signal Source #

ToSig Float args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: Float -> SDBody' args Signal Source #

ToSig Int args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: Int -> SDBody' args Signal Source #

ToSig Integer args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: Integer -> SDBody' args Signal Source #

ToSig BufferId args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: BufferId -> SDBody' args Signal Source #

ToSig Signal args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: Signal -> SDBody' args Signal Source #

(KnownSymbol a, Subset (a ': ([] :: [Symbol])) args) => ToSig (Variable a) args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: Variable a -> SDBody' args Signal Source #

a ~ args => ToSig (SDBody' a Signal) args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: SDBody' a Signal -> SDBody' args Signal Source #

data Signal Source #

Instances
Eq Signal Source # 
Instance details

Defined in Vivid.SynthDef.Types

Methods

(==) :: Signal -> Signal -> Bool #

(/=) :: Signal -> Signal -> Bool #

Show Signal Source # 
Instance details

Defined in Vivid.SynthDef.Types

ToSig Signal args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: Signal -> SDBody' args Signal Source #

a ~ args => ToSig (SDBody' a Signal) args Source # 
Instance details

Defined in Vivid.SynthDef.ToSig

Methods

toSig :: SDBody' a Signal -> SDBody' args Signal Source #

sd :: VarList argList => argList -> SDBody' (InnerVars argList) [Signal] -> SynthDef (InnerVars argList) Source #

Define a Synth Definition

sdNamed :: VarList argList => String -> argList -> SDBody' (InnerVars argList) [Signal] -> SynthDef (InnerVars argList) Source #

Define a Synth Definition and give it a name you can refer to from e.g. sclang

(?) :: SDBody' args Signal -> CalculationRate -> SDBody' args Signal Source #

Set the calculation rate of a UGen

e.g.

play $ do
   s0 <- 1 ~+ (lfSaw (freq_ 1) ? KR)
   s1 <- 0.1 ~* lfSaw (freq_ $ 220 ~* s0)
   out 0 [s1, s1]

Mnemonic: "?" is like thinking

In the future, the representation of calculation rates may change

data DoneAction Source #

Action to take with a UGen when it's finished

This representation will change in the future

Instances
Eq DoneAction Source # 
Instance details

Defined in Vivid.SynthDef

Show DoneAction Source # 
Instance details

Defined in Vivid.SynthDef

execState #

Arguments

:: State s a

state-passing computation to execute

-> s

initial value

-> s

final state

Evaluate a state computation with the given initial state and return the final state, discarding the final value.

Built-in Unit Generator Operations

data UnaryOp #

Unary signal operations. Many of these have functions so you don't need to use this internal representation (e.g. Neg has neg, etc).

This type might not be exposed in the future.

Constructors

Neg 
Not 
IsNil 
NotNil 
BitNot

There's a bug in some SC versions where .bitNot isn't implemented correctly. Vivid backfills it with a fix, so you can use BitNot with any SC version

Abs 
AsFloat 
AsInt 
Ciel 
Floor 
Frac 
Sign 
Squared 
Cubed 
Sqrt 
Exp 
Recip 
MIDICPS 
CPSMIDI 
MIDIRatio 
RatioMIDI 
DbAmp 
AmpDb 
OctCPS 
CPSOct 
Log 
Log2 
Log10 
Sin 
Cos 
Tan 
ArcSin 
ArcCos 
ArcTan 
SinH 
CosH 
TanH 
Rand 
Rand2 
LinRand 
BiLinRand 
Sum3Rand 
Distort 
SoftClip 
Coin 
DigitValue 
Silence 
Thru 
RectWindow 
HanWindow 
WelchWindow 
TriWindow 
Ramp 
SCurve 
NumUnarySelectors 

data BinaryOp #

Binary signal operations. For the simple ones (like Add, Mul, etc.), there are functions (like ~+, ~*, etc.) that wrap them up so you don't have to make a ugen for them yourself.

In the future these may not be exported -- we'll just have functions for all of them.

Constructors

Add 
Sub 
Mul 
IDiv

Integer division

FDiv

Float division

Mod 
Eq 
Ne 
Lt 
Gt 
Le 
Ge 
Min 
Max 
BitAnd 
BitOr 
BitXor 
Lcm 
Gcd 
Round 
RoundUp 
Trunc 
Atan2 
Hypot 
Hypotx 
Pow 
ShiftLeft 
ShiftRight 
UnsignedShift 
Fill 
Ring1

a * (b + 1) == a * b + a

Ring2

a * b + a + b

Ring3

a * a * b

Ring4

a * a * b - a * b * b

DifSqr

a * a - b * b

SumSqr

a * a + b * b

SqrSum

(a + b) ^ 2

SqrDif

(a - b) ^ 2

AbsDif

abs(a - b)

Thresh 
AMClip 
ScaleNeg 
Clip2 
Excess 
Fold2 
Wrap2 
FirstArg 
RandRange 
ExpRandRange 
NumBinarySelectors 

makeSynthDef :: VarList argList => SDName -> argList -> SDBody' (InnerVars argList) [Signal] -> SynthDef (InnerVars argList) Source #

shrinkSDArgs :: Subset new old => SynthDef old -> SynthDef new Source #

Orphan instances

Hashable (SynthDef a) Source #

This is the hash of the UGen graph and params, but not the name! So (re)naming a SynthDef will not change its hash.

Instance details

Methods

hashWithSalt :: Int -> SynthDef a -> Int #

hash :: SynthDef a -> Int #