csound-expression-typed-0.2.7: typed core for the library csound-expression
Safe HaskellNone
LanguageHaskell2010

Csound.Typed.Plugins

Synopsis

Documentation

adsr140 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

Gated, Re-triggerable ADSR modeled after the Doepfer A-140 opcode adsr140, a, aakkkk

inputs: agate, aretrig, kattack, kdecay, ksustain, krelease

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

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

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

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

zlp1 :: Sig -> Sig -> Sig Source #

zhp1 :: Sig -> Sig -> Sig Source #

zap1 :: Sig -> Sig -> Sig Source #

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

zlp :: Sig -> Sig -> Sig -> Sig Source #

zbp :: Sig -> Sig -> Sig -> Sig Source #

zhp :: Sig -> Sig -> Sig -> Sig Source #

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

zbr :: Sig -> Sig -> Sig -> Sig Source #

zladder :: Sig -> Sig -> Sig -> Sig Source #

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

zlp4 :: Sig -> Sig -> Sig -> Sig Source #

zbp4 :: Sig -> Sig -> Sig -> Sig Source #

zhp4 :: Sig -> Sig -> Sig -> Sig Source #

peakEq :: Sig -> Sig -> Sig -> Sig -> Sig Source #

lowShelf :: Sig -> Sig -> Sig -> Sig Source #

diode :: Sig -> Sig -> Sig -> Sig -> Sig Source #

Non-Linear normalized diode ladder filter.

diode saturation centerFrequency resonance asig

resonance ranges in the interval [0, 1] and higher. self-resonance occurs at 1.

saturation ranges from 1 and higher (typical value: 4)

linDiode :: Sig -> Sig -> Sig -> Sig Source #

Linear diode ladder filter.

linDiode centerFrequency resonance asig

resonance ranges in the interval [0, 1] and higher. self-resonance occurs at 1.

noNormDiode :: Sig -> Sig -> Sig -> Sig -> Sig Source #

Non-Linear not normalized diode ladder filter.

noNormDiode saturation centerFrequency resonance asig

resonance ranges in the interval [0, 1] and higher. self-resonance occurs at 1.

saturation ranges from 1 and higher (typical value: 4)

linKorg_lp :: Sig -> Sig -> Sig -> Sig Source #

Linear korg 35 low pass filter (12 dB).

linDiode centerFrequency resonance asig

resonance ranges in the interval [0, 1] and higher. self-resonance occurs at 1.

linKorg_hp :: Sig -> Sig -> Sig -> Sig Source #

Linear korg 35 high pass filter (6 dB).

linDiode centerFrequency resonance asig

resonance ranges in the interval [0, 1] and higher. self-resonance occurs at 1.

korg_lp :: Sig -> Sig -> Sig -> Sig -> Sig Source #

Korg 35 low pass filter (12 dB).

diode saturation centerFrequency resonance asig

resonance ranges in the interval [0, 1] and higher. self-resonance occurs at 1.

saturation ranges from 1 and higher (typical value: 4)

korg_hp :: Sig -> Sig -> Sig -> Sig -> Sig Source #

Korg 35 high pass filter (6 dB).

diode saturation centerFrequency resonance asig

resonance ranges in the interval [0, 1] and higher. self-resonance occurs at 1.

saturation ranges from 1 and higher (typical value: 4)

data ZConvSpec Source #

Zero convolution specification

Constructors

ZConvSpec 

Fields

Instances

Instances details
Default ZConvSpec Source # 
Instance details

Defined in Csound.Typed.Plugins.ZeroDelayConvolution

Methods

def :: ZConvSpec #

zconv :: Tab -> Sig -> Sig Source #

Zero delay convolution with default parameters.

zconv tabIR  ain = ...

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

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 **************************************************/

pitchShifterDelay :: D -> (Sig, Sig) -> Sig -> Sig -> Sig -> Sig Source #

fxAnalogDelay :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

fxFlanger :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

fxFreqShifter :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

fxLoFi :: Sig -> Sig -> Sig -> Sig Source #

fxPanTrem :: Sig -> Sig -> Sig -> Sig -> Sig2 -> Sig2 Source #

fxMonoTrem :: Sig -> Sig -> Sig -> Sig -> Sig Source #

fxPhaser :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

fxPitchShifter :: D -> Sig -> Sig -> Sig -> Sig -> Sig Source #

fxChorus2 :: Sig -> Sig -> Sig -> Sig2 -> Sig2 Source #

fxPingPong :: D -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig2 -> Sig2 Source #

Stereo ping-pong delay effect

fxPingPong maxDelayTime kmix width tone time feedback (ainL, ainR)

Tape echo

tapeRead :: Sig -> Sig -> Sig -> SE Sig Source #

Function to read from tape.

tapeRead aIn, kDelay, kRandomSpread

The function is used in the same manner as deltapi first init the delay buffer and the use tapeRead.

aIn - input signal kDelay - delay time kRandomSpread - [0, Inf] - the random spread of reading from the tape the higher the worser the quality of the tape. opcode tapeRead, a, akk

tapeWrite :: Sig -> Sig -> Sig -> SE () Source #

Function to write to tape

tapeWrite aIn, aOut, kFbGain

It should be though of as delayw for magnetic tape.

aIn - input signal aOut - output signal kFbGain - gain of feedback [0, 2]

tapeEcho :: D -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

Generic multi-tap echo opcode.

tapeEcho iSize kDelay kEchoGain kFbGain kTone kRandomSpread aIn
  • iSize - how many units of echo
  • kDelay - delay time
  • kEchoGain - gain of the echoes
  • kFbGain - feedback
  • kTone - low pass filter frequency
  • kRandomSpread - quality of the tape [0, Inf], the higher the worser the quality of the tape.
  • aIn - input signal

Live row

liveRow :: D -> TabList -> D -> D -> Sig -> Tab -> Sig Source #

liveRows :: D -> TabList -> TabList -> D -> D -> Sig -> Tab -> Sig2 Source #

Ambi row

ambiRow :: Arr1 Str -> Sig -> Sig -> D -> Sig2 Source #

delay1k :: Sig -> Sig Source #

Delay a control signal by single sample.