csound-expression-5.2.2: library to make electronic music

Safe HaskellNone
LanguageHaskell98

Csound.Air.Fx

Contents

Description

Effects

Synopsis

Reverbs

reverbsc1 :: Sig -> Feedback -> ToneSig -> Sig Source #

Mono version of the cool reverberation opcode reverbsc.

reverbsc1 asig feedbackLevel cutOffFreq

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

Mono reverb (based on reverbsc)

rever1 feedback asig

rever2 :: Feedback -> Sig2 -> Sig2 Source #

Mono reverb (based on reverbsc)

rever2 feedback (asigLeft, asigRight)

reverTime :: DelayTime -> Sig -> Sig Source #

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 -> Sig2 Source #

Stereo reverb for small room.

smallHall2 :: Sig2 -> Sig2 Source #

Stereo reverb for small hall.

largeHall2 :: Sig2 -> Sig2 Source #

Stereo reverb for large hall.

magicCave2 :: Sig2 -> Sig2 Source #

The magic cave reverb (stereo).

room :: MixAt Sig2 Sig2 a => Sig -> a -> AtOut Sig2 Sig2 a Source #

An alias for

let room dryWet asig = mixAt dryWet smallRoom2 asig

chamber :: MixAt Sig2 Sig2 a => Sig -> a -> AtOut Sig2 Sig2 a Source #

An alias for

let room dryWet asig = mixAt dryWet smallHall2 asig

hall :: MixAt Sig2 Sig2 a => Sig -> a -> AtOut Sig2 Sig2 a Source #

An alias for

let room dryWet asig = mixAt dryWet largeHall2 asig

cave :: MixAt Sig2 Sig2 a => Sig -> a -> AtOut Sig2 Sig2 a Source #

An alias for

let room dryWet asig = mixAt dryWet magicCave2 asig

Impulse Responce convolution reverbs

Be careful with volumes. Some IRs can require scaling with really small coefficients like 0.01.

monoIR :: FilePath -> Sig -> Sig Source #

Fast zero delay convolution with impulse response that is contained in mono-audio file.

monoIR irFile ain

stereoIR :: FilePath -> Sig2 -> Sig2 Source #

Fast zero delay convolution with impulse response that is contained in stereo-audio file.

stereoIR irFile ain

stereoIR2 :: (FilePath, FilePath) -> Sig2 -> Sig2 Source #

If IR is encoded in a couple of mono files.

pmonoIR :: FilePath -> Sig -> Sig Source #

Precise mono IR with pconvolve (requires a lot of CPU).

pstereoIR :: FilePath -> Sig2 -> Sig2 Source #

Precise stereo IR with pconvolve (requires a lot of CPU).

monoIR' :: ZConvSpec -> FilePath -> Sig -> Sig Source #

Fast zero delay convolution with impulse response that is contained in mono-audio file. We can specify aux parameters for convolution algorithm (see zconv').

monoIR' spec irFile ain

stereoIR' :: ZConvSpec -> FilePath -> Sig2 -> Sig2 Source #

Fast zero delay convolution with impulse response that is contained in stereo-audio file. We can specify aux parameters for convolution algorithm (see zconv').

stereoIR' spec irFile ain

stereoIR2' :: ZConvSpec -> (FilePath, FilePath) -> Sig2 -> Sig2 Source #

If IR is encoded in a couple of mono files.

data ZConvSpec :: * #

Zero convolution specification

Constructors

ZConvSpec 

Fields

Instances

zconv :: Tab -> Sig -> Sig #

Zero delay convolution with default parameters.

zconv tabIR  ain = ...

zconv' :: ZConvSpec -> Tab -> Sig -> Sig #

zero delay convolution.

zconv' (ZConvSpec ipart irat inp) ifn ain

Original UDO code by Victor Lazzarini.

/************************************************** asig ZConv ain,ipart,irat,inp,ifn ain - input signal ipart - first partition size in samples irat - partition growth ratio inp - total number of partition sizes ifn - function table number containing the IR **************************************************/

Delays

type MaxDelayTime = D Source #

The maximum delay time.

type DelayTime = Sig Source #

The delaya time

type Feedback = Sig Source #

Feedback for delay

type Balance = Sig Source #

Dry/Wet mix value (ranges from 0 to 1). The 0 is all dry. The 1 is all wet.

echo :: MaxDelayTime -> Feedback -> Sig -> Sig Source #

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

echo delayLength ratio

fvdelay :: MaxDelayTime -> DelayTime -> Feedback -> Sig -> Sig Source #

Delay with feedback.

fdelay maxDelayLength delayLength feedback balance

fvdelays :: MaxDelayTime -> [(DelayTime, Feedback)] -> Balance -> Sig -> SE Sig Source #

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 :: MaxDelayTime -> [(DelayTime, Sig -> Sig)] -> Balance -> Sig -> SE Sig Source #

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

tabDelay :: (Tab -> Sig -> SE Sig) -> MaxDelayTime -> DelayTime -> Feedback -> Balance -> Sig -> SE Sig Source #

Delay for functions that use some table (as a buffer). As granular synth or mincer.

tabDelay fn maxDelayTime delayTime feedback balance asig

data PingPongSpec Source #

Aux parameters for ping pong delay. They are maximum delay time, low pass filter center frequency and Pan width. The defaults are (5 sec, 3500, 0.3).

pingPong :: DelayTime -> Feedback -> Balance -> Sig2 -> Sig2 Source #

Ping-pong delay.

pingPong delayTime feedback mixLevel

pingPong' :: PingPongSpec -> DelayTime -> Feedback -> Balance -> Sig2 -> Sig2 Source #

Ping-pong delay with miscellaneous arguments.

pingPong' spec delayTime feedback mixLevel

csdPingPong :: MaxDelayTime -> DelayTime -> Sig -> Feedback -> Sig -> Balance -> Sig2 -> Sig2 Source #

Ping-pong delay defined in csound style. All arguments are present (nothing is hidden).

csdPingPong maxTime delTime damp feedback width mixLevel (ainL, ainR)

Distortion

distortion :: Sig -> Sig -> Sig Source #

Distortion.

distort distLevel asig

Chorus

chorus :: DepthSig -> RateSig -> Balance -> Sig -> SE Sig Source #

Chorus.

chorus depth rate balance asig

Flanger

flange :: Lfo -> Feedback -> Balance -> Sig -> Sig Source #

Flanger. Lfo depth ranges in 0 to 1.

flanger lfo feedback balance asig

Phase

phase1 :: Sig -> Lfo -> Feedback -> Balance -> Sig -> Sig Source #

First order phaser.

harmPhase :: Sig -> Lfo -> Sig -> Sig -> Feedback -> Balance -> Sig -> Sig Source #

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

powerPhase :: Sig -> Lfo -> Sig -> Sig -> Feedback -> Balance -> Sig -> Sig Source #

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

Effects with unit parameters

Implemented by Iain McCurdy's Csound code.

type FftSize = D Source #

fxDistort :: Feedback -> Sig -> ToneSig -> Sig -> Sig Source #

Distortion

fxDistort level drive tone sigIn

stChorus2 :: Balance -> RateSig -> DepthSig -> WidthSig -> Sig2 -> Sig2 Source #

Stereo chorus.

stChorus2 mix rate depth width sigIn

fxPhaser :: RateSig -> DepthSig -> BaseCps -> Feedback -> Sig -> Sig Source #

Phaser

An phase shifting effect that mimics the design of a so called 'stomp box'

fxPhaser rate depth freq fback ain

Arguments:

  • rate -- rate of lfo of the effect (range 0 to 1)
  • depth -- depth of lfo of the effect (range 0 to 1)
  • freq -- centre frequency of the phase shifting effect in octaves (suggested range 6 to 11)
  • fback -- feedback and therefore intensity of the effect (range 0 to 1)
  • ain -- input audio to be pitch shifted

fxFlanger :: RateSig -> DepthSig -> DelayTime -> Feedback -> Sig -> Sig Source #

A flanger effect following the typical design of a so called 'stomp box'

 fxFlanger rate depth delayTime feedback ain = 

Arguments

  • rate -- rate control of the lfo of the effect *NOT IN HERTZ* (range 0 to 1)
  • depth -- depth of the lfo of the effect (range 0 to 1)
  • delayTime -- static delay offset of the flanging effect (range 0 to 1)
  • feedback -- feedback and therefore intensity of the effect (range 0 to 1)
  • ain -- input audio to which the flanging effect will be applied

analogDelay :: Balance -> Feedback -> DelayTime -> ToneSig -> Sig -> Sig Source #

Analog delay.

analogDelay mix feedback time tone sigIn

fxEcho :: D -> Sig -> Sig -> Sig -> Sig Source #

Simplified delay

fxEcho maxDelayLength delTime feedback sigIn

fxFilter :: Sig -> Sig -> Sig -> Sig -> Sig Source #

Filter effect (a pair of butterworth low and high pass filters).

fxFilter lowPassfFreq highPassFreq gain 

fxWhite :: Sig -> Sig -> Sig -> SE Sig Source #

Adds filtered white noize to the signal

fxWhite lfoFreq depth sigIn

fxPink :: Sig -> Sig -> Sig -> SE Sig Source #

Adds filtered pink noize to the signal

fxWhite lfoFreq depth sigIn

equalizer :: [(Sig, Sig)] -> Sig -> Sig -> Sig Source #

Equalizer

equalizer gainsAndFrequencies gain sigIn

eq4 :: [Sig] -> Sig -> Sig -> Sig Source #

Equalizer with frequencies: 100, 400, 1600, 6400

eq7 :: [Sig] -> Sig -> Sig -> Sig Source #

Equalizer with frequencies: 100, 200, 400, 800, 1600, 3200, 6400

fxGain :: SigSpace a => Sig -> a -> a Source #

Gain

fxGain gain sigIn

fxAnalogDelay :: Balance -> DelayTime -> Feedback -> ToneSig -> Sig -> Sig Source #

Delay line with low-pass filter in the feedback chain. The filter adds natural decay to the echoes.

fxAnalogDelay mixRatio delayTime feedback toneRatio ain

Note that the center frequency of the filter is measured in normalized units (form 0 to 1).

fxDistortion :: DriveSig -> ToneSig -> Sig -> Sig Source #

Distortion unit with low-pass filter.

fxDistortion driveLevel toneRatio ain

Note that the center frequency of the filter is measured in normalized units (form 0 to 1).

fxFollower :: SensitivitySig -> BaseCps -> Resonance -> Sig -> Sig Source #

Envelope follower.

fxFollower sensitivity baseFrequencyRatio resonance ain

Arguments:

  • sensitivity -- sensitivity of the envelope follower (suggested range: 0 to 1)
  • baseFrequencyRatio -- base frequency of the filter before modulation by the input dynamics (range: 0 to 1)

; resonance -- resonance of the lowpass filter (suggested range: 0 to 1)

fxReverse :: TimeSig -> Sig -> Sig Source #

An effect that reverses an audio stream in chunks

fxReverse time

time -- the size of the chunck in seconds.

fxLoFi :: BitsReductionSig -> FoldoverSig -> Sig -> Sig Source #

LoFi

'Low Fidelity' distorting effects of bit reduction and downsampling (foldover)

fxLoFi  bits fold ain = ...

Arguments

  • bits -- bit depth reduction (range 0 to 1)
  • fold -- amount of foldover (range 0 to 1)
  • ain -- input audio to have low fidelity distortion effects applied

fxChorus2 :: RateSig -> DepthSig -> WidthSig -> Sig2 -> Sig2 Source #

Stereo Chorus

A stereo chorus effect

fxChorus2 rate depth width (ainLeft, ainRight)

Arguments

  • rate -- rate control of the lfo of the effect *NOT IN HERTZ* (range 0 to 1)
  • depth -- depth of the lfo of the effect (range 0 to 1)
  • width -- width of stereo widening (range 0 to 1)
  • ainX -- input stereo signal

fxAutoPan :: TremWaveSig -> DepthSig -> RateSig -> Sig2 -> Sig2 Source #

Auto pan

fxAutoPan wave rate depth ain

; Arguments:

  • wave -- waveform used by the lfo (0=sine 1=triangle 2=square)
  • rate -- rate control of the lfo of the effect *NOT IN HERTZ* (range 0 to 1)
  • depth -- depth of the lfo of the effect (range 0 to 1)
  • mode -- mode of the effect (0=auto-panning 1=tremolo)
  • ain -- input stereo audio

fxTrem :: TremWaveSig -> DepthSig -> RateSig -> Sig2 -> Sig2 Source #

Tremolo

tremolo effect

fxTrem wave rate depth ain

; Arguments:

  • wave -- waveform used by the lfo (0=sine 1=triangle 2=square)
  • rate -- rate control of the lfo of the effect *NOT IN HERTZ* (range 0 to 1)
  • depth -- depth of the lfo of the effect (range 0 to 1)
  • mode -- mode of the effect (0=auto-panning 1=tremolo)
  • ain -- input stereo audio

fxPitchShifter :: FftSize -> Balance -> RatioSig -> Feedback -> Sig -> Sig Source #

PitchShifter

A pitch shifter effect based on FFT technology

fxPitchShifter  fftSize mixRatio transposeRatio feedback ain

Arguments

  • fftSize -- size for FFT analysis (good values 1024, 512, 256, 2048), the higher values introduce latency but lower values are less accurate.
  • mix -- dry / wet mix of the output signal (range 0 to 1)
  • transpose -- pitch ratio
  • feedback -- control of the amount of output signal fed back into the input of the effect (suggested range 0 to 1)
  • ain -- input audio to be pitch shifted

fxFreqShifter :: Balance -> Sig -> Sig -> Feedback -> Sig -> Sig Source #

FreqShifter ; ---------------- ; A frequency shifter effect using the hilbert filter ; ; aout FreqShifter adry,kmix,kfreq,kmult,kfback ; ; Performance ; ----------- ; adry -- input audio to be frequency shifted ; kmix -- dry / wet mix of the output signal (range 0 to 1) ; kfreq -- frequency of frequency shifter effect (suggested range -1000 to 1000) ; kmult -- multiplier of frequency value for fine tuning control (suggested range -1 to 1) ; kfback -- control of the amount of output signal fed back into the input of the effect (suggested range 0 to 1)

fxCompress :: Sig -> (Sig, Sig) -> Sig -> (Sig, Sig) -> Sig -> Sig -> Sig Source #

Compressor. All arguments are relative (range in 0 to 1).

fxCompress thresh (loknee, hiknee) ratio (att, rel) gain ain

audaciousEq :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #

opcode audaciouseq, a, kkkkkkkkkka

inputs: kgain1, kgain2, kgain3, kgain4, kgain5, kgain6, kgain7, kgain8, kgain9, kgain10 ain

10-band EQ Input: kgain1, kgain2, ... kgain10, asig Output: aout

10 kgain arguments maps to each band Bands are: 31.25, 52.6, 125, 500, 1000, 2000, 4000, 8000, 16000

Misc

trackerSplice :: D -> Sig -> Sig -> Sig -> SE Sig Source #

Instrument plays an input signal in different modes. The segments of signal can be played back and forth.

trackerSplice maxLength segLength mode
  • maxLength -- the maximum length of the played segment (in seconds)
  • segLength -- the segment length in seconds
  • mode -- mode of the playing. If it's 1 - only a part of the sample is plyaed and it's played forward. The portion of the signal starts from the current playback point. It lasts for segLength. If it's 2 - the segment is played in reverse. Other values produce the normal input signal.

Original author: Rory Walsh

Example:

main = dac $ do    
   let ev ch1 ch2 dt = fmap (\x -> (x, dt)) $ mconcat [
         fmap (const 1.5) $ charOn ch1 
       , fmap (const 2.5) $ charOn ch2 
       , fmap (const 0) $ charOff ch1 <> charOff ch2]

   (k, dt) <- stepper (0, 0.1) $ ev 'q' 'w' 0.1 <> ev 'a' 's' 0.2 <> ev 'z' 'x' 0.4
   mul 1.3 $ trackerSplice 0.8 dt (int' k) $ fst $ loopWav 1 "drumLoop.wav"

pitchShifterDelay :: MaxDelayTime -> (Feedback, Feedback) -> DelayTime -> Sig -> Sig -> Sig Source #

PitchShifterDelay

A pitch shifter effect that employs delay lines

pitchShifterDelay maxDelayTime delayTime (feedback1, feedback2) transposeRatio ain

Arguments

  • maxDelayTime -- maximum delay time (kdlt should not exceed this value)
  • transposeRatio -- pitch transposition (in semitones)
  • delayTime -- delay time employed by the pitch shifter effect (should be within the range ksmps/sr and imaxdlt)
  • feedback1 -- feedback using method 1 (output from delay taps are fed back directly into their own buffers before enveloping and mixing)
  • feedback2 -- feedback using method 2 (enveloped and mixed output from both taps is fed back into both buffers)--
  • ain -- input audio to be pitch shifted