csound-expression-3.1.0: library to make electronic music

Safe HaskellNone

Csound.Air

Contents

Synopsis

Basic waveforms

Basic waveforms that are used most often. A waveform function take in a time varied frequency (in Hz).

Bipolar

osc :: Sig -> SigSource

A pure tone (sine wave).

oscBy :: Tab -> Sig -> SigSource

An oscillator with user provided waveform.

saw :: Sig -> Sig

A sawtooth.

isaw :: Sig -> Sig

Integrated sawtooth: 4 * x * (1 - x).

pulse :: Sig -> Sig

Pulse (not normalized).

sqr :: Sig -> Sig

A square wave.

tri :: Sig -> Sig

A triangle wave.

blosc :: Tab -> Sig -> Sig

A band-limited oscillator with user defined waveform (it's stored in the table).

Unipolar

unipolar :: Sig -> SigSource

Turns a bipolar sound (ranges from -1 to 1) to unipolar (ranges from 0 to 1)

bipolar :: Sig -> SigSource

Turns an unipolar sound (ranges from 0 to 1) to bipolar (ranges from -1 to 1)

on :: Sig -> Sig -> Sig -> SigSource

Rescaling of the bipolar signal (-1, 1) -> (a, b)

 on a b biSig

uon :: Sig -> Sig -> Sig -> SigSource

Rescaling of the unipolar signal (0, 1) -> (a, b)

 on a b uniSig

uosc :: Sig -> SigSource

Unipolar pure tone.

uoscBy :: Tab -> Sig -> SigSource

Unipolar oscBy.

usaw :: Sig -> SigSource

Unipolar sawtooth.

uisaw :: Sig -> SigSource

Unipolar integrated sawtooth.

upulse :: Sig -> SigSource

Unipolar pulse.

usqr :: Sig -> SigSource

Unipolar square wave.

utri :: Sig -> SigSource

Unipolar triangle wave.

ublosc :: Tab -> Sig -> SigSource

Unipolar band-limited oscillator.

Envelopes

Relative duration

onIdur :: [D] -> [D]Source

Makes time intervals relative to the note's duration. So that:

 onIdur [a, t1, b, t2, c]

becomes:

 [a, t1 * idur, b, t2 * idur, c]

lindur :: [D] -> SigSource

The opcode linseg with time intervals relative to the total duration of the note.

expdur :: [D] -> SigSource

The opcode expseg with time intervals relative to the total duration of the note.

linendur :: Sig -> D -> D -> SigSource

The opcode linen with time intervals relative to the total duration of the note. Total time is set to the value of idur.

 linendur asig rise decay

onDur :: D -> [D] -> [D]Source

Makes time intervals relative to the note's duration. So that:

 onDur dt [a, t1, b, t2, c]

becomes:

 [a, t1 * dt, b, t2 * dt, c]

lindurBy :: D -> [D] -> SigSource

The opcode linseg with time intervals relative to the total duration of the note given by the user.

expdurBy :: D -> [D] -> SigSource

The opcode expseg with time intervals relative to the total duration of the note given by the user.

linendurBy :: D -> Sig -> D -> D -> SigSource

The opcode linen with time intervals relative to the total duration of the note. Total time is set to the value of the first argument.

 linendurBy dt asig rise decay

once :: Tab -> SigSource

Reads table once during the note length.

onceBy :: D -> Tab -> SigSource

Reads table once during a given period of time.

several :: Tab -> Sig -> SigSource

Reads table several times during the note length.

Looping envelopes

oscLins :: [D] -> Sig -> SigSource

Loops over line segments with the given rate.

 oscLins [a, durA, b, durB, c, durC ..] cps

where

  • a, b, c ... -- values
  • durA, durB, durC -- durations of the segments relative to the current frequency.

oscElins :: [D] -> Sig -> SigSource

Loops over equally spaced line segments with the given rate.

 oscElins [a, b, c] === oscLins [a, 1, b, 1, c]

oscExps :: [D] -> Sig -> SigSource

Loops over exponential segments with the given rate.

 oscLins [a, durA, typeA, b, durB, typeB, c, durC, typeC ..] cps

where

  • a, b, c ... -- values
  • durA, durB, durC -- durations of the segments relative to the current frequency.
  • typeA, typeB, typeC, ... -- shape of the envelope. If the value is 0 then the shap eis linear; otherwise it is an concave exponential (positive type) or a convex exponential (negative type).

oscEexps :: [D] -> Sig -> SigSource

Loops over equally spaced exponential segments with the given rate.

 oscLins [a, typeA, b, typeB, c, typeC ..] === oscLins [a, 1, typeA, b, 1, typeB, c, 1, typeC ..]

oscLine :: D -> D -> Sig -> SigSource

 oscLine a b cps

Goes from a to b and back by line segments. One period is equal to 2/cps so that one period is passed by 1/cps seconds.

Faders

fadeIn :: D -> SigSource

Fades in with the given attack time.

fadeOut :: D -> SigSource

Fades out with the given attack time.

fades :: D -> D -> SigSource

A combination of fade in and fade out.

 fades attackDuration decayDuration

expFadeIn :: D -> SigSource

Fades in by exponent with the given attack time.

expFadeOut :: D -> SigSource

Fades out by exponent with the given attack time.

expFades :: D -> D -> SigSource

A combination of exponential fade in and fade out.

 expFades attackDuration decayDuration

Filters

Arguemnts are inversed to get most out of curruing. First come parameters and the last one is the signal.

Simple filters

lp :: Sig -> Sig -> SigSource

Low-pass filter.

 lp cutoff sig

hp :: Sig -> Sig -> SigSource

High-pass filter.

 hp cutoff sig

bp :: Sig -> Sig -> Sig -> SigSource

Band-pass filter.

 bp cutoff bandwidth sig

br :: Sig -> Sig -> Sig -> SigSource

Band-regect filter.

 br cutoff bandwidth sig

Butterworth filters

blp :: Sig -> Sig -> SigSource

Low-pass filter.

 blp cutoff sig

bhp :: Sig -> Sig -> SigSource

High-pass filter.

 bhp cutoff sig

bbp :: Sig -> Sig -> Sig -> SigSource

Band-pass filter.

 bbp cutoff bandwidth sig

bbr :: Sig -> Sig -> Sig -> SigSource

Band-regect filter.

 bbr cutoff bandwidth sig

Balanced filters

Applies filter and balances the output by the input signal.

lpb :: Sig -> Sig -> SigSource

Balanced low-pass filter.

hpb :: Sig -> Sig -> SigSource

Balanced high-pass filter.

bpb :: Sig -> Sig -> Sig -> SigSource

Balanced band-pass filter.

brb :: Sig -> Sig -> Sig -> SigSource

Balanced band-reject filter.

blpb :: Sig -> Sig -> SigSource

Balanced butterworth low-pass filter.

bhpb :: Sig -> Sig -> SigSource

Balanced butterworth high-pass filter.

bbpb :: Sig -> Sig -> Sig -> SigSource

Balanced butterworth band-pass filter.

bbrb :: Sig -> Sig -> Sig -> SigSource

Balanced butterworth band-reject filter.

Specific filters

mlp :: Sig -> Sig -> Sig -> SigSource

Moog's low-pass filter.

 mlp centerFrequency qResonance signal

Patterns

mean :: Fractional a => [a] -> aSource

Mean value.

vibrate :: Sig -> Sig -> (Sig -> a) -> Sig -> aSource

Adds vibrato to the sound unit. Sound units is a function that takes in a frequency.

randomPitch :: Sig -> Sig -> (Sig -> a) -> Sig -> SE aSource

Adds a random vibrato to the sound unit. Sound units is a function that takes in a frequency.

chorus :: Fractional a => [Sig] -> (Sig -> a) -> Sig -> aSource

Chorus takes a list of displacments from the base frequencies and a sound unit. Output is mean of signals with displacments that is applied to the base frequency.

resons :: [(Sig, Sig)] -> Sig -> SigSource

Applies a resonator to the signals. A resonator is a list of band pass filters. A list contains the parameters for the filters:

 [(centerFrequency, bandWidth)]

resonsBy :: (cps -> bw -> Sig -> Sig) -> [(cps, bw)] -> Sig -> SigSource

A resonator with user defined band pass filter. Warning: a filter takes in a center frequency, band width and the signal. The signal comes last (this order is not standard in the Csound but it's more convinient to use with Haskell).

modes :: [(Sig, Sig)] -> Sig -> Sig -> SigSource

Chain of mass-spring-damping filters.

 modes params baseCps exciter 
  • params - a list of pairs (resonantFrequencyRatio, filterQuality)
  • baseCps - base frequency of the resonator
  • exciter - an impulse that starts a resonator.

dryWet :: Sig -> (Sig -> Sig) -> Sig -> SigSource

Mixes dry and wet signals.

 dryWet ratio effect asig
  • ratio - of dry signal to wet
  • effect - means to wet the signal
  • asig -- processed signal

List functions

odds :: [a] -> [a]Source

Selects odd elements from the list.

evens :: [a] -> [a]Source

Selects even elements from the list.

Widgets

data AdsrBound Source

Constructors

AdsrBound 

data AdsrInit Source

Constructors

AdsrInit 

classicWaves :: String -> Int -> Source (Sig -> Sig)Source

A widget with four standard waveforms: pure tone, triangle, square and sawtooth. The last parameter is a default waveform (it's set at init time).

masterVolume :: Source SigSource

Slider for master volume

masterVolumeKnob :: Source SigSource

Knob for master volume

Other

reverbsc1 :: Sig -> Sig -> Sig -> SigSource

Mono version of the cool reverberation opcode reverbsc.

 reverbsc1 asig feedbackLevel cutOffFreq