csound-expression-5.2.2: library to make electronic music

Safe HaskellNone
LanguageHaskell98

Csound.Air.Fx.FxBox

Contents

Description

A friendly family of effects. These functions are kindly provided by Iain McCurdy (designed in Csound).

Synopsis

Documentation

adele :: Sigs a => Balance -> DelayTime -> Feedback -> ToneSig -> a -> a Source #

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

adele mixRatio delayTime feedback toneRatio ain

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

pongy :: Sig2s a => Balance -> DelayTime -> Feedback -> ToneSig -> WidthSig -> a -> a Source #

Ping-pong delay

pongy kmix delayTime feedback tone ain

tort :: Sigs a => DriveSig -> ToneSig -> a -> a Source #

Distortion unit with low-pass filter.

tort driveLevel toneRatio ain

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

fowler :: Sigs a => SensitivitySig -> BaseCps -> Resonance -> a -> a Source #

Envelope follower.

fowler 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)

revsy :: Sigs a => TimeSig -> a -> a Source #

An effect that reverses an audio stream in chunks

revsy time

time -- the size of the chunck in seconds.

flan :: Sigs a => RateSig -> DepthSig -> DelayTime -> Feedback -> a -> a Source #

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

 flan 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

phasy :: Sigs a => RateSig -> DepthSig -> BaseCps -> Feedback -> a -> a Source #

Phaser

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

phasy 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 0 to 1)
  • fback -- feedback and therefore intensity of the effect (range 0 to 1)
  • ain -- input audio to be pitch shifted

crusher :: Sigs a => BitsReductionSig -> FoldoverSig -> a -> a Source #

LoFi (Bit Crusher)

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

crusher  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

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

Stereo Chorus

A stereo chorus effect

chory 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

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

Auto pan

pany 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)
  • ain -- input stereo audio

oscPany :: DepthSig -> RateSig -> Sig2 -> Sig2 Source #

Sine auto pan

oscPany = pany 0

triPany :: DepthSig -> RateSig -> Sig2 -> Sig2 Source #

Triangle auto pan

triPany = pany 1

sqrPany :: DepthSig -> RateSig -> Sig2 -> Sig2 Source #

Square auto pan

sqrPany = pany 2

tremy :: Sigs a => TremWaveSig -> DepthSig -> RateSig -> a -> a Source #

Tremolo

tremolo effect

tremy 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)
  • ain -- input stereo audio

oscTremy :: Sigs a => DepthSig -> RateSig -> a -> a Source #

Sine tremolo

oscTremy = tremy 0

triTremy :: Sigs a => DepthSig -> RateSig -> a -> a Source #

Triangle tremolo

triTremy = tremy 1

sqrTremy :: Sigs a => DepthSig -> RateSig -> a -> a Source #

Square tremolo

sqrTremy = tremy 2

ringo :: Sigs a => Balance -> RateSig -> EnvelopeModSig -> a -> a Source #

RingModulator

An ring modulating effect with an envelope follower

ringo balance rate envelopeMod ain
  • balance -- dry / wet mix of the output signal (range 0 to 1) ; rate -- frequency of thew ring modulator *NOT IN HERTZ* (range 0 to 1) ; envelopeMod -- amount of dynamic envelope following modulation of frequency (range 0 to 1)
  • ain -- input audio to be pitch shifted

Presets

For all presets we have 5 levels of strength. They are signified by numbers from 1 to 5. Also for some effects (delay and distortion) we have miscellaneous way to alter preset by suffix b (means bright) and m (means muffled). It alters the tone color of the effect.

Analog Delay

adele1 :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele2 :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele3 :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele4 :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele5 :: Sigs a => Balance -> DelayTime -> a -> a Source #

Bright

adele1b :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele2b :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele3b :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele4b :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele5b :: Sigs a => Balance -> DelayTime -> a -> a Source #

Muted

adele1m :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele2m :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele3m :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele4m :: Sigs a => Balance -> DelayTime -> a -> a Source #

adele5m :: Sigs a => Balance -> DelayTime -> a -> a Source #

Ping Pong Delay

pongy1 :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy2 :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy3 :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy4 :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy5 :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

Bright

pongy1b :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy2b :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy3b :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy4b :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy5b :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

Muted

pongy1m :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy2m :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy3m :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy4m :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

pongy5m :: Sig2s a => Balance -> DelayTime -> WidthSig -> a -> a Source #

Distortion

tort1 :: Sigs a => a -> a Source #

tort2 :: Sigs a => a -> a Source #

tort3 :: Sigs a => a -> a Source #

tort4 :: Sigs a => a -> a Source #

tort5 :: Sigs a => a -> a Source #

Bright

tort1b :: Sigs a => a -> a Source #

tort2b :: Sigs a => a -> a Source #

tort3b :: Sigs a => a -> a Source #

tort4b :: Sigs a => a -> a Source #

tort5b :: Sigs a => a -> a Source #

Muted

tort1m :: Sigs a => a -> a Source #

tort2m :: Sigs a => a -> a Source #

tort3m :: Sigs a => a -> a Source #

tort4m :: Sigs a => a -> a Source #

tort5m :: Sigs a => a -> a Source #

Envelope follower

fowler' :: Sigs a => Sig -> a -> a Source #

fowler1 :: Sigs a => a -> a Source #

fowler2 :: Sigs a => a -> a Source #

fowler3 :: Sigs a => a -> a Source #

fowler4 :: Sigs a => a -> a Source #

fowler5 :: Sigs a => a -> a Source #

Flanger

flan' :: Sigs a => Sig -> a -> a Source #

flan1 :: Sigs a => a -> a Source #

flan2 :: Sigs a => a -> a Source #

flan3 :: Sigs a => a -> a Source #

flan4 :: Sigs a => a -> a Source #

flan5 :: Sigs a => a -> a Source #

Phaser

phasy' :: Sigs a => Sig -> a -> a Source #

phasy1 :: Sigs a => a -> a Source #

phasy2 :: Sigs a => a -> a Source #

phasy3 :: Sigs a => a -> a Source #

phasy4 :: Sigs a => a -> a Source #

phasy5 :: Sigs a => a -> a Source #

Chorus

chory' :: Sig2s a => Sig -> a -> a Source #

chory1 :: Sig2s a => a -> a Source #

chory2 :: Sig2s a => a -> a Source #

chory3 :: Sig2s a => a -> a Source #

chory4 :: Sig2s a => a -> a Source #

chory5 :: Sig2s a => a -> a Source #

Auto Pan

oscPany' :: Sig2s a => Sig -> a -> a Source #

oscPany1 :: Sig2s a => a -> a Source #

oscPany2 :: Sig2s a => a -> a Source #

oscPany3 :: Sig2s a => a -> a Source #

oscPany4 :: Sig2s a => a -> a Source #

oscPany5 :: Sig2s a => a -> a Source #

triPany' :: Sig2s a => Sig -> a -> a Source #

triPany1 :: Sig2s a => a -> a Source #

triPany2 :: Sig2s a => a -> a Source #

triPany3 :: Sig2s a => a -> a Source #

triPany4 :: Sig2s a => a -> a Source #

triPany5 :: Sig2s a => a -> a Source #

sqrPany' :: Sig2s a => Sig -> a -> a Source #

sqrPany1 :: Sig2s a => a -> a Source #

sqrPany2 :: Sig2s a => a -> a Source #

sqrPany3 :: Sig2s a => a -> a Source #

sqrPany4 :: Sig2s a => a -> a Source #

sqrPany5 :: Sig2s a => a -> a Source #

Tremolo

oscTremy' :: Sigs a => Sig -> a -> a Source #

oscTremy1 :: Sigs a => a -> a Source #

oscTremy2 :: Sigs a => a -> a Source #

oscTremy3 :: Sigs a => a -> a Source #

oscTremy4 :: Sigs a => a -> a Source #

oscTremy5 :: Sigs a => a -> a Source #

triTremy' :: Sigs a => Sig -> a -> a Source #

triTremy1 :: Sigs a => a -> a Source #

triTremy2 :: Sigs a => a -> a Source #

triTremy3 :: Sigs a => a -> a Source #

triTremy4 :: Sigs a => a -> a Source #

triTremy5 :: Sigs a => a -> a Source #

sqrTremy' :: Sigs a => Sig -> a -> a Source #

sqrTremy1 :: Sigs a => a -> a Source #

sqrTremy2 :: Sigs a => a -> a Source #

sqrTremy3 :: Sigs a => a -> a Source #

sqrTremy4 :: Sigs a => a -> a Source #

sqrTremy5 :: Sigs a => a -> a Source #

Ring modulation

ringo' :: Sigs a => Sig -> a -> a Source #

ringo1 :: Sigs a => a -> a Source #

ringo2 :: Sigs a => a -> a Source #

ringo3 :: Sigs a => a -> a Source #

ringo4 :: Sigs a => a -> a Source #

ringo5 :: Sigs a => a -> a Source #

Presets with UIs

If we use prefix ui we can create an image of our effect that looks like guitar stompbox.

Let's take a distortion fr instance:

type FxFun = Sig2 -> SE Sig2

uiTort2 :: Source FxFun

We can combine the effects with functions:

fxHor, fxVer :: [Source FxFun] -> Source FxFun

fxMatrix :: Int -> [Source FxFun] -> Source FxFun
fxMatrix numberOfColumns fxs = ...

All these functions stack the effects in the list and align visuals. The visuals can be stacked horizontally, vertically or placed on a square grid.

Let's create a chain of effects and apply it to the input signal:

> let pedals ain = lift1 (\f -> f ain) $ fxHor [uiFlan1, uiAdele2 0.25 0.5, uiHall 0.2, uiGain 0.4]

> vdac $ pedals =<< (atMidi $ dryPatch vibraphone)

With uiGain we can change the volume of the output.

Reverb

Rooms

Chambers

Halls

Caves

Mono Reverb

Rooms

Chambers

Halls

Caves

Delay

Ping Pong Delay

Distortion

Envelope follower

Flanger

Phaser

Chorus

Auto Pan

Tremolo

Reverse

LoFi

Ring modulation

Compressor

TODO