vivid-0.1.0.0: Sound synthesis with SuperCollider

Safe HaskellNone
LanguageHaskell98
Extensions
  • OverloadedStrings
  • ExistentialQuantification
  • ExplicitForAll

Vivid.UGens

Contents

Description

Unit Generators, which are the signal-generating/processing components of synths.

Most of your time reading documentation will probably be in this module

Most of these take named arguments with types like In, Freq, etc. This just means you construct them with the same data constructor. The data constructor is the same as its type (In and In, etc.). So e.g. to make a lowpass filter which filters whitenoise at 440hz, you'd write:

lpf (In whiteNoise) (Freq 440)

This is far from all the ones in SC, so I've exposed the internals so you can make your own when you want. Some exports may disappear in future versions.

Synopsis

Generators

Generate signals, which can then be processed

Audio or control rate

These can be used as direct sound sources or as control parameters

lfTri :: Freq -> SDState Signal Source

"A non-band-limited triangle oscillator. Output ranges from -1 to +1."

lfSaw :: Freq -> SDState Signal Source

"A non-band-limited sawtooth oscillator. Output ranges from -1 to +1."

whiteNoise :: SDState Signal Source

"Generates noise whose spectrum has equal power at all frequencies."

pinkNoise :: SDState Signal Source

"Generates noise whose spectrum falls off in power by 3 dB per octave. This gives equal power over the span of each octave. This version gives 8 octaves of pink noise."

brownNoise :: SDState Signal Source

"Generates noise whose spectrum falls off in power by 6 dB per octave."

Control rate

These wouldn't be useful as direct sound sources, but instead as parameters to other UGens

xLine :: Start -> End -> Dur -> DoneAction -> SDState Signal Source

"Generates an exponential curve from the start value to the end value. Both the start and end values must be non-zero and have the same sign."

Defaults to KR

line :: Start -> End -> Dur -> DoneAction -> SDState Signal Source

"Generates a line from the start value to the end value."

Defaults to KR

User input

Generators which get signals from user input

Audio rate

soundIn0 :: SDState Signal Source

Bus input (usually mic). "0" because it's from the 0th bus

Control rate

Filters

Filter signals

bpf :: In -> Freq -> Rq -> SDState Signal Source

Band-pass filter

lpf :: In -> Freq -> SDState Signal Source

Low-pass filter

hpf :: In -> Freq -> SDState Signal Source

High-pass filter

clip :: In -> Hi -> SDState Signal Source

Unlike in SuperCollider, you don't specify a "lo" parameter -- "lo" is always negative "hi"

Buffers

playBuf1 :: Buf -> SDState Signal Source

Play a 1-channel buffer

recordBuf1 :: In -> Buf -> SDState Signal Source

Record a 1-channel buffer

FFT

Stuff for Fast Fourier Transforms. Very incomplete atm.

localBuf :: NumFrames -> NumChans -> SDState Signal Source

Add a single LocalBuf for FFT

Signal math

Add, multiply, etc.

Operators

Mnemonic: the ~ looks like a sound wave

(~*) :: (ToSigM sig0, ToSigM sig1) => sig0 -> sig1 -> SDState Signal Source

(~+) :: (ToSigM i0, ToSigM i1) => i0 -> i1 -> SDState Signal Source

(~/) :: (ToSigM i0, ToSigM i1) => i0 -> i1 -> SDState Signal Source

(~-) :: (ToSigM i0, ToSigM i1) => i0 -> i1 -> SDState Signal Source

(~>) :: (ToSigM i0, ToSigM i1) => i0 -> i1 -> SDState Signal Source

Functions

midiCPS :: ToSigM i => i -> SDState Signal Source

Convert from a midi note number (0-127, each representing a musical half step) to a frequency in hz (cycles per second)

abs' :: ToSigM i => i -> SDState Signal Source

The prime is to not conflict with "abs" in the prelude. May just use "uOp Abs" in the future

binaryOp :: (ToSigM s0, ToSigM s1) => BinaryOp -> s0 -> s1 -> SDState Signal Source

Build your own!

biOp :: (ToSigM s0, ToSigM s1) => BinaryOp -> s0 -> s1 -> SDState Signal Source

Alias of binaryOp. Shorter, fer livecodin

unaryOp :: ToSigM sig => UnaryOp -> sig -> SDState Signal Source

Build your own, from UnaryOps

uOp :: ToSigM sig => UnaryOp -> sig -> SDState Signal Source

Alias of unaryOp

Uncategorized

Haven't organized yet

pan2 :: In -> Pos -> SDState [Signal] Source

pos is -1 to 1

out :: ToSigM i => Float -> [i] -> SDState [Signal] Source

mix :: ToSigM s => [s] -> SDState Signal Source

Mixes down a list of audio rate inputs to one. The list can't be empty.

This is more efficient than e.g. foldl1 (~*)

lag :: In -> Secs -> SDState Signal Source

The "Secs" arg is the same as the "lagTime" arg in SC