Safe Haskell | None |
---|---|
Language | Haskell98 |
Extensions |
|
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 SynthDef
s 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")
- data SynthDef args = SynthDef {}
- data UGen = UGen {}
- addUGen :: UGen -> SDBody' args Signal
- addMonoUGen :: UGen -> SDBody' args Signal
- addPolyUGen :: UGen -> SDBody' args [Signal]
- class ToSig s args where
- data Signal
- encodeSD :: SynthDef a -> ByteString
- sd :: VarList argList => argList -> SDBody' (InnerVars argList) [Signal] -> SynthDef (InnerVars argList)
- sdNamed :: VarList argList => String -> argList -> SDBody' (InnerVars argList) [Signal] -> SynthDef (InnerVars argList)
- sdPretty :: SynthDef a -> String
- (?) :: SDBody' args Signal -> CalculationRate -> SDBody' args Signal
- data DoneAction
- doneActionNum :: DoneAction -> Float
- sdLitPretty :: LiteralSynthDef -> String
- sdToLiteral :: SynthDef a -> LiteralSynthDef
- execState :: State s a -> s -> s
- getCalcRate :: Signal -> SDBody' args CalculationRate
- data UnaryOp
- = Neg
- | Not
- | IsNil
- | NotNil
- | BitNot
- | 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
- uOpToSpecialI :: UnaryOp -> Int16
- specialIToUOp :: Int16 -> UnaryOp
- data BinaryOp
- = Add
- | Sub
- | Mul
- | IDiv
- | FDiv
- | 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
- | Ring2
- | Ring3
- | Ring4
- | DifSqr
- | SumSqr
- | SqrSum
- | SqrDif
- | AbsDif
- | Thresh
- | AMClip
- | ScaleNeg
- | Clip2
- | Excess
- | Fold2
- | Wrap2
- | FirstArg
- | RandRange
- | ExpRandRange
- | NumBinarySelectors
- biOpToSpecialI :: BinaryOp -> Int16
- specialIToBiOp :: Int16 -> BinaryOp
- module Vivid.SynthDef.Types
- getSDHashName :: SynthDef a -> ByteString
- makeSynthDef :: VarList argList => SDName -> argList -> SDBody' (InnerVars argList) [Signal] -> SynthDef (InnerVars argList)
- shrinkSDArgs :: Subset new old => SynthDef old -> SynthDef new
- type SDBody a = SDBody' (SDBodyArgs a)
Synth actions
Synth Definition Construction
Representation of Unit Generators. You usually won't be creating these
by hand, but instead using things from the library in UGens
UGen | |
|
addPolyUGen :: UGen -> SDBody' args [Signal] Source #
Polyphonic -- returns a list of Signal
s.
In the future this might be a tuple instead of a list
class ToSig s args where Source #
Don't define other instances of this! (Unless you know what you're doing) Instance resolution could get screwed up.
encodeSD :: SynthDef a -> ByteString 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
doneActionNum :: DoneAction -> Float Source #
sdLitPretty :: LiteralSynthDef -> String Source #
sdToLiteral :: SynthDef a -> LiteralSynthDef Source #
:: State s a | state-passing computation to execute |
-> s | initial value |
-> s | final state |
getCalcRate :: Signal -> SDBody' args CalculationRate Source #
Built-in Unit Generator Operations
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.
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 |
uOpToSpecialI :: UnaryOp -> Int16 Source #
specialIToUOp :: Int16 -> UnaryOp Source #
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.
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 |
biOpToSpecialI :: BinaryOp -> Int16 Source #
specialIToBiOp :: Int16 -> BinaryOp Source #
module Vivid.SynthDef.Types
getSDHashName :: SynthDef a -> ByteString Source #
makeSynthDef :: VarList argList => SDName -> argList -> SDBody' (InnerVars argList) [Signal] -> SynthDef (InnerVars argList) Source #
shrinkSDArgs :: Subset new old => SynthDef old -> SynthDef new Source #
Like shrinkNodeArgs
but for SynthDef
s
type SDBody a = SDBody' (SDBodyArgs a) Source #