tidal-0.9.9: Pattern language for improvised music

Safe HaskellNone
LanguageHaskell2010

Sound.Tidal.Params

Synopsis

Documentation

grp :: [Param] -> Pattern String -> ParamPattern Source #

group multiple params into one

sound :: Pattern String -> ParamPattern Source #

A pattern of strings representing sounds or synth notes.

Internally, sound or its shorter alias s is a combination of the samplebank name and number when used with samples, or synth name and note number when used with a synthesiser. For example `bd:2` specifies the third sample (not the second as you might expect, because we start counting at zero) in the bd sample folder.

  • Internally, sound/s is a combination of two parameters, the hidden parameter s' which specifies the samplebank or synth, and the n parameter which specifies the sample or note number. For example:
d1 $ sound "bd:2 sn:0"

is essentially the same as:

d1 $ s' "bd sn" # n "2 0"

n is therefore useful when you want to pattern the sample or note number separately from the samplebank or synth. For example:

d1 $ n "0 5 ~ 2" # sound "drum"

is equivalent to:

d1 $ sound "drum:0 drum:5 ~ drum:2"

accelerate :: Pattern Double -> ParamPattern Source #

a pattern of numbers that speed up (or slow down) samples while they play.

attack :: Pattern Double -> ParamPattern Source #

a pattern of numbers to specify the attack time (in seconds) of an envelope applied to each sample. Only takes effect if release is also specified.

bandf :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Sets the center frequency of the band-pass filter.

bandq :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Sets the q-factor of the band-pass filter.y

begin_p :: Param Source #

a pattern of numbers from 0 to 1. Skips the beginning of each sample, e.g. `0.25` to cut off the first quarter from each sample.

Using `begin "-1"` combined with `cut "-1"` means that when the sample cuts itself it will begin playback from where the previous one left off, so it will sound like one seamless sample. This allows you to apply a synth param across a long sample in a way similar to chop:

cps 0.5

d1 $ sound "breaks125*8"  begin "-1"  coarse "1 2 4 8 16 32 64 128"

This will play the breaks125 sample and apply the changing coarse parameter over the sample. Compare to:

d1 $ (chop 8 $ sounds "breaks125")  coarse "1 2 4 8 16 32 64 128"

which performs a similar effect, but due to differences in implementation sounds different.

channel_p :: Param Source #

a pattern of numbers from 0 to 1. Skips the beginning of each sample, e.g. `0.25` to cut off the first quarter from each sample.

Using `begin "-1"` combined with `cut "-1"` means that when the sample cuts itself it will begin playback from where the previous one left off, so it will sound like one seamless sample. This allows you to apply a synth param across a long sample in a way similar to chop:

cps 0.5

d1 $ sound "breaks125*8"  begin "-1"  coarse "1 2 4 8 16 32 64 128"

This will play the breaks125 sample and apply the changing coarse parameter over the sample. Compare to:

d1 $ (chop 8 $ sounds "breaks125")  coarse "1 2 4 8 16 32 64 128"

which performs a similar effect, but due to differences in implementation sounds different.

legato_p :: Param Source #

a pattern of numbers from 0 to 1. Skips the beginning of each sample, e.g. `0.25` to cut off the first quarter from each sample.

Using `begin "-1"` combined with `cut "-1"` means that when the sample cuts itself it will begin playback from where the previous one left off, so it will sound like one seamless sample. This allows you to apply a synth param across a long sample in a way similar to chop:

cps 0.5

d1 $ sound "breaks125*8"  begin "-1"  coarse "1 2 4 8 16 32 64 128"

This will play the breaks125 sample and apply the changing coarse parameter over the sample. Compare to:

d1 $ (chop 8 $ sounds "breaks125")  coarse "1 2 4 8 16 32 64 128"

which performs a similar effect, but due to differences in implementation sounds different.

clhatdecay_p :: Param Source #

a pattern of numbers from 0 to 1. Skips the beginning of each sample, e.g. `0.25` to cut off the first quarter from each sample.

Using `begin "-1"` combined with `cut "-1"` means that when the sample cuts itself it will begin playback from where the previous one left off, so it will sound like one seamless sample. This allows you to apply a synth param across a long sample in a way similar to chop:

cps 0.5

d1 $ sound "breaks125*8"  begin "-1"  coarse "1 2 4 8 16 32 64 128"

This will play the breaks125 sample and apply the changing coarse parameter over the sample. Compare to:

d1 $ (chop 8 $ sounds "breaks125")  coarse "1 2 4 8 16 32 64 128"

which performs a similar effect, but due to differences in implementation sounds different.

coarse_p :: Param Source #

a pattern of numbers from 0 to 1. Skips the beginning of each sample, e.g. `0.25` to cut off the first quarter from each sample.

Using `begin "-1"` combined with `cut "-1"` means that when the sample cuts itself it will begin playback from where the previous one left off, so it will sound like one seamless sample. This allows you to apply a synth param across a long sample in a way similar to chop:

cps 0.5

d1 $ sound "breaks125*8"  begin "-1"  coarse "1 2 4 8 16 32 64 128"

This will play the breaks125 sample and apply the changing coarse parameter over the sample. Compare to:

d1 $ (chop 8 $ sounds "breaks125")  coarse "1 2 4 8 16 32 64 128"

which performs a similar effect, but due to differences in implementation sounds different.

crush_p :: Param Source #

a pattern of numbers from 0 to 1. Skips the beginning of each sample, e.g. `0.25` to cut off the first quarter from each sample.

Using `begin "-1"` combined with `cut "-1"` means that when the sample cuts itself it will begin playback from where the previous one left off, so it will sound like one seamless sample. This allows you to apply a synth param across a long sample in a way similar to chop:

cps 0.5

d1 $ sound "breaks125*8"  begin "-1"  coarse "1 2 4 8 16 32 64 128"

This will play the breaks125 sample and apply the changing coarse parameter over the sample. Compare to:

d1 $ (chop 8 $ sounds "breaks125")  coarse "1 2 4 8 16 32 64 128"

which performs a similar effect, but due to differences in implementation sounds different.

crush :: Pattern Double -> ParamPattern Source #

bit crushing, a pattern of numbers from 1 (for drastic reduction in bit-depth) to 16 (for barely no reduction).

channel :: Pattern Int -> ParamPattern Source #

choose the physical channel the pattern is sent to, this is super dirt specific

coarse :: Pattern Int -> ParamPattern Source #

fake-resampling, a pattern of numbers for lowering the sample rate, i.e. 1 for original 2 for half, 3 for a third and so on.

cut :: Pattern Int -> ParamPattern Source #

In the style of classic drum-machines, cut will stop a playing sample as soon as another samples with in same cutgroup is to be played.

An example would be an open hi-hat followed by a closed one, essentially muting the open.

d1 $ stack [
  sound "bd",
  sound "~ [~ [ho:2 hc/2]]" # cut "1"
  ]

This will mute the open hi-hat every second cycle when the closed one is played.

Using cut with negative values will only cut the same sample. This is useful to cut very long samples

d1 $ sound "bev, [ho:3]" # cut "-1"

Using `cut "0"` is effectively _no_ cutgroup.

cutoff :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Applies the cutoff frequency of the low-pass filter.

delay :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Sets the level of the delay signal.

delayfeedback :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Sets the amount of delay feedback.

delaytime :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Sets the length of the delay.

dry :: Pattern Double -> ParamPattern Source #

when set to `1` will disable all reverb for this pattern. See room and size for more information about reverb.

gain :: Pattern Double -> ParamPattern Source #

a pattern of numbers that specify volume. Values less than 1 make the sound quieter. Values greater than 1 make the sound louder.

hcutoff :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Applies the cutoff frequency of the high-pass filter.

hold :: Pattern Double -> ParamPattern Source #

a pattern of numbers to specify the hold time (in seconds) of an envelope applied to each sample. Only takes effect if attack and release are also specified.

hresonance :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Applies the resonance of the high-pass filter.

lock :: Pattern Double -> ParamPattern Source #

A pattern of numbers. Specifies whether delaytime is calculated relative to cps. When set to 1, delaytime is a direct multiple of a cycle.

loop :: Pattern Double -> ParamPattern Source #

loops the sample (from begin to end) the specified number of times.

n :: Pattern Double -> ParamPattern Source #

specifies the sample or note number to be used

degree :: Pattern Double -> ParamPattern Source #

Pushes things forward (or backwards within built-in latency) in time. Allows for nice things like _swing_ feeling:

d1 $ stack [
  sound "bd bd/4",
  sound "hh(5,8)"
  ] # nudge "[0 0.04]*4"
  • -pitch model

mtranspose :: Pattern Double -> ParamPattern Source #

Pushes things forward (or backwards within built-in latency) in time. Allows for nice things like _swing_ feeling:

d1 $ stack [
  sound "bd bd/4",
  sound "hh(5,8)"
  ] # nudge "[0 0.04]*4"
  • -pitch model

ctranspose :: Pattern Double -> ParamPattern Source #

Pushes things forward (or backwards within built-in latency) in time. Allows for nice things like _swing_ feeling:

d1 $ stack [
  sound "bd bd/4",
  sound "hh(5,8)"
  ] # nudge "[0 0.04]*4"
  • -pitch model

harmonic :: Pattern Double -> ParamPattern Source #

Pushes things forward (or backwards within built-in latency) in time. Allows for nice things like _swing_ feeling:

d1 $ stack [
  sound "bd bd/4",
  sound "hh(5,8)"
  ] # nudge "[0 0.04]*4"
  • -pitch model

stepsPerOctave :: Pattern Double -> ParamPattern Source #

Pushes things forward (or backwards within built-in latency) in time. Allows for nice things like _swing_ feeling:

d1 $ stack [
  sound "bd bd/4",
  sound "hh(5,8)"
  ] # nudge "[0 0.04]*4"
  • -pitch model

octaveRatio :: Pattern Double -> ParamPattern Source #

Pushes things forward (or backwards within built-in latency) in time. Allows for nice things like _swing_ feeling:

d1 $ stack [
  sound "bd bd/4",
  sound "hh(5,8)"
  ] # nudge "[0 0.04]*4"
  • -pitch model

orbit :: Pattern Int -> ParamPattern Source #

a pattern of numbers. An orbit is a global parameter context for patterns. Patterns with the same orbit will share hardware output bus offset and global effects, e.g. reverb and delay. The maximum number of orbits is specified in the superdirt startup, numbers higher than maximum will wrap around.

pan :: Pattern Double -> ParamPattern Source #

a pattern of numbers between 0 and 1, from left to right (assuming stereo), once round a circle (assuming multichannel)

panspan :: Pattern Double -> ParamPattern Source #

a pattern of numbers between -inf and inf, which controls how much multichannel output is fanned out (negative is backwards ordering)

pansplay :: Pattern Double -> ParamPattern Source #

a pattern of numbers between 0.0 and 1.0, which controls the multichannel spread range (multichannel only)

panwidth :: Pattern Double -> ParamPattern Source #

a pattern of numbers between 0.0 and inf, which controls how much each channel is distributed over neighbours (multichannel only)

panorient :: Pattern Double -> ParamPattern Source #

a pattern of numbers between -1.0 and 1.0, which controls the relative position of the centre pan in a pair of adjacent speakers (multichannel only)

release :: Pattern Double -> ParamPattern Source #

a pattern of numbers to specify the release time (in seconds) of an envelope applied to each sample. Only takes effect if attack is also specified.

resonance :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Specifies the resonance of the low-pass filter.

room :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Sets the level of reverb.

shape :: Pattern Double -> ParamPattern Source #

wave shaping distortion, a pattern of numbers from 0 for no distortion up to 1 for loads of distortion.

size :: Pattern Double -> ParamPattern Source #

a pattern of numbers from 0 to 1. Sets the perceptual size (reverb time) of the room to be used in reverb.

speed :: Pattern Double -> ParamPattern Source #

a pattern of numbers which changes the speed of sample playback, i.e. a cheap way of changing pitch. Negative values will play the sample backwards!

s' :: Pattern String -> ParamPattern Source #

a pattern of strings. Selects the sample to be played.

unit :: Pattern String -> ParamPattern Source #

used in conjunction with speed, accepts values of "r" (rate, default behavior), "c" (cycles), or "s" (seconds). Using `unit "c"` means speed will be interpreted in units of cycles, e.g. `speed "1"` means samples will be stretched to fill a cycle. Using `unit "s"` means the playback speed will be adjusted so that the duration is the number of seconds specified by speed.

vowel :: Pattern String -> ParamPattern Source #

formant filter to make things sound like vowels, a pattern of either a, e, i, o or u. Use a rest (`~`) for no effect.

drumN :: Num a => String -> a Source #