Safe Haskell | None |
---|---|
Language | Haskell98 |
Envelopes
- leg :: D -> D -> D -> D -> Sig
- xeg :: D -> D -> D -> D -> Sig
- onIdur :: [D] -> [D]
- lindur :: [D] -> Sig
- expdur :: [D] -> Sig
- linendur :: Sig -> D -> D -> Sig
- onDur :: D -> [D] -> [D]
- lindurBy :: D -> [D] -> Sig
- expdurBy :: D -> [D] -> Sig
- linendurBy :: D -> Sig -> D -> D -> Sig
- fadeIn :: D -> Sig
- fadeOut :: D -> Sig
- fades :: D -> D -> Sig
- expFadeIn :: D -> Sig
- expFadeOut :: D -> Sig
- expFades :: D -> D -> Sig
- class HumanizeValue a where
- type HumanizeValueOut a :: *
- humanVal :: Sig -> a -> HumanizeValueOut a
- class HumanizeTime a where
- type HumanizeTimeOut a :: *
- humanTime :: Sig -> a -> HumanizeTimeOut a
- class HumanizeValueTime a where
- type HumanizeValueTimeOut a :: *
- humanValTime :: Sig -> Sig -> a -> HumanizeValueTimeOut a
- hval :: HumanizeValue a => Sig -> a -> HumanizeValueOut a
- htime :: HumanizeTime a => Sig -> a -> HumanizeTimeOut a
- hvalTime :: HumanizeValueTime a => Sig -> Sig -> a -> HumanizeValueTimeOut a
- lpshold :: [Sig] -> Sig -> Sig
- loopseg :: [Sig] -> Sig -> Sig
- loopxseg :: [Sig] -> Sig -> Sig
- lpsholdBy :: D -> [Sig] -> Sig -> Sig
- loopsegBy :: D -> [Sig] -> Sig -> Sig
- loopxsegBy :: D -> [Sig] -> Sig -> Sig
- holdSeq :: [Sig] -> [Sig] -> Sig -> Sig
- linSeq :: [Sig] -> [Sig] -> Sig -> Sig
- expSeq :: [Sig] -> [Sig] -> Sig -> Sig
- linloop :: [Sig] -> Sig
- exploop :: [Sig] -> Sig
- sah :: [Sig] -> Sig
- stepSeq :: [Sig] -> Sig -> Sig
- constSeq :: [Sig] -> Sig -> Sig
- triSeq :: [Sig] -> Sig -> Sig
- sqrSeq :: [Sig] -> Sig -> Sig
- sawSeq :: [Sig] -> Sig -> Sig
- isawSeq :: [Sig] -> Sig -> Sig
- xsawSeq :: [Sig] -> Sig -> Sig
- ixsawSeq :: [Sig] -> Sig -> Sig
- isqrSeq :: [Sig] -> Sig -> Sig
- xtriSeq :: [Sig] -> Sig -> Sig
- pwSeq :: Sig -> [Sig] -> Sig -> Sig
- ipwSeq :: Sig -> [Sig] -> Sig -> Sig
- rampSeq :: Sig -> [Sig] -> Sig -> Sig
- irampSeq :: Sig -> [Sig] -> Sig -> Sig
- xrampSeq :: Sig -> [Sig] -> Sig -> Sig
- ixrampSeq :: Sig -> [Sig] -> Sig -> Sig
- adsrSeq :: Sig -> Sig -> Sig -> Sig -> [Sig] -> Sig -> Sig
- xadsrSeq :: Sig -> Sig -> Sig -> Sig -> [Sig] -> Sig -> Sig
- adsrSeq_ :: Sig -> Sig -> Sig -> Sig -> Sig -> [Sig] -> Sig -> Sig
- xadsrSeq_ :: Sig -> Sig -> Sig -> Sig -> Sig -> [Sig] -> Sig -> Sig
- data Seq
- toSeq :: Sig -> Seq
- onBeat :: Seq -> Seq
- onBeats :: Sig -> Seq -> Seq
- seqConst :: [Seq] -> Sig -> Sig
- seqLin :: [Seq] -> Sig -> Sig
- seqExp :: [Seq] -> Sig -> Sig
- seqPw :: Sig -> [Seq] -> Sig -> Sig
- iseqPw :: Sig -> [Seq] -> Sig -> Sig
- seqSqr :: [Seq] -> Sig -> Sig
- iseqSqr :: [Seq] -> Sig -> Sig
- seqSaw :: [Seq] -> Sig -> Sig
- iseqSaw :: [Seq] -> Sig -> Sig
- xseqSaw :: [Seq] -> Sig -> Sig
- ixseqSaw :: [Seq] -> Sig -> Sig
- seqRamp :: Sig -> [Seq] -> Sig -> Sig
- iseqRamp :: Sig -> [Seq] -> Sig -> Sig
- seqTri :: [Seq] -> Sig -> Sig
- seqTriRamp :: Sig -> [Seq] -> Sig -> Sig
- seqAdsr :: Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig
- xseqAdsr :: Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig
- seqAdsr_ :: Sig -> Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig
- xseqAdsr_ :: Sig -> Sig -> Sig -> Sig -> Sig -> [Seq] -> Sig -> Sig
- seqPat :: [Int] -> Seq
- seqAsc :: [Int] -> Seq
- seqDesc :: [Int] -> Seq
- seqHalf :: [Int] -> Seq
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
Relative duration
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]
The opcode linseg
with time intervals
relative to the total duration of the note.
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
A combination of fade in and fade out.
fades attackDuration decayDuration
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
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.
type HumanizeValueOut a :: * Source
humanVal :: Sig -> a -> HumanizeValueOut a Source
HumanizeValue ([Sig] -> Sig -> Sig) | |
HumanizeValue ([D] -> D -> Sig) | |
HumanizeValue ([D] -> Sig) | |
HumanizeValue ([Seq] -> Sig -> Sig) |
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.
type HumanizeTimeOut a :: * Source
humanTime :: Sig -> a -> HumanizeTimeOut a Source
HumanizeTime ([D] -> D -> Sig) | |
HumanizeTime ([D] -> Sig) | |
HumanizeTime ([Seq] -> Sig -> Sig) |
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.
type HumanizeValueTimeOut a :: * Source
humanValTime :: Sig -> Sig -> a -> HumanizeValueTimeOut a Source
HumanizeValueTime ([D] -> D -> Sig) | |
HumanizeValueTime ([D] -> Sig) | |
HumanizeValueTime ([Seq] -> Sig -> Sig) |
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).
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.
constSeq :: [Sig] -> Sig -> Sig Source
Sample and hold sequence. It outputs the looping sequence of constan elements.
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
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
.
Fractional Seq | |
Num Seq | |
Duration Seq | |
Melody Seq | |
Delay Seq | |
Stretch Seq | |
Rest Seq | |
HumanizeValueTime ([Seq] -> Sig -> Sig) | |
HumanizeTime ([Seq] -> Sig -> Sig) | |
HumanizeValue ([Seq] -> Sig -> Sig) | |
type DurOf Seq = Sig | |
type HumanizeValueTimeOut ([Seq] -> Sig -> Sig) = [Seq] -> Sig -> SE Sig | |
type HumanizeTimeOut ([Seq] -> Sig -> Sig) = [Seq] -> Sig -> SE Sig | |
type HumanizeValueOut ([Seq] -> Sig -> Sig) = [Seq] -> Sig -> SE Sig |
onBeats :: Sig -> Seq -> Seq Source
Squashes a sequence to a single beat and then stretches to the given value.
seqPw :: Sig -> [Seq] -> Sig -> Sig Source
The sequence of pulse width waves. The first argument is a duty cycle (ranges from 0 to 1).
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.
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.
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
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