csound-expression-5.3.4: library to make electronic music
Safe HaskellNone
LanguageHaskell2010

Csound.Air.Envelope

Description

Envelopes

Synopsis

Documentation

leg :: D -> D -> D -> D -> Sig Source #

Linear adsr envelope generator with release

leg attack decay sustain release

xeg :: D -> D -> D -> D -> Sig Source #

Exponential adsr envelope generator with release

xeg attack decay sustain release

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

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

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

trigTab :: Tab -> Sig -> Sig -> Sig Source #

Triggers the table based envelope when the trigger signal equals to 1 and plays for dur seconds:

trigTab table dur trigger

trigTabEvt :: Tab -> Sig -> Evt a -> Sig Source #

Triggers the table based envelope when the something happens on the event stream and plays for dur seconds:

trigTabEvt table dur trigger

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] -> Sig Source #

The opcode linseg with time intervals relative to the total duration of the note.

expdur :: [D] -> Sig Source #

The opcode expseg with time intervals relative to the total duration of the note.

linendur :: Sig -> D -> D -> Sig Source #

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] -> Sig Source #

The opcode linseg with time intervals relative to the total duration of the note given by the user.

expdurBy :: D -> [D] -> Sig Source #

The opcode expseg with time intervals relative to the total duration of the note given by the user.

linendurBy :: D -> Sig -> D -> D -> Sig Source #

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

Faders

fadeIn :: D -> Sig Source #

Fades in with the given attack time.

fadeOut :: D -> Sig Source #

Fades out with the given attack time.

fades :: D -> D -> Sig Source #

A combination of fade in and fade out.

fades attackDuration decayDuration

expFadeIn :: D -> Sig Source #

Fades in by exponent with the given attack time.

expFadeOut :: D -> Sig Source #

Fades out by exponent with the given attack time.

expFades :: D -> D -> Sig Source #

A combination of exponential fade in and fade out.

expFades attackDuration decayDuration

slope :: D -> D -> Sig Source #

Slope envelope. It stays at zero for a given time then it raises to 1 for thre given time. The function is usefull to delay the LFO.

slope zeroTime rizeTime

expSlope :: D -> D -> Sig Source #

Exponential slope (See the function slope).

Humanize

class HumanizeValue a where Source #

A function transformer (decorator). We can transform an envelope producer so that all values are sumed with some random value. The amplitude of the random value is given with the first argument.

It can transform linseg, expseg, sequence producers and simplified sequence producers.

An example:

dac $ mul (humanVal 0.1 sqrSeq [1, 0.5, 0.2, 0.1] 1) $ white

As you can see it transforms the whole function. So we don't need for extra parenthesis.

Associated Types

type HumanizeValueOut a :: * Source #

Methods

humanVal :: Sig -> a -> HumanizeValueOut a Source #

Instances

Instances details
HumanizeValue ([Sig] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueOut ([Sig] -> Sig -> Sig) Source #

Methods

humanVal :: Sig -> ([Sig] -> Sig -> Sig) -> HumanizeValueOut ([Sig] -> Sig -> Sig) Source #

HumanizeValue ([D] -> D -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueOut ([D] -> D -> Sig) Source #

Methods

humanVal :: Sig -> ([D] -> D -> Sig) -> HumanizeValueOut ([D] -> D -> Sig) Source #

HumanizeValue ([D] -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueOut ([D] -> Sig) Source #

Methods

humanVal :: Sig -> ([D] -> Sig) -> HumanizeValueOut ([D] -> Sig) Source #

HumanizeValue ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueOut ([Seq] -> Sig -> Sig) Source #

Methods

humanVal :: Sig -> ([Seq] -> Sig -> Sig) -> HumanizeValueOut ([Seq] -> Sig -> Sig) Source #

class HumanizeTime a where Source #

A function transformer (decorator). We can transform an envelope producer so that all durations are sumed with some random value. The amplitude of the random value is given with the first argument.

It can transform linseg, expseg, sequence producers and simplified sequence producers.

An example:

dac $ mul (humanTime 0.1 sqrSeq [1, 0.5, 0.2, 0.1] 1) $ white

As you can see it transforms the whole function. So we don't need for extra parenthesis.

Associated Types

type HumanizeTimeOut a :: * Source #

Methods

humanTime :: Sig -> a -> HumanizeTimeOut a Source #

Instances

Instances details
HumanizeTime ([D] -> D -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeTimeOut ([D] -> D -> Sig) Source #

Methods

humanTime :: Sig -> ([D] -> D -> Sig) -> HumanizeTimeOut ([D] -> D -> Sig) Source #

HumanizeTime ([D] -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeTimeOut ([D] -> Sig) Source #

Methods

humanTime :: Sig -> ([D] -> Sig) -> HumanizeTimeOut ([D] -> Sig) Source #

HumanizeTime ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeTimeOut ([Seq] -> Sig -> Sig) Source #

Methods

humanTime :: Sig -> ([Seq] -> Sig -> Sig) -> HumanizeTimeOut ([Seq] -> Sig -> Sig) Source #

class HumanizeValueTime a where Source #

A function transformer (decorator). We can transform an envelope producer so that all values and durations are sumed with some random value. The amplitude of the random value is given with the first two arguments.

It can transform linseg, expseg, sequence producers and simplified sequence producers.

An example:

dac $ mul (humanValTime 0.1 0.1 sqrSeq [1, 0.5, 0.2, 0.1] 1) $ white

As you can see it transforms the whole function. So we don't need for extra parenthesis.

Associated Types

type HumanizeValueTimeOut a :: * Source #

Instances

Instances details
HumanizeValueTime ([D] -> D -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueTimeOut ([D] -> D -> Sig) Source #

Methods

humanValTime :: Sig -> Sig -> ([D] -> D -> Sig) -> HumanizeValueTimeOut ([D] -> D -> Sig) Source #

HumanizeValueTime ([D] -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueTimeOut ([D] -> Sig) Source #

Methods

humanValTime :: Sig -> Sig -> ([D] -> Sig) -> HumanizeValueTimeOut ([D] -> Sig) Source #

HumanizeValueTime ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueTimeOut ([Seq] -> Sig -> Sig) Source #

Methods

humanValTime :: Sig -> Sig -> ([Seq] -> Sig -> Sig) -> HumanizeValueTimeOut ([Seq] -> Sig -> Sig) Source #

hval :: HumanizeValue a => Sig -> a -> HumanizeValueOut a Source #

Alias for humanVal.

htime :: HumanizeTime a => Sig -> a -> HumanizeTimeOut a Source #

Alias for humanTime.

hvalTime :: HumanizeValueTime a => Sig -> Sig -> a -> HumanizeValueTimeOut a Source #

Alias for humanValTime.

Looping envelopes

Simple

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

Looping sample and hold envelope. The first argument is the list of pairs:

[a, durA, b, durB, c, durc, ...]

It's a list of values and durations. The durations are relative to the period of repetition. The period is specified with the second argument. The second argument is the frequency of repetition measured in Hz.

lpshold valDurs frequency

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

Looping linear segments envelope. The first argument is the list of pairs:

[a, durA, b, durB, c, durc, ...]

It's a list of values and durations. The durations are relative to the period of repetition. The period is specified with the second argument. The second argument is the frequency of repetition measured in Hz.

loopseg valDurs frequency

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

Looping exponential segments envelope. The first argument is the list of pairs:

[a, durA, b, durB, c, durc, ...]

It's a list of values and durations. The durations are relative to the period of repetition. The period is specified with the second argument. The second argument is the frequency of repetition measured in Hz.

loopxseg valDurs frequency

lpsholdBy :: D -> [Sig] -> Sig -> Sig Source #

It's like lpshold but we can specify the phase of repetition (phase belongs to [0, 1]).

loopsegBy :: D -> [Sig] -> Sig -> Sig Source #

It's like loopseg but we can specify the phase of repetition (phase belongs to [0, 1]).

loopxsegBy :: D -> [Sig] -> Sig -> Sig Source #

It's like loopxseg but we can specify the phase of repetition (phase belongs to [0, 1]).

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

The looping sequence of constant segments.

linSeg [a, durA, b, durB, c, durC, ...] [scale1, scale2, scale3] cps

The first argument is the list that specifies the shape of the looping wave. It's the alternating values and durations of transition from one value to another. The durations are relative to the period. So that lists

[0, 0.5, 1, 0.5, 0]  and [0, 50, 1, 50, 0]

produce the same results. The second list is the list of scales for subsequent periods. Every value in the period is scaled with values from the second list. The last argument is the rate of repetition (Hz).

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

The looping sequence of linear segments.

linSeg [a, durA, b, durB, c, durC, ...] [scale1, scale2, scale3] cps

The first argument is the list that specifies the shape of the looping wave. It's the alternating values and durations of transition from one value to another. The durations are relative to the period. So that lists

[0, 0.5, 1, 0.5, 0]  and [0, 50, 1, 50, 0]

produce the same results. The second list is the list of scales for subsequent periods. Every value in the period is scaled with values from the second list. The last argument is the rate of repetition (Hz).

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

The looping sequence of exponential segments.

expSeg [a, durA, b, durB, c, durC, ...] [scale1, scale2, scale3] cps

The first argument is the list that specifies the shape of the looping wave. It's the alternating values and durations of transition from one value to another. The durations are relative to the period. So that lists

[0, 0.5, 1, 0.5, 0]  and [0, 50, 1, 50, 0]

produce the same results. The second list is the list of scales for subsequent periods. Every value in the period is scaled with values from the second list. The last argument is the rate of repetition (Hz).

linloop :: [Sig] -> Sig Source #

It's just like linseg but it loops over the envelope.

exploop :: [Sig] -> Sig Source #

It's just like expseg but it loops over the envelope.

sah :: [Sig] -> Sig Source #

Sample and hold cyclic signal. It takes the list of

[a, dta, b, dtb, c, dtc, ...]

the a, b, c, ... are values of the constant segments

the dta, dtb, dtc, are durations in seconds of constant segments.

The period of the repetition equals to the sum of all durations.

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

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

Sample and hold sequence. It outputs the looping sequence of constan elements.

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

Step sequencer with unipolar triangle.

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

Step sequencer with unipolar square.

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

Step sequencer with unipolar sawtooth.

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

Step sequencer with unipolar inveted sawtooth.

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

Step sequencer with unipolar exponential sawtooth.

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

Step sequencer with unipolar inverted exponential sawtooth.

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

Step sequencer with unipolar inveted square.

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

Step sequencer with unipolar exponential triangle.

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

A sequence of unipolar waves with pulse width moulation (see upw). The first argument is a duty cycle in range 0 to 1.

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

A sequence of unipolar inverted waves with pulse width moulation (see upw). The first argument is a duty cycle in range 0 to 1.

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

A sequence of unipolar triangle waves with ramp factor (see uramp). The first argument is a ramp factor cycle in range 0 to 1.

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

A sequence of unipolar inverted triangle waves with ramp factor (see uramp). The first argument is a ramp factor cycle in range 0 to 1.

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

A sequence of unipolar exponential triangle waves with ramp factor (see uramp). The first argument is a ramp factor cycle in range 0 to 1.

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

A sequence of unipolar inverted exponential triangle waves with ramp factor (see uramp). The first argument is a ramp factor cycle in range 0 to 1.

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

The looping ADSR envelope.

xadsrSeq attack decay sustain release weights frequency

The sum of attack, decay, sustain and release time durations should be equal to one.

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

The looping exponential ADSR envelope. there is a fifth segment at the end of the envelope during which the envelope equals to zero.

xadsrSeq attack decay sustain release weights frequency

The sum of attack, decay, sustain and release time durations should be equal to one.

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

The looping ADSR envelope with the rest at the end.

adsrSeq attack decay sustain release rest weights frequency

The sum of attack, decay, sustain, release and rest time durations should be equal to one.

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

The looping exponential ADSR envelope. there is a fifth segment at the end of the envelope during which the envelope equals to zero.

xadsrSeq_ attack decay sustain release rest weights frequency

The sum of attack, decay, sustain, release and rest time durations should be equal to one.

Complex

data Seq Source #

The seq is a type for step sequencers. The step sequencer is a monophonic control signal. Most often step sequencer is a looping segment of some values. It's used to create bas lines or conrtrol the frequency of the filter in dub or trance music. There are simple functions for creation of step sequencers defined in the module Csound.Air.Envelope.

Basically the step sequence is a list of pairs:

 [(valA, durA), (valB, durB), (valC, durC)]

each pair defines a segment of height valN that lasts for durN. The sequence is repeated with the given frequency. Each segment has certain shape. It can be a constant or line segment or fragment of square wave or fragment of an adsr envelope. There are many predefined functions.

With Seq we can construct control signals in very flexible way. We can use the score composition functions for creation of sequences. We can use mel for sequencing of individual steps, we can use str for stretching the sequence in time domain, we can delay with del.

Here is an example:

dac $ tri $ seqConst [str 0.25 $ mel [440, 220, 330, 220], 110] 1

We can see how the function str was used to make a certain segment faster. There are numerical instaces for Seq. Bt it defines only functions fronInteger and fromRational.

Instances

Instances details
Fractional Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

(/) :: Seq -> Seq -> Seq #

recip :: Seq -> Seq #

fromRational :: Rational -> Seq #

Num Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

(+) :: Seq -> Seq -> Seq #

(-) :: Seq -> Seq -> Seq #

(*) :: Seq -> Seq -> Seq #

negate :: Seq -> Seq #

abs :: Seq -> Seq #

signum :: Seq -> Seq #

fromInteger :: Integer -> Seq #

Duration Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

dur :: Seq -> DurOf Seq #

Melody Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

mel :: [Seq] -> Seq #

(+:+) :: Seq -> Seq -> Seq #

Delay Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

del :: DurOf Seq -> Seq -> Seq #

Stretch Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

str :: DurOf Seq -> Seq -> Seq #

Rest Seq Source # 
Instance details

Defined in Csound.Air.Envelope

Methods

rest :: DurOf Seq -> Seq #

HumanizeValueTime ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueTimeOut ([Seq] -> Sig -> Sig) Source #

Methods

humanValTime :: Sig -> Sig -> ([Seq] -> Sig -> Sig) -> HumanizeValueTimeOut ([Seq] -> Sig -> Sig) Source #

HumanizeTime ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeTimeOut ([Seq] -> Sig -> Sig) Source #

Methods

humanTime :: Sig -> ([Seq] -> Sig -> Sig) -> HumanizeTimeOut ([Seq] -> Sig -> Sig) Source #

HumanizeValue ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

Associated Types

type HumanizeValueOut ([Seq] -> Sig -> Sig) Source #

Methods

humanVal :: Sig -> ([Seq] -> Sig -> Sig) -> HumanizeValueOut ([Seq] -> Sig -> Sig) Source #

type DurOf Seq Source # 
Instance details

Defined in Csound.Air.Envelope

type DurOf Seq = Sig
type HumanizeValueTimeOut ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

type HumanizeValueTimeOut ([Seq] -> Sig -> Sig) = [Seq] -> Sig -> SE Sig
type HumanizeTimeOut ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

type HumanizeTimeOut ([Seq] -> Sig -> Sig) = [Seq] -> Sig -> SE Sig
type HumanizeValueOut ([Seq] -> Sig -> Sig) Source # 
Instance details

Defined in Csound.Air.Envelope

type HumanizeValueOut ([Seq] -> Sig -> Sig) = [Seq] -> Sig -> SE Sig

toSeq :: Sig -> Seq Source #

Creates a

onBeat :: Seq -> Seq Source #

Squashes a sequence to a single beat.

onBeats :: Sig -> Seq -> Seq Source #

Squashes a sequence to a single beat and then stretches to the given value.

seqConst :: [Seq] -> Sig -> Sig Source #

A sequence of constant segments.

seqLin :: [Seq] -> Sig -> Sig Source #

A linear sequence.

seqExp :: [Seq] -> Sig -> Sig Source #

An exponential sequence.

seqPw :: Sig -> [Seq] -> Sig -> Sig Source #

The sequence of pulse width waves. The first argument is a duty cycle (ranges from 0 to 1).

iseqPw :: Sig -> [Seq] -> Sig -> Sig Source #

The sequence of inversed pulse width waves.

seqSqr :: [Seq] -> Sig -> Sig Source #

The sequence of square waves.

iseqSqr :: [Seq] -> Sig -> Sig Source #

The sequence of inversed square waves.

seqSaw :: [Seq] -> Sig -> Sig Source #

The sequence of sawtooth waves.

iseqSaw :: [Seq] -> Sig -> Sig Source #

The sequence of inversed sawtooth waves.

xseqSaw :: [Seq] -> Sig -> Sig Source #

The sequence of exponential sawtooth waves.

ixseqSaw :: [Seq] -> Sig -> Sig Source #

The sequence of inversed exponential sawtooth waves.

seqRamp :: Sig -> [Seq] -> Sig -> Sig Source #

The sequence of ramp functions. The first argument is a duty cycle.

iseqRamp :: Sig -> [Seq] -> Sig -> Sig Source #

The sequence of inversed ramp functions. The first argument is a duty cycle.

seqTri :: [Seq] -> Sig -> Sig Source #

The sequence of triangular waves.

seqTriRamp :: Sig -> [Seq] -> Sig -> Sig Source #

The sequence of ramped triangular waves.

seqAdsr :: Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig Source #

The sequence of ADSR-envelopes.

seqAdsr att dec sus rel

It has to be:

att + dec + sus_time + rel == 1

xseqAdsr :: Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig Source #

The sequence of exponential ADSR-envelopes.

seqAdsr_ :: Sig -> Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig Source #

The sequence of ADSR-envelopes with rest at the end.

seqAdsr att dec sus rel rest

It has to be:

att + dec + sus_time + rel + rest == 1

xseqAdsr_ :: Sig -> Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig Source #

The sequence of exponential ADSR-envelopes with rest at the end.

seqPat :: [Int] -> Seq Source #

Function for creation of accented beats. The steady beat pattern of accents is repeated. The first argument describes the list of integers. Each integer is a main beat and the length of the beat. We can create a typical latino beat:

dac $ mul (seqSaw [seqPat [3, 3, 2]] 1) white

seqAsc :: [Int] -> Seq Source #

It's like seqPat but inplace of rests it fills the gaps with segments ascending in value.

dac $ mul (seqSaw [seqAsc [3, 3, 2]] 1) white

seqDesc :: [Int] -> Seq Source #

It's like seqPat but inplace of rests it fills the gaps with segments descending in value.

dac $ mul (seqSaw [seqDesc [3, 3, 2]] 1) white

seqHalf :: [Int] -> Seq Source #

It's like seqPat but inplace of rests it fills the gaps with 0.5s.

dac $ mul (seqSaw [seqHalf [3, 3, 2]] 1) white