tidal-1.0.3: Pattern language for improvised music

Safe HaskellNone
LanguageHaskell2010

Sound.Tidal.UI

Contents

Synopsis

UI

timeToRand :: RealFrac a => a -> Double Source #

Randomisation

rand :: Fractional a => Pattern a Source #

rand generates a continuous pattern of (pseudo-)random numbers between `0` and `1`.

sound "bd*8" # pan rand

pans bass drums randomly

sound "sn sn ~ sn" # gain rand

makes the snares' randomly loud and quiet.

Numbers coming from this pattern are seeded by time. So if you reset time (via `cps (-1)`, then `cps 1.1` or whatever cps you want to restart with) the random pattern will emit the exact same _random_ numbers again.

In cases where you need two different random patterns, you can shift one of them around to change the time from which the _random_ pattern is read, note the difference:

jux ( gain rand

and with the juxed version shifted backwards for 1024 cycles:

jux ( gain rand

irand :: Num a => Int -> Pattern a Source #

Just like rand but for whole numbers, `irand n` generates a pattern of (pseudo-) random whole numbers between `0` to `n-1` inclusive. Notably used to pick a random samples from a folder:

d1 $ n (irand 5) # sound "drum"

perlinWith :: Pattern Double -> Pattern Double Source #

1D Perlin (smooth) noise, works like rand but smoothly moves between random values each cycle. perlinWith takes a pattern as the RNG's "input" instead of automatically using the cycle count. d1 $ s "arpy*32" # cutoff (perlinWith (saw * 4) * 2000) will generate a smooth random pattern for the cutoff frequency which will repeat every cycle (because the saw does) The perlin function uses the cycle count as input and can be used much like rand.

choose :: [a] -> Pattern a Source #

Randomly picks an element from the given list

sound "superpiano(3,8)" # note (choose ["a", "e", "g", "c"])

plays a melody randomly choosing one of the four notes "a", "e", "g", "c".

wchoose :: [(a, Double)] -> Pattern a Source #

Like choose, but works on an a list of tuples of values and weights

sound "superpiano(3,8)" # note (choose [("a",1), ("e",0.5), ("g",2), ("c",1)])

In the above example, the "a" and "c" notes are twice as likely to play as the "e" note, and half as likely to play as the "g" note.

degradeBy :: Pattern Double -> Pattern a -> Pattern a Source #

Similar to degrade degradeBy allows you to control the percentage of events that are removed. For example, to remove events 90% of the time:

d1 $ slow 2 $ degradeBy 0.9 $ sound "[[[feel:5*8,feel*3] feel:3*8], feel*4]"
   # accelerate "-6"
   # speed "2"

sometimesBy :: Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

Use sometimesBy to apply a given function "sometimes". For example, the following code results in `density 2` being applied about 25% of the time:

d1 $ sometimesBy 0.25 (density 2) $ sound "bd*8"

There are some aliases as well:

sometimes = sometimesBy 0.5
often = sometimesBy 0.75
rarely = sometimesBy 0.25
almostNever = sometimesBy 0.1
almostAlways = sometimesBy 0.9

sometimes :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

sometimes is an alias for sometimesBy 0.5.

often :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

often is an alias for sometimesBy 0.75.

rarely :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

rarely is an alias for sometimesBy 0.25.

almostNever :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

almostNever is an alias for sometimesBy 0.1

almostAlways :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

almostAlways is an alias for sometimesBy 0.9

never :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

always :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

someCyclesBy :: Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

someCyclesBy is a cycle-by-cycle version of sometimesBy. It has a `someCycles = someCyclesBy 0.5` alias

degrade :: Pattern a -> Pattern a Source #

degrade randomly removes events from a pattern 50% of the time:

d1 $ slow 2 $ degrade $ sound "[[[feel:5*8,feel*3] feel:3*8], feel*4]"
   # accelerate "-6"
   # speed "2"

The shorthand syntax for degrade is a question mark: ?. Using ? will allow you to randomly remove events from a portion of a pattern:

d1 $ slow 2 $ sound "bd ~ sn bd ~ bd? [sn bd?] ~"

You can also use ? to randomly remove events from entire sub-patterns:

d1 $ slow 2 $ sound "[[[feel:5*8,feel*3] feel:3*8]?, feel*4]"

brak :: Pattern a -> Pattern a Source #

(The above means that brak is a function from patterns of any type, to a pattern of the same type.)

Make a pattern sound a bit like a breakbeat

Example:

d1 $ sound (brak "bd sn kurt")

iter :: Pattern Int -> Pattern c -> Pattern c Source #

Divides a pattern into a given number of subdivisions, plays the subdivisions in order, but increments the starting subdivision each cycle. The pattern wraps to the first subdivision after the last subdivision is played.

Example:

d1 $ iter 4 $ sound "bd hh sn cp"

This will produce the following over four cycles:

bd hh sn cp
hh sn cp bd
sn cp bd hh
cp bd hh sn

There is also iter', which shifts the pattern in the opposite direction.

iter' :: Pattern Int -> Pattern c -> Pattern c Source #

iter' is the same as iter, but decrements the starting subdivision instead of incrementing it.

palindrome :: Pattern a -> Pattern a Source #

palindrome p applies rev to p every other cycle, so that the pattern alternates between forwards and backwards.

seqP :: [(Time, Time, Pattern a)] -> Pattern a Source #

Composing patterns

The function seqP allows you to define when a sound within a list starts and ends. The code below contains three separate patterns in a stack, but each has different start times (zero cycles, eight cycles, and sixteen cycles, respectively). All patterns stop after 128 cycles:

d1 $ seqP [
  (0, 128, sound "bd bd*2"),
  (8, 128, sound "hh*2 [sn cp] cp future*4"),
  (16, 128, sound (samples "arpy*8" (run 16)))
]

fadeOut :: Time -> Pattern a -> Pattern a Source #

Degrades a pattern over the given time.

fadeOutFrom :: Time -> Time -> Pattern a -> Pattern a Source #

Alternate version to fadeOut where you can provide the time from which the fade starts

fadeIn :: Time -> Pattern a -> Pattern a Source #

Undegrades a pattern over the given time.

fadeInFrom :: Time -> Time -> Pattern a -> Pattern a Source #

Alternate version to fadeIn where you can provide the time from which the fade in starts

spread :: (a -> t -> Pattern b) -> [a] -> t -> Pattern b Source #

The spread function allows you to take a pattern transformation which takes a parameter, such as slow, and provide several parameters which are switched between. In other words it spreads a function across several values.

Taking a simple high hat loop as an example:

d1 $ sound "ho ho:2 ho:3 hc"

We can slow it down by different amounts, such as by a half:

d1 $ slow 2 $ sound "ho ho:2 ho:3 hc"

Or by four thirds (i.e. speeding it up by a third; `4%3` means four over three):

d1 $ slow (4%3) $ sound "ho ho:2 ho:3 hc"

But if we use spread, we can make a pattern which alternates between the two speeds:

d1 $ spread slow [2,4%3] $ sound "ho ho:2 ho:3 hc"

Note that if you pass ($) as the function to spread values over, you can put functions as the list of values. For example:

d1 $ spread ($) [density 2, rev, slow 2, striate 3, (# speed "0.8")]
    $ sound "[bd*2 [~ bd]] [sn future]*2 cp jvbass*4"

Above, the pattern will have these transforms applied to it, one at a time, per cycle:

  • cycle 1: `density 2` - pattern will increase in speed
  • cycle 2: rev - pattern will be reversed
  • cycle 3: `slow 2` - pattern will decrease in speed
  • cycle 4: `striate 3` - pattern will be granualized
  • cycle 5: `(# speed "0.8")` - pattern samples will be played back more slowly

After `(# speed "0.8")`, the transforms will repeat and start at `density 2` again.

slowspread :: (a -> t -> Pattern b) -> [a] -> t -> Pattern b Source #

fastspread :: (a -> t -> Pattern b) -> [a] -> t -> Pattern b Source #

fastspread works the same as spread, but the result is squashed into a single cycle. If you gave four values to spread, then the result would seem to speed up by a factor of four. Compare these two:

d1 $ spread chop [4,64,32,16] $ sound "ho ho:2 ho:3 hc"

d1 $ fastspread chop [4,64,32,16] $ sound "ho ho:2 ho:3 hc"

There is also slowspread, which is an alias of spread.

spread' :: Monad m => (a -> b -> m c) -> m a -> b -> m c Source #

There's a version of this function, spread' (pronounced "spread prime"), which takes a *pattern* of parameters, instead of a list:

d1 $ spread' slow "2 4%3" $ sound "ho ho:2 ho:3 hc"

This is quite a messy area of Tidal - due to a slight difference of implementation this sounds completely different! One advantage of using spread' though is that you can provide polyphonic parameters, e.g.:

d1 $ spread' slow "[2 4%3, 3]" $ sound "ho ho:2 ho:3 hc"

spreadChoose :: (t -> t1 -> Pattern b) -> [t] -> t1 -> Pattern b Source #

`spreadChoose f xs p` is similar to slowspread but picks values from xs at random, rather than cycling through them in order. It has a shorter alias spreadr.

spreadr :: (t -> t1 -> Pattern b) -> [t] -> t1 -> Pattern b Source #

ifp :: (Int -> Bool) -> (Pattern a -> Pattern a) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

Decide whether to apply one or another function depending on the result of a test function that is passed the current cycle as a number.

d1 $ ifp ((== 0).(flip mod 2))
  (striate 4)
  (# coarse "24 48") $
  sound "hh hc"

This will apply `striate 4` for every _even_ cycle and aply `# coarse "24 48"` for every _odd_.

Detail: As you can see the test function is arbitrary and does not rely on anything tidal specific. In fact it uses only plain haskell functionality, that is: it calculates the modulo of 2 of the current cycle which is either 0 (for even cycles) or 1. It then compares this value against 0 and returns the result, which is either True or False. This is what the ifp signature's first part signifies `(Int -> Bool)`, a function that takes a whole number and returns either True or False.

wedge :: Time -> Pattern a -> Pattern a -> Pattern a Source #

wedge t p p' combines patterns p and p' by squashing the p into the portion of each cycle given by t, and p' into the remainer of each cycle.

whenmod :: Int -> Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

whenmod has a similar form and behavior to every, but requires an additional number. Applies the function to the pattern, when the remainder of the current loop number divided by the first parameter, is greater or equal than the second parameter.

For example the following makes every other block of four loops twice as dense:

d1 $ whenmod 8 4 (density 2) (sound "bd sn kurt")

superimpose :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

superimpose f p = stack [p, f p]

superimpose plays a modified version of a pattern at the same time as the original pattern, resulting in two patterns being played at the same time.

d1 $ superimpose (density 2) $ sound "bd sn [cp ht] hh"
d1 $ superimpose ((# speed "2") . (0.125 <~)) $ sound "bd sn cp hh"

trunc :: Pattern Time -> Pattern a -> Pattern a Source #

trunc truncates a pattern so that only a fraction of the pattern is played. The following example plays only the first quarter of the pattern:

d1 $ trunc 0.25 $ sound "bd sn*2 cp hh*4 arpy bd*2 cp bd*2"

linger :: Pattern Time -> Pattern a -> Pattern a Source #

linger is similar to trunc but the truncated part of the pattern loops until the end of the cycle

d1 $ linger 0.25 $ sound "bd sn*2 cp hh*4 arpy bd*2 cp bd*2"

within :: (Time, Time) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

Use within to apply a function to only a part of a pattern. For example, to apply `density 2` to only the first half of a pattern:

d1 $ within (0, 0.5) (density 2) $ sound "bd*2 sn lt mt hh hh hh hh"

Or, to apply `(# speed "0.5") to only the last quarter of a pattern:

d1 $ within (0.75, 1) (# speed "0.5") $ sound "bd*2 sn lt mt hh hh hh hh"

withinArc :: Arc -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

within' :: (Time, Time) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

For many cases, within' will function exactly as within. The difference between the two occurs when applying functions that change the timing of notes such as fast or <~. within first applies the function to all notes in the cycle, then keeps the results in the specified interval, and then combines it with the old cycle (an "apply split combine" paradigm). within' first keeps notes in the specified interval, then applies the function to these notes, and then combines it with the old cycle (a "split apply combine" paradigm).

For example, whereas using the standard version of within

d1 $ within (0, 0.25) (fast 2) $ sound "bd hh cp sd"

sounds like:

d1 $ sound "[bd hh] hh cp sd"

using this alternative version, within'

d1 $ within' (0, 0.25) (fast 2) $ sound "bd hh cp sd"

sounds like:

d1 $ sound "[bd bd] hh cp sd"

euclid :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a Source #

You can use the e function to apply a Euclidean algorithm over a complex pattern, although the structure of that pattern will be lost:

d1 $ e 3 8 $ sound "bd*2 [sn cp]"

In the above, three sounds are picked from the pattern on the right according to the structure given by the `e 3 8`. It ends up picking two bd sounds, a cp and missing the sn entirely.

These types of sequences use "Bjorklund's algorithm", which wasn't made for music but for an application in nuclear physics, which is exciting. More exciting still is that it is very similar in structure to the one of the first known algorithms written in Euclid's book of elements in 300 BC. You can read more about this in the paper [The Euclidean Algorithm Generates Traditional Musical Rhythms](http:/cgm.cs.mcgill.ca~godfriedpublicationsbanff.pdf) by Toussaint. Some examples from this paper are included below, including rotation in some cases.

- (2,5) : A thirteenth century Persian rhythm called Khafif-e-ramal.
- (3,4) : The archetypal pattern of the Cumbia from Colombia, as well as a Calypso rhythm from Trinidad.
- (3,5,2) : Another thirteenth century Persian rhythm by the name of Khafif-e-ramal, as well as a Rumanian folk-dance rhythm.
- (3,7) : A Ruchenitza rhythm used in a Bulgarian folk-dance.
- (3,8) : The Cuban tresillo pattern.
- (4,7) : Another Ruchenitza Bulgarian folk-dance rhythm.
- (4,9) : The Aksak rhythm of Turkey.
- (4,11) : The metric pattern used by Frank Zappa in his piece titled Outside Now.
- (5,6) : Yields the York-Samai pattern, a popular Arab rhythm.
- (5,7) : The Nawakhat pattern, another popular Arab rhythm.
- (5,8) : The Cuban cinquillo pattern.
- (5,9) : A popular Arab rhythm called Agsag-Samai.
- (5,11) : The metric pattern used by Moussorgsky in Pictures at an Exhibition.
- (5,12) : The Venda clapping pattern of a South African children’s song.
- (5,16) : The Bossa-Nova rhythm necklace of Brazil.
- (7,8) : A typical rhythm played on the Bendir (frame drum).
- (7,12) : A common West African bell pattern.
- (7,16,14) : A Samba rhythm necklace from Brazil.
- (9,16) : A rhythm necklace used in the Central African Republic.
- (11,24,14) : A rhythm necklace of the Aka Pygmies of Central Africa.
- (13,24,5) : Another rhythm necklace of the Aka Pygmies of the upper Sangha.

euclidFull :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a -> Pattern a Source #

`euclidfull n k pa pb` stacks e n k pa with einv n k pb

euclidInv :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a Source #

euclidInv fills in the blanks left by e - e 3 8 "x" -> "x ~ ~ x ~ ~ x ~"

euclidInv 3 8 "x" -> "~ x x ~ x x ~ x"

index :: Real b => b -> Pattern b -> Pattern c -> Pattern c Source #

rot :: Ord a => Pattern Int -> Pattern a -> Pattern a Source #

rot n p rotates the values in a pattern p by n beats to the left. Example: d1 $ every 4 (rot 2) $ slow 2 $ sound "bd hh hh hh"

_rot :: Ord a => Int -> Pattern a -> Pattern a Source #

segment :: Pattern Time -> Pattern a -> Pattern a Source #

segment n p: samples the pattern p at a rate of n events per cycle. Useful for turning a continuous pattern into a discrete one.

discretise :: Pattern Time -> Pattern a -> Pattern a Source #

discretise: the old (deprecated) name for segment

randcat :: [Pattern a] -> Pattern a Source #

randcat ps: does a slowcat on the list of patterns ps but randomises the order in which they are played.

fit :: Int -> [a] -> Pattern Int -> Pattern a Source #

The fit function takes a pattern of integer numbers, which are used to select values from the given list. What makes this a bit strange is that only a given number of values are selected each cycle. For example:

d1 $ sound (fit 3 ["bd", "sn", "arpy", "arpy:1", "casio"] "0 [~ 1] 2 1")

The above fits three samples into the pattern, i.e. for the first cycle this will be `"bd"`, `"sn"` and `"arpy"`, giving the result `"bd [~ sn] arpy sn"` (note that we start counting at zero, so that `0` picks the first value). The following cycle the *next* three values in the list will be picked, i.e. `"arpy:1"`, `"casio"` and `"bd"`, giving the pattern `"arpy:1 [~ casio] bd casio"` (note that the list wraps round here).

permstep :: RealFrac b => Int -> [a] -> Pattern b -> Pattern a Source #

struct :: Pattern Bool -> Pattern a -> Pattern a Source #

struct a b: structures pattern b in terms of the pattern of boolean values a. Only True values in the boolean pattern are used.

substruct :: Pattern String -> Pattern b -> Pattern b Source #

substruct a b: similar to struct, but each event in pattern a gets replaced with pattern b, compressed to fit the timespan of the event.

stripe :: Pattern Int -> Pattern a -> Pattern a Source #

stripe n p: repeats pattern p, n times per cycle. So similar to fast, but with random durations. The repetitions will be continguous (touching, but not overlapping) and the durations will add up to a single cycle. n can be supplied as a pattern of integers.

slowstripe :: Pattern Int -> Pattern a -> Pattern a Source #

slowstripe n p: The same as stripe, but the result is also n times slower, so that the mean average duration of the stripes is exactly one cycle, and every nth stripe starts on a cycle boundary (in indian classical terms, the sam).

lindenmayer :: Int -> String -> String -> String Source #

returns the nth iteration of a Lindenmayer System with given start sequence.

for example:

lindenmayer 1 "a:b,b:ab" "ab" -> "bab"

lindenmayerI :: Num b => Int -> String -> String -> [b] Source #

lindenmayerI converts the resulting string into a a list of integers with fromIntegral applied (so they can be used seamlessly where floats or rationals are required)

mask :: Pattern Bool -> Pattern a -> Pattern a Source #

Removes events from second pattern that don't start during an event from first.

Consider this, kind of messy rhythm without any rests.

d1 $ sound (slowcat ["sn*8", "[cp*4 bd*4, hc*5]"]) # n (run 8)

If we apply a mask to it

d1 $ s (mask ("1 1 1 ~ 1 1 ~ 1" :: Pattern Bool)
  (slowcat ["sn*8", "[cp*4 bd*4, bass*5]"] ))
  # n (run 8)

Due to the use of slowcat here, the same mask is first applied to `"sn*8"` and in the next cycle to `"[cp*4 bd*4, hc*5]".

You could achieve the same effect by adding rests within the slowcat patterns, but mask allows you to do this more easily. It kind of keeps the rhythmic structure and you can change the used samples independently, e.g.

d1 $ s (mask ("1 ~ 1 ~ 1 1 ~ 1")
  (slowcat ["can*8", "[cp*4 sn*4, jvbass*16]"] ))
  # n (run 8)

enclosingArc :: [Arc] -> Arc Source #

TODO: refactor towards union

fit' :: Pattern Time -> Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a Source #

fit' is a generalization of fit, where the list is instead constructed by using another integer pattern to slice up a given pattern. The first argument is the number of cycles of that latter pattern to use when slicing. It's easier to understand this with a few examples:

d1 $ sound (fit' 1 2 "0 1" "1 0" "bd sn")

So what does this do? The first `1` just tells it to slice up a single cycle of `"bd sn"`. The `2` tells it to select two values each cycle, just like the first argument to fit. The next pattern `"0 1"` is the "from" pattern which tells it how to slice, which in this case means `"0"` maps to `"bd"`, and `"1"` maps to `"sn"`. The next pattern `"1 0"` is the "to" pattern, which tells it how to rearrange those slices. So the final result is the pattern `"sn bd"`.

A more useful example might be something like

d1 $ fit' 1 4 (run 4) "[0 3*2 2 1 0 3*2 2 [1*8 ~]]/2" $ chop 4 $ (sound "breaks152" # unit "c")

which uses chop to break a single sample into individual pieces, which fit' then puts into a list (using the `run 4` pattern) and reassembles according to the complicated integer pattern.

chunk :: Int -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b Source #

chunk n f p treats the given pattern p as having n chunks, and applies the function f to one of those sections per cycle, running from left to right.

d1 $ chunk 4 (density 4) $ sound "cp sn arpy [mt lt]"

runWith :: Int -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b Source #

chunk' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b Source #

chunk' works much the same as chunk, but runs from right to left.

runWith' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b Source #

inside :: Pattern Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a Source #

toScale' :: Num a => Int -> [a] -> Pattern Int -> Pattern a Source #

toScale lets you turn a pattern of notes within a scale (expressed as a list) to note numbers. For example `toScale [0, 4, 7] "0 1 2 3"` will turn into the pattern `"0 4 7 12"`. It assumes your scale fits within an octave; to change this use toScale size`. Example: toScale 24 [0,4,7,10,14,17] (run 8)` turns into `"0 4 7 10 14 17 24 28"`

toScale :: Num a => [a] -> Pattern Int -> Pattern a Source #

swingBy :: Pattern Time -> Pattern Time -> Pattern a -> Pattern a Source #

`swingBy x n` divides a cycle into n slices and delays the notes in the second half of each slice by x fraction of a slice . swing is an alias for `swingBy (1%3)`

cycleChoose :: [a] -> Pattern a Source #

cycleChoose is like choose but only picks a new item from the list once each cycle

shuffle :: Int -> Pattern a -> Pattern a Source #

`shuffle n p` evenly divides one cycle of the pattern p into n parts, and returns a random permutation of the parts each cycle. For example, `shuffle 3 "a b c"` could return `"a b c"`, `"a c b"`, `"b a c"`, `"b c a"`, `"c a b"`, or `"c b a"`. But it will **never** return `"a a a"`, because that is not a permutation of the parts.

scramble :: Int -> Pattern a -> Pattern a Source #

`scramble n p` is like shuffle but randomly selects from the parts of p instead of making permutations. For example, `scramble 3 "a b c"` will randomly select 3 parts from `"a"` `"b"` and `"c"`, possibly repeating a single part.

ur :: Time -> Pattern String -> [(String, Pattern a)] -> [(String, Pattern a -> Pattern a)] -> Pattern a Source #

spaceOut :: [Time] -> Pattern a -> Pattern a Source #

spaceOut xs p repeats a pattern p at different durations given by the list of time values in xs

flatpat :: Pattern [a] -> Pattern a Source #

flatpat takes a Pattern of lists and pulls the list elements as separate Events

layer :: [a -> Pattern b] -> a -> Pattern b Source #

layer takes a Pattern of lists and pulls the list elements as separate Events

arpeggiate :: Pattern a -> Pattern a Source #

arpeggiate finds events that share the same timespan, and spreads them out during that timespan, so for example arpeggiate "[bd,sn]" gets turned into "bd sn". Useful for creating arpeggios/broken chords.

arpg :: Pattern a -> Pattern a Source #

Shorthand alias for arpeggiate

stutter :: Integral i => i -> Time -> Pattern a -> Pattern a Source #

jux :: (Pattern ControlMap -> Pattern ControlMap) -> Pattern ControlMap -> Pattern ControlMap Source #

The jux function creates strange stereo effects, by applying a function to a pattern, but only in the right-hand channel. For example, the following reverses the pattern on the righthand side:

d1 $ slow 32 $ jux (rev) $ striateBy 32 (1/16) $ sound "bev"

When passing pattern transforms to functions like jux and every, it's possible to chain multiple transforms together with ., for example this both reverses and halves the playback speed of the pattern in the righthand channel:

d1 $ slow 32 $ jux ((# speed "0.5") . rev) $ striateBy 32 (1/16) $ sound "bev"

jux' :: [t -> Pattern ControlMap] -> t -> Pattern ControlMap Source #

In addition to jux, jux' allows using a list of pattern transform. resulting patterns from each transformation will be spread via pan from left to right.

For example:

d1 $ jux' [iter 4, chop 16, id, rev, palindrome] $ sound "bd sn"

will put `iter 4` of the pattern to the far left and palindrome to the far right. In the center the original pattern will play and mid left mid right the chopped and the reversed version will appear.

One could also write:

d1 $ stack [
    iter 4 $ sound "bd sn" # pan "0",
    chop 16 $ sound "bd sn" # pan "0.25",
    sound "bd sn" # pan "0.5",
    rev $ sound "bd sn" # pan "0.75",
    palindrome $ sound "bd sn" # pan "1",
    ]

jux4 :: (Pattern ControlMap -> Pattern ControlMap) -> Pattern ControlMap -> Pattern ControlMap Source #

Multichannel variant of jux, _not sure what it does_

juxBy :: Pattern Double -> (Pattern ControlMap -> Pattern ControlMap) -> Pattern ControlMap -> Pattern ControlMap Source #

With jux, the original and effected versions of the pattern are panned hard left and right (i.e., panned at 0 and 1). This can be a bit much, especially when listening on headphones. The variant juxBy has an additional parameter, which brings the channel closer to the centre. For example:

d1 $ juxBy 0.5 (density 2) $ sound "bd sn:1"

In the above, the two versions of the pattern would be panned at 0.25 and 0.75, rather than 0 and 1.

spreadf :: [a -> Pattern b] -> a -> Pattern b Source #

range :: Num a => Pattern a -> Pattern a -> Pattern a -> Pattern a Source #

range will take a pattern which goes from 0 to 1 (like sine), and range it to a different range - between the first and second arguments. In the below example, `range 1 1.5` shifts the range of sine1 from 0 - 1 to 1 - 1.5.

d1 $ jux (iter 4) $ sound "arpy arpy:2*2"
  |+ speed (slow 4 $ range 1 1.5 sine1)

_range :: (Functor f, Num b) => b -> b -> f b -> f b Source #

rangex :: (Functor f, Floating b) => b -> b -> f b -> f b Source #

rangex is an exponential version of range, good for using with frequencies. Do *not* use negative numbers or zero as arguments!

off :: Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

_off :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

step :: String -> String -> Pattern String Source #

Step sequencing

step' :: [String] -> String -> Pattern String Source #

like step, but allows you to specify an array of strings to use for 0,1,2...

ghost'' :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #

tabby :: Int -> Pattern a -> Pattern a -> Pattern a Source #

tabby - A more literal weaving than the weave function, give number of threads per cycle and two patterns, and this function will weave them together using a plain (aka tabby) weave, with a simple over/under structure

select :: Pattern Double -> [Pattern a] -> Pattern a Source #

chooses between a list of patterns, using a pattern of floats (from 0-1)

contrast :: (ControlPattern -> ControlPattern) -> (ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern -> ControlPattern Source #

contrast p f f' p' splits controlpattern p' in two, applying the function f to one and f' to the other. This depends on whether events in it contains values matching with those in p. For example in contrast (n "1") ( vowel "a") $ n "0 1" speed 3, the first event will have the vowel effect applied and the second will have the crush applied.

fix :: (ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern -> ControlPattern Source #

Like contrast, but one function is given, and applied to events with matching controls.

unfix :: (ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern -> ControlPattern Source #

Like contrast, but one function is given, and applied to events with controls which don't match.

quantise :: (Functor f, RealFrac b) => b -> f b -> f b Source #

limit values in a Pattern (or other Functor) to n equally spaced divisions of 1.

inv :: Functor f => f Bool -> f Bool Source #

Inverts all the values in a boolean pattern

mono :: Pattern a -> Pattern a Source #

Serialises a pattern so there's only one event playing at any one time, making it monophonic. Events which start/end earlier are given priority.