csound-expression-5.1.0: 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 -> SE Sig Source #

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

echo delayLength ratio

fdelay :: MaxDelayTime -> Feedback -> Balance -> Sig -> SE Sig Source #

Delay with feedback.

fdelay delayLength decayRatio balance

fvdelay :: MaxDelayTime -> DelayTime -> Feedback -> Balance -> Sig -> SE 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 -> SE Sig2 Source #

Ping-pong delay.

pingPong delayTime feedback mixLevel

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

Ping-pong delay with miscellaneous arguments.

pingPong' spec delayTime feedback mixLevel

csdPingPong :: MaxDelayTime -> DelayTime -> Sig -> Feedback -> Sig -> Balance -> Sig2 -> SE 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

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

Distortion

fxDistort level drive tone sigIn

fxDistort2 :: Feedback -> Sig -> ToneSig -> Sig2 -> Sig2 Source #

Stereo distortion.

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

Stereo chorus.

stChorus2 mix rate depth width sigIn

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

Phaser

fxPhaser mix rate depth freq feedback sigIn

fxPhaser2 :: Balance -> Feedback -> RateSig -> DepthSig -> Sig -> Sig2 -> Sig2 Source #

Stereo phaser.

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

Flanger

fxFlanger mix feedback rate depth delay sigIn

fxFlanger2 :: Balance -> Feedback -> RateSig -> DepthSig -> DelayTime -> Sig2 -> Sig2 Source #

Stereo flanger

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

Analog delay.

analogDelay mix feedback time tone sigIn

analogDelay2 :: Balance -> Feedback -> DelayTime -> ToneSig -> Sig2 -> SE Sig2 Source #

Stereo analog delay.

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

Simplified delay

fxEcho maxDelayLength delTime feedback sigIn

fxEcho2 :: D -> Sig -> Sig -> Sig2 -> SE Sig2 Source #

Simplified stereo delay.

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

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

fxFilter lowPassfFreq highPassFreq gain 

fxFilter2 :: Sig -> Sig -> Sig -> Sig2 -> Sig2 Source #

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

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

Adds filtered white noize to the signal

fxWhite lfoFreq depth sigIn

fxWhite2 :: Sig -> Sig -> Sig2 -> SE Sig2 Source #

Adds filtered white noize to the stereo signal

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

Adds filtered pink noize to the signal

fxWhite lfoFreq depth sigIn

fxPink2 :: Sig -> Sig -> Sig2 -> SE Sig2 Source #

Adds filtered pink noize to the stereo signal

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

Equalizer

equalizer gainsAndFrequencies gain sigIn

equalizer2 :: [(Sig, Sig)] -> Sig -> Sig2 -> Sig2 Source #

Stereo equalizer.

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

Equalizer with frequencies: 100, 400, 1600, 6400

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

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

fxGain :: Sig -> Sig2 -> Sig2 Source #

Gain

fxGain gain sigIn

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"