csound-expression-4.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

isaw :: Sig -> Sig

pulse :: Sig -> Sig

sqr :: Sig -> Sig

tri :: Sig -> Sig

blosc :: Tab -> Sig -> Sig

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.

Noise

rndh :: Sig -> SE SigSource

Constant random signal. It updates random numbers with given frequency.

 constRnd freq 

urndh :: Sig -> SE SigSource

Unipolar rndh

rndi :: Sig -> SE SigSource

Linear random signal. It updates random numbers with given frequency.

 rndi freq 

urndi :: Sig -> SE SigSource

Unipolar rndi

white :: SE SigSource

White noise.

pink :: SE SigSource

Pink noise.

Envelopes

leg :: D -> D -> D -> D -> SigSource

Linear adsr envelope generator with release

 leg attack decay sustain release

xeg :: D -> D -> D -> D -> SigSource

Exponential adsr envelope generator with release

 xeg attack decay sustain release

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

Low frequency oscillators

type Lfo = SigSource

Low frequency oscillator

lfo :: (Sig -> Sig) -> Sig -> Sig -> SigSource

Low frequency oscillator

 lfo shape depth rate

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 -> Sig -> SigSource

Low-pass filter.

 lp cutoff resonance sig

hp :: Sig -> Sig -> Sig -> SigSource

High-pass filter.

 hp cutoff resonance sig

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

Band-pass filter.

 bp cutoff resonance sig

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

Band-reject filter.

 br cutoff resonance sig

alp :: Sig -> Sig -> Sig -> SigSource

All-pass filter.

 alp cutoff resonance 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

Specific filters

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

Moog's low-pass filter.

 mlp centerFrequency qResonance signal

Sound files playback

Stereo

readSnd :: String -> (Sig, Sig)Source

Reads stereo signal from the sound-file (wav or mp3 or aiff).

loopSnd :: String -> (Sig, Sig)Source

Reads stereo signal from the sound-file (wav or mp3 or aiff) and loops it with the file length.

loopSndBy :: D -> String -> (Sig, Sig)Source

Reads stereo signal from the sound-file (wav or mp3 or aiff) and loops it with the given period (in seconds).

readWav :: Sig -> String -> (Sig, Sig)Source

Reads the wav file with the given speed (if speed is 1 it's a norma playback). We can use negative speed to read file in reverse.

loopWav :: Sig -> String -> (Sig, Sig)Source

Reads th wav file and loops over it.

readSegWav :: D -> D -> Sig -> String -> (Sig, Sig)Source

Reads a segment from wav file.

tempoLoopWav :: Sig -> String -> (Sig, Sig)Source

Reads th wav file and loops over it. Scales the tempo with first argument.

tempoReadWav :: Sig -> String -> (Sig, Sig)Source

Reads the wav file with the given speed (if speed is 1 it's a norma playback). We can use negative speed to read file in reverse. Scales the tempo with first argument.

Mono

readSnd1 :: String -> SigSource

The mono variant of the function readSnd.

loopSnd1 :: String -> SigSource

The mono variant of the function loopSnd.

loopSndBy1 :: D -> String -> SigSource

The mono variant of the function loopSndBy.

readWav1 :: Sig -> String -> SigSource

The mono variant of the function readWav.

loopWav1 :: Sig -> String -> SigSource

The mono variant of the function loopWav.

readSegWav1 :: D -> D -> Sig -> String -> SigSource

Reads a segment from wav file.

tempoLoopWav1 :: Sig -> String -> SigSource

Reads th mono wav file and loops over it. Scales the tempo with first argument.

tempoReadWav1 :: Sig -> String -> SigSource

Reads the mono wav file with the given speed (if speed is 1 it's a norma playback). We can use negative speed to read file in reverse. Scales the tempo with first argument.

Read sound with RAM

data LoopMode Source

Constructors

Once 
Loop 
Bounce 

ramSnd :: LoopMode -> Sig -> String -> Sig2Source

Loads the sample in the table. The sample should be short. The size of the table is limited. It's up to 6 minutes for

Writing sound files

data SampleFormat Source

The sample format.

Constructors

NoHeaderFloat32

32-bit floating point samples without header

NoHeaderInt16

16-bit integers without header

HeaderInt16

16-bit integers with a header. The header type depends on the render (-o) format

UlawSamples

u-law samples with a header

Int16

16-bit integers with a header

Int32

32-bit integers with a header

Float32

32-bit floats with a header

Uint8

8-bit unsigned integers with a header

Int24

24-bit integers with a header

Float64

64-bit floats with a header

writeSigs :: FormatType -> SampleFormat -> String -> [Sig] -> SE ()Source

Writes a sound signal to the file with the given format. It supports only four formats: Wav, Aiff, Raw and Ircam.

writeWav :: String -> (Sig, Sig) -> SE ()Source

Writes wav files.

writeAiff :: String -> (Sig, Sig) -> SE ()Source

Writes aiff files.

writeWav1 :: String -> Sig -> SE ()Source

Writes mono signals to wav files.

writeAiff1 :: String -> Sig -> SE ()Source

Writes mono signals to aiff files.

Utility

lengthSnd :: String -> DSource

Length in seconds of the sound file.

segments :: D -> Evt (D, Unit)Source

Produces repeating segments with the given time in seconds.

Signal manipulation

takeSnd :: Sigs a => D -> a -> aSource

Takes only given amount (in seconds) from the signal (the rest is silence).

delaySnd :: Sigs a => D -> a -> aSource

Delays signals by the given amount (in seconds).

segmentSnd :: Sigs a => D -> D -> a -> aSource

Delays a signal by the first argument and takes only second argument amount of signal (everything is measured in seconds).

repeatSnd :: Sigs a => D -> a -> aSource

Repeats the signal with the given period.

toMono :: (Sig, Sig) -> SigSource

Converts stereosignal to mono with function mean.

Spectral functions

toSpec :: Sig -> SpecSource

Converts signal to spectrum.

fromSpec :: Spec -> SigSource

Converts spectrum to signal.

mapSpec :: (Spec -> Spec) -> Sig -> SigSource

Applies a transformation to the spectrum of the signal.

scaleSpec :: Sig -> Sig -> SigSource

Scales all frequencies. Usefull for transposition. For example, we can transpose a signal by the given amount of semitones:

 scaleSpec (semitone 1) asig

addSpec :: Sig -> Sig -> SigSource

Adds given amount of Hz to all frequencies.

 addSpec hz asig

scalePitch :: Sig -> Sig -> SigSource

Scales frequency in semitones.

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.

chorusPitch :: Int -> Sig -> (Sig -> Sig) -> Sig -> SigSource

Chorus takes a number of copies, chorus width and wave shape.

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

Reverbs

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

Mono version of the cool reverberation opcode reverbsc.

 reverbsc1 asig feedbackLevel cutOffFreq

rever1 :: Sig -> Sig -> (Sig, Sig)Source

Mono reverb (based on reverbsc)

 rever1 feedback asig

rever2 :: Sig -> Sig2 -> Sig2Source

Mono reverb (based on reverbsc)

 rever2 feedback asigLeft asigRight

reverTime :: Sig -> Sig -> SigSource

Reverb with given time.

smallRoom :: Sig -> (Sig, Sig)Source

Mono reverb for small room.

smallHall :: Sig -> (Sig, Sig)Source

Mono reverb for small hall.

largeHall :: Sig -> (Sig, Sig)Source

Mono reverb for large hall.

magicCave :: Sig -> (Sig, Sig)Source

The magic cave reverb (mono).

smallRoom2 :: Sig2 -> Sig2Source

Stereo reverb for small room.

smallHall2 :: Sig2 -> Sig2Source

Stereo reverb for small hall.

largeHall2 :: Sig2 -> Sig2Source

Stereo reverb for large hall.

magicCave2 :: Sig2 -> Sig2Source

The magic cave reverb (stereo).

Delays

echo :: D -> Sig -> Sig -> SE SigSource

The simplest delay with feedback. Arguments are: delay length and decay ratio.

 echo delayLength ratio

fdelay :: D -> Sig -> Sig -> Sig -> SE SigSource

Delay with feedback.

 fdelay maxDelayLength delayLength decayRatio

fvdelay :: D -> Sig -> Sig -> Sig -> Sig -> SE SigSource

Delay with feedback.

 fdelay maxDelayLength delayLength feedbackLevel decayRatio

fvdelays :: D -> [(Sig, Sig)] -> Sig -> Sig -> SE SigSource

Multitap delay. Arguments are: max delay length, list of pairs (delayLength, decayRatio), balance of mixed signal with processed signal.

 fdelay maxDelayLength  delays balance asig

funDelays :: D -> [(Sig, Sig -> Sig)] -> Sig -> Sig -> SE SigSource

Generic multitap delay. It's just like fvdelays but instead of constant feedbackLevel it expects a function for processing a delayed signal on the tap.

 fdelay maxDelayLength  delays balance asig

Distortion

distortion :: Sig -> Sig -> SigSource

Distortion.

 distort distLevel asig

Chorus

chorus :: Sig -> Sig -> Sig -> Sig -> SE SigSource

Chorus.

 chorus depth rate balance asig

Flanger

flange :: Lfo -> Sig -> Sig -> Sig -> SigSource

Flanger. Lfo depth ranges in 0 to 1.

flanger lfo feedback balance asig

Phase

phase1 :: Sig -> Lfo -> Sig -> Sig -> Sig -> SigSource

First order phaser.

harmPhase :: Sig -> Lfo -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

Second order phaser. Sweeping gaps in the timbre are placed harmonicaly

powerPhase :: Sig -> Lfo -> Sig -> Sig -> Sig -> Sig -> Sig -> SigSource

Second order phaser. Sweeping gaps in the timbre are placed by powers of the base frequency.