Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides the main user interface functions, including sources of randomness and transformations of patterns. All these functions are available in the context of the TidalCycles REPL.
Many functions in this module taking Pattern
values as arguments have a
corresponding function with an underscore prepended to its name (e.g.
degradeBy
and _degradeBy
). These functions accept plain values, not
Pattern
s, and are generally intended for those developing or extending Tidal.
Synopsis
- xorwise :: Int -> Int
- timeToIntSeed :: RealFrac a => a -> Int
- intSeedToRand :: Fractional a => Int -> a
- timeToRand :: (RealFrac a, Fractional b) => a -> b
- timeToRands :: (RealFrac a, Fractional b) => a -> Int -> [b]
- timeToRands' :: Fractional a => Int -> Int -> [a]
- rand :: Fractional a => Pattern a
- brand :: Pattern Bool
- brandBy :: Pattern Double -> Pattern Bool
- _brandBy :: Double -> Pattern Bool
- irand :: Num a => Pattern Int -> Pattern a
- _irand :: Num a => Int -> Pattern a
- perlinWith :: Fractional a => Pattern Double -> Pattern a
- perlin :: Fractional a => Pattern a
- perlin2With :: Pattern Double -> Pattern Double -> Pattern Double
- perlin2 :: Pattern Double -> Pattern Double
- choose :: [a] -> Pattern a
- chooseBy :: Pattern Double -> [a] -> Pattern a
- wchoose :: [(a, Double)] -> Pattern a
- wchooseBy :: Pattern Double -> [(a, Double)] -> Pattern a
- randcat :: [Pattern a] -> Pattern a
- wrandcat :: [(Pattern a, Double)] -> Pattern a
- degrade :: Pattern a -> Pattern a
- degradeBy :: Pattern Double -> Pattern a -> Pattern a
- _degradeBy :: Double -> Pattern a -> Pattern a
- _degradeByUsing :: Pattern Double -> Double -> Pattern a -> Pattern a
- unDegradeBy :: Pattern Double -> Pattern a -> Pattern a
- _unDegradeBy :: Double -> Pattern a -> Pattern a
- degradeOverBy :: Int -> Pattern Double -> Pattern a -> Pattern a
- sometimesBy :: Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- sometimesBy' :: Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- sometimes :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- sometimes' :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- often :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- often' :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- rarely :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- rarely' :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- almostNever :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- almostNever' :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- almostAlways :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- almostAlways' :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- never :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- always :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- someCyclesBy :: Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _someCyclesBy :: Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- somecyclesBy :: Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- someCycles :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- somecycles :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- brak :: Pattern a -> Pattern a
- iter :: Pattern Int -> Pattern c -> Pattern c
- _iter :: Int -> Pattern a -> Pattern a
- iter' :: Pattern Int -> Pattern c -> Pattern c
- _iter' :: Int -> Pattern a -> Pattern a
- palindrome :: Pattern a -> Pattern a
- fadeOut :: Time -> Pattern a -> Pattern a
- fadeOutFrom :: Time -> Time -> Pattern a -> Pattern a
- fadeIn :: Time -> Pattern a -> Pattern a
- fadeInFrom :: Time -> Time -> Pattern a -> Pattern a
- spread :: (a -> t -> Pattern b) -> [a] -> t -> Pattern b
- slowspread :: (a -> t -> Pattern b) -> [a] -> t -> Pattern b
- fastspread :: (a -> t -> Pattern b) -> [a] -> t -> Pattern b
- spread' :: Monad m => (a -> b -> m c) -> m a -> b -> m c
- spreadChoose :: (t -> t1 -> Pattern b) -> [t] -> t1 -> Pattern b
- spreadr :: (t -> t1 -> Pattern b) -> [t] -> t1 -> Pattern b
- ifp :: (Int -> Bool) -> (Pattern a -> Pattern a) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- wedge :: Pattern Time -> Pattern a -> Pattern a -> Pattern a
- _wedge :: Time -> Pattern a -> Pattern a -> Pattern a
- whenmod :: Pattern Time -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _whenmod :: Time -> Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- superimpose :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- trunc :: Pattern Time -> Pattern a -> Pattern a
- _trunc :: Time -> Pattern a -> Pattern a
- linger :: Pattern Time -> Pattern a -> Pattern a
- _linger :: Time -> Pattern a -> Pattern a
- within :: (Time, Time) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- withinArc :: Arc -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- within' :: (Time, Time) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- revArc :: (Time, Time) -> Pattern a -> Pattern a
- euclid :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a
- _euclid :: Int -> Int -> Pattern a -> Pattern a
- euclidFull :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a -> Pattern a
- _euclidBool :: Int -> Int -> Pattern Bool
- _euclid' :: Int -> Int -> Pattern a -> Pattern a
- euclidOff :: Pattern Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a
- eoff :: Pattern Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a
- _euclidOff :: Int -> Int -> Int -> Pattern a -> Pattern a
- euclidOffBool :: Pattern Int -> Pattern Int -> Pattern Int -> Pattern Bool -> Pattern Bool
- _euclidOffBool :: Int -> Int -> Int -> Pattern Bool -> Pattern Bool
- distrib :: [Pattern Int] -> Pattern a -> Pattern a
- _distrib :: [Int] -> Pattern a -> Pattern a
- euclidInv :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a
- _euclidInv :: Int -> Int -> Pattern a -> Pattern a
- index :: Real b => b -> Pattern b -> Pattern c -> Pattern c
- rot :: Ord a => Pattern Int -> Pattern a -> Pattern a
- _rot :: Ord a => Int -> Pattern a -> Pattern a
- segment :: Pattern Time -> Pattern a -> Pattern a
- _segment :: Time -> Pattern a -> Pattern a
- discretise :: Pattern Time -> Pattern a -> Pattern a
- fit :: Pattern Int -> [a] -> Pattern Int -> Pattern a
- _fit :: Int -> [a] -> Pattern Int -> Pattern a
- permstep :: RealFrac b => Int -> [a] -> Pattern b -> Pattern a
- struct :: Pattern Bool -> Pattern a -> Pattern a
- substruct :: Pattern Bool -> Pattern b -> Pattern b
- randArcs :: Int -> Pattern [Arc]
- randStruct :: Int -> Pattern Int
- substruct' :: Pattern Int -> Pattern a -> Pattern a
- stripe :: Pattern Int -> Pattern a -> Pattern a
- _stripe :: Int -> Pattern a -> Pattern a
- slowstripe :: Pattern Int -> Pattern a -> Pattern a
- parseLMRule :: String -> [(String, String)]
- parseLMRule' :: String -> [(Char, String)]
- lindenmayer :: Int -> String -> String -> String
- lindenmayerI :: Num b => Int -> String -> String -> [b]
- runMarkov :: Int -> [[Double]] -> Int -> Time -> [Int]
- markovPat :: Pattern Int -> Pattern Int -> [[Double]] -> Pattern Int
- _markovPat :: Int -> Int -> [[Double]] -> Pattern Int
- mask :: Pattern Bool -> Pattern a -> Pattern a
- enclosingArc :: [Arc] -> Arc
- stretch :: Pattern a -> Pattern a
- fit' :: Pattern Time -> Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a
- chunk :: Pattern Int -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b
- _chunk :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b
- chunk' :: Integral a1 => Pattern a1 -> (Pattern a2 -> Pattern a2) -> Pattern a2 -> Pattern a2
- _chunk' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b
- inside :: Pattern Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a
- _inside :: Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a
- outside :: Pattern Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a
- _outside :: Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a
- loopFirst :: Pattern a -> Pattern a
- timeLoop :: Pattern Time -> Pattern a -> Pattern a
- seqPLoop :: [(Time, Time, Pattern a)] -> Pattern a
- toScale :: Num a => [a] -> Pattern Int -> Pattern a
- toScale' :: Num a => Int -> [a] -> Pattern Int -> Pattern a
- swingBy :: Pattern Time -> Pattern Time -> Pattern a -> Pattern a
- swing :: Pattern Time -> Pattern a -> Pattern a
- cycleChoose :: [a] -> Pattern a
- _rearrangeWith :: Pattern Int -> Int -> Pattern a -> Pattern a
- shuffle :: Pattern Int -> Pattern a -> Pattern a
- _shuffle :: Int -> Pattern a -> Pattern a
- scramble :: Pattern Int -> Pattern a -> Pattern a
- _scramble :: Int -> Pattern a -> Pattern a
- randrun :: Int -> Pattern Int
- seqP :: [(Time, Time, Pattern a)] -> Pattern a
- ur :: Time -> Pattern String -> [(String, Pattern a)] -> [(String, Pattern a -> Pattern a)] -> Pattern a
- inhabit :: [(String, Pattern a)] -> Pattern String -> Pattern a
- spaceOut :: [Time] -> Pattern a -> Pattern a
- flatpat :: Pattern [a] -> Pattern a
- layer :: [a -> Pattern b] -> a -> Pattern b
- arpeggiate :: Pattern a -> Pattern a
- arpg :: Pattern a -> Pattern a
- arpWith :: ([EventF (ArcF Time) a] -> [EventF (ArcF Time) b]) -> Pattern a -> Pattern b
- arp :: Pattern String -> Pattern a -> Pattern a
- _arp :: String -> Pattern a -> Pattern a
- rolled :: Pattern a -> Pattern a
- rolledBy :: Pattern (Ratio Integer) -> Pattern a -> Pattern a
- rolledWith :: Ratio Integer -> Pattern a -> Pattern a
- ply :: Pattern Rational -> Pattern a -> Pattern a
- _ply :: Rational -> Pattern a -> Pattern a
- plyWith :: (Ord t, Num t) => Pattern t -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _plyWith :: (Ord t, Num t) => t -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- press :: Pattern a -> Pattern a
- pressBy :: Pattern Time -> Pattern a -> Pattern a
- _pressBy :: Time -> Pattern a -> Pattern a
- sew :: Pattern Bool -> Pattern a -> Pattern a -> Pattern a
- stitch :: Pattern Bool -> Pattern a -> Pattern a -> Pattern a
- while :: Pattern Bool -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- stutter :: Integral i => i -> Time -> Pattern a -> Pattern a
- jux :: (Pattern ValueMap -> Pattern ValueMap) -> Pattern ValueMap -> Pattern ValueMap
- juxcut :: (Pattern ValueMap -> Pattern ValueMap) -> Pattern ValueMap -> Pattern ValueMap
- juxcut' :: [t -> Pattern ValueMap] -> t -> Pattern ValueMap
- jux' :: [t -> Pattern ValueMap] -> t -> Pattern ValueMap
- jux4 :: (Pattern ValueMap -> Pattern ValueMap) -> Pattern ValueMap -> Pattern ValueMap
- juxBy :: Pattern Double -> (Pattern ValueMap -> Pattern ValueMap) -> Pattern ValueMap -> Pattern ValueMap
- pick :: String -> Int -> String
- samples :: Applicative f => f String -> f Int -> f String
- samples' :: Applicative f => f String -> f Int -> f String
- spreadf :: [a -> Pattern b] -> a -> Pattern b
- stackwith :: Unionable a => Pattern a -> [Pattern a] -> Pattern a
- range :: Num a => Pattern a -> Pattern a -> Pattern a -> Pattern a
- _range :: (Functor f, Num b) => b -> b -> f b -> f b
- rangex :: (Functor f, Floating b) => b -> b -> f b -> f b
- off :: Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _off :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- offadd :: Num a => Pattern Time -> Pattern a -> Pattern a -> Pattern a
- step :: String -> String -> Pattern String
- steps :: [(String, String)] -> Pattern String
- step' :: [String] -> String -> Pattern String
- ghost'' :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- ghostWith :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- ghost' :: Time -> Pattern ValueMap -> Pattern ValueMap
- ghost :: Pattern ValueMap -> Pattern ValueMap
- tabby :: Int -> Pattern a -> Pattern a -> Pattern a
- select :: Pattern Double -> [Pattern a] -> Pattern a
- _select :: Double -> [Pattern a] -> Pattern a
- selectF :: Pattern Double -> [Pattern a -> Pattern a] -> Pattern a -> Pattern a
- _selectF :: Double -> [Pattern a -> Pattern a] -> Pattern a -> Pattern a
- pickF :: Pattern Int -> [Pattern a -> Pattern a] -> Pattern a -> Pattern a
- _pickF :: Int -> [Pattern a -> Pattern a] -> Pattern a -> Pattern a
- contrast :: (ControlPattern -> ControlPattern) -> (ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern -> ControlPattern
- contrastBy :: (a -> Value -> Bool) -> (ControlPattern -> Pattern b) -> (ControlPattern -> Pattern b) -> Pattern (Map String a) -> Pattern (Map String Value) -> Pattern b
- contrastRange :: (ControlPattern -> Pattern a) -> (ControlPattern -> Pattern a) -> Pattern (Map String (Value, Value)) -> ControlPattern -> Pattern a
- fix :: (ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern -> ControlPattern
- unfix :: (ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern -> ControlPattern
- fixRange :: (ControlPattern -> Pattern ValueMap) -> Pattern (Map String (Value, Value)) -> ControlPattern -> ControlPattern
- unfixRange :: (ControlPattern -> Pattern ValueMap) -> Pattern (Map String (Value, Value)) -> ControlPattern -> ControlPattern
- quantise :: (Functor f, RealFrac b) => b -> f b -> f b
- qfloor :: (Functor f, RealFrac b) => b -> f b -> f b
- qceiling :: (Functor f, RealFrac b) => b -> f b -> f b
- qround :: (Functor f, RealFrac b) => b -> f b -> f b
- inv :: Functor f => f Bool -> f Bool
- mono :: Pattern a -> Pattern a
- smooth :: Fractional a => Pattern a -> Pattern a
- swap :: Eq a => [(a, b)] -> Pattern a -> Pattern b
- snowball :: Int -> (Pattern a -> Pattern a -> Pattern a) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- soak :: Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- deconstruct :: Int -> Pattern String -> String
- bite :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a
- _bite :: Int -> Pattern Int -> Pattern a -> Pattern a
- squeeze :: Pattern Int -> [Pattern a] -> Pattern a
- squeezeJoinUp :: Pattern ControlPattern -> ControlPattern
- _chew :: Int -> Pattern Int -> ControlPattern -> ControlPattern
- chew :: Pattern Int -> Pattern Int -> ControlPattern -> ControlPattern
- __binary :: Bits b => Int -> b -> [Bool]
- _binary :: Bits b => Int -> b -> Pattern Bool
- _binaryN :: Int -> Pattern Int -> Pattern Bool
- binaryN :: Pattern Int -> Pattern Int -> Pattern Bool
- binary :: Pattern Int -> Pattern Bool
- ascii :: Pattern String -> Pattern Bool
- grain :: Pattern Double -> Pattern Double -> ControlPattern
- necklace :: Rational -> [Int] -> Pattern Bool
UI
Randomisation
xorwise :: Int -> Int Source #
An implementation of the well-known xorshift
random number generator.
Given a seed number, generates a reasonably random number out of it.
This is an efficient algorithm suitable for use in tight loops and used
to implement the below functions, which are used to implement rand
.
See George Marsaglia (2003). "Xorshift RNGs", in Journal of Statistical Software, pages 8–14.
timeToIntSeed :: RealFrac a => a -> Int Source #
intSeedToRand :: Fractional a => Int -> a Source #
timeToRand :: (RealFrac a, Fractional b) => a -> b Source #
timeToRands :: (RealFrac a, Fractional b) => a -> Int -> [b] Source #
timeToRands' :: Fractional a => Int -> Int -> [a] Source #
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, and
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
(using resetCycles
, setCycle
, or cps
) 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) $ sound "sn sn ~ sn" # gain rand
and with the juxed version shifted backwards for 1024 cycles:
jux (# ((1024 <~) $ gain rand)) $ sound "sn sn ~ sn" # gain rand
brand :: Pattern Bool Source #
Boolean rand - a continuous stream of true/false values, with a 50/50 chance.
brandBy :: Pattern Double -> Pattern Bool Source #
Boolean rand with probability as input, e.g. brandBy 0.25
produces trues 25% of the time.
irand :: Num a => Pattern 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 $ segment 4 $ n (irand 5) # sound "drum"
perlinWith :: Fractional a => Pattern Double -> Pattern a 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
.
perlin :: Fractional a => Pattern a Source #
As perlin
with a suitable choice of input pattern (
).sig
fromRational
perlin2With :: Pattern Double -> Pattern Double -> Pattern Double Source #
perlin2With
is Perlin noise with a 2-dimensional input. This can be
useful for more control over how the randomness repeats (or doesn't).
d1 $ s "[supersaw:-12*32]" # lpf (rangex 60 5000 $ perlin2With (cosine*2) (sine*2)) # lpq 0.3
will generate a smooth random cutoff pattern that repeats every cycle without
any reversals or discontinuities (because the 2D path is a circle).
perlin2
only needs one input because it uses the cycle count as the
second input.
perlin2 :: Pattern Double -> Pattern Double Source #
As perlin2
with a suitable choice of input pattern (
).sig
fromRational
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 (wchoose [("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.
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.
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]"
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"
You can also invoke this behavior in the shorthand notation by specifying a percentage, as a number between 0 and 1, after the question mark:
d1 $ s "bd hh?0.8 bd hh?0.4"
unDegradeBy :: Pattern Double -> Pattern a -> Pattern a Source #
As degradeBy
, but the pattern of probabilities represents the chances to retain rather
than remove the corresponding element.
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.5often
= sometimesBy 0.75rarely
= sometimesBy 0.25almostNever
= sometimesBy 0.1almostAlways
= sometimesBy 0.9
sometimesBy' :: Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
As sometimesBy
, but applies the given transformation to the pattern in its entirety
before filtering its actual appearances. Less efficient than sometimesBy
but may
be useful when the passed pattern transformation depends on properties of the
pattern before probabilities are taken into account.
sometimes'
= sometimesBy' 0.5often'
= sometimesBy' 0.75rarely'
= sometimesBy' 0.25almostNever'
= sometimesBy' 0.1almostAlways'
= 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 #
Never apply a transformation, returning the pattern unmodified.
never = flip const
always :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
Apply the transformation to the pattern unconditionally.
always = id
someCyclesBy :: Pattern Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
someCyclesBy
is a cycle-by-cycle version of
.sometimesBy
someCycles = someCyclesBy 0.5
someCycles :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
someCycles = someCyclesBy 0.5
Pattern transformations
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.
fadeOutFrom :: Time -> Time -> Pattern a -> Pattern a Source #
Alternate version to fadeOut
where you can provide the time from which the fade starts
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. (spreadf
is an alias for spread ($)
.)
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 #
An alias for spread
consistent with fastspread
.
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.
spreadr :: (t -> t1 -> Pattern b) -> [t] -> t1 -> Pattern b Source #
A shorter alias for spreadChoose
.
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
for every _even_ cycle and apply striate
4# 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 :: Pattern 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 :: Pattern Time -> Pattern Time -> (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"
If you give it a negative number, it will linger on the last part of the pattern, instead of the start of it. E.g. to linger on the last quarter:
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"
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"
revArc :: (Time, Time) -> Pattern a -> Pattern a Source #
Reverse the part of the pattern sliced out by the (start, end)
pair.
revArc a = within a rev
euclid :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a Source #
You can use the euclid
function to apply a Euclidean algorithm over a
complex pattern, although the structure of that pattern will be lost:
d1 $ euclid 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 euclid 3 8
. It ends up picking two bd
sounds, a
cp
and missing the sn
entirely.
A negative first argument provides the inverse of the euclidean pattern.
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 as a third parameter in some cases (see euclidOff
).
- (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.
There was once a shorter alias e
for this function. It has been removed, but you
may see references to it in older Tidal code.
_euclidBool :: Int -> Int -> Pattern Bool Source #
Less expressive than euclid
due to its constrained types, but may be more efficient.
euclidOff :: Pattern Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a Source #
As euclid
, but taking a third rotational parameter corresponding to the onset
at which to start the rhythm.
eoff :: Pattern Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a Source #
A shorter alias for euclidOff
.
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 #
Calculates a whole cycle, rotates it, then constrains events to the original query arc.
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
fit :: Pattern 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).
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 Bool -> 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
is 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 n
th stripe starts on a cycle
boundary (in Indian classical terms, the sam).
lindenmayer :: Int -> String -> String -> String Source #
Returns the n
th iteration of a Lindenmayer System with given start sequence.
An 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)
runMarkov :: Int -> [[Double]] -> Int -> Time -> [Int] Source #
runMarkov n tmat xi seed
generates a Markov chain (as a list) of length n
using the transition matrix tmat
starting from initial state xi
, starting
with random numbers generated from seed
Each entry in the chain is the index of state (starting from zero).
Each row of the matrix will be automatically normalized. For example:
runMarkov 8 [[2,3], [1,3]] 0 0
will produce a two-state chain 8 steps long, from initial state 0
, where the
transition probability from state 0->0 is 25, 0->1 is 35, 1->0 is 1/4, and
1->1 is 3/4.
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 :: Pattern Int -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b Source #
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 if chunk number is positive
- from right to left if chunk number is negative
d1 $ chunk 4 (fast 4) $ sound "cp sn arpy [mt lt]"
chunk' :: Integral a1 => Pattern a1 -> (Pattern a2 -> Pattern a2) -> Pattern a2 -> Pattern a2 Source #
DEPRECATED, use chunk
with negative numbers instead
_chunk' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b Source #
DEPRECATED, use _chunk
with negative numbers instead
inside :: Pattern Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a Source #
inside
carries out an operation inside a cycle.
For example, while rev "0 1 2 3 4 5 6 7"
is the same as "7 6 5 4 3 2 1 0"
,
inside 2 rev "0 1 2 3 4 5 6 7"
gives "3 2 1 0 7 6 5 4"
.
outside :: Pattern Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a Source #
outside
is the inverse of the inside
function. outside
applies its function outside the cycle.
Say you have a pattern that takes 4 cycles to repeat and apply the rev function:
d1 $ rev $ cat [s "bd bd sn",s "sn sn bd", s"lt lt sd", s "sd sd bd"]
The above generates:
d1 $ rev $ cat [s "sn bd bd",s "bd sn sn", s "sd lt lt", s "bd sd sd"]
However if you apply outside
:
d1 $ outside 4 (rev) $ cat [s "bd bd sn",s "sn sn bd", s"lt lt sd", s "sd sd bd"]
The result is:
d1 $ rev $ cat [s "bd sd sd", s "sd lt lt", s "sn sn bd", s "bd bd sn"]
toScale :: Num a => [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"
.
This function assumes your scale fits within an
octave; if that's not true, use toScale'
.
toScale = toScale' 12
toScale' :: Num a => Int -> [a] -> Pattern Int -> Pattern a Source #
As toScale
, though allowing scales of arbitrary size.
An example: toScale' 24 [0,4,7,10,14,17] (run 8)
turns into "0 4 7 10 14 17 24 28"
.
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 :: Pattern Time -> Pattern a -> Pattern a Source #
As swingBy
, with the cycle division set to ⅓.
cycleChoose :: [a] -> Pattern a Source #
cycleChoose
is like choose
but only picks a new item from the list
once each cycle
_rearrangeWith :: Pattern Int -> Int -> Pattern a -> Pattern a Source #
Internal function used by shuffle and scramble
shuffle :: Pattern 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 :: Pattern 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.
randrun :: Int -> Pattern Int Source #
randrun n
generates a pattern of random integers less than n
.
The following plays random notes in an octave:
d1 $ s "superhammond!12" # n (fromIntegral $ randrun 13)
Composing patterns
seqP :: [(Time, Time, Pattern a)] -> Pattern a Source #
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))) ]
ur :: Time -> Pattern String -> [(String, Pattern a)] -> [(String, Pattern a -> Pattern a)] -> Pattern a Source #
The ur
function is designed for longer form composition, by allowing you to
create ’patterns of patterns’ in a repeating loop. It takes four parameters:
how long the loop will take, a pattern giving the structure of the composition,
a lookup table for named patterns to feed into that structure, and a second
lookup table for named transformations/effects.
The ur- prefix comes from German and means proto- or original. For a mnemonic device, think of this function as assembling a set of original patterns (ur-patterns) into a larger, newer whole.
Lets say you had three patterns (called a
, b
and c
), and that you wanted
to play them four cycles each, over twelve cycles in total. Here is one way to
do it:
let pats = [ ("a", stack [n "c4 c5 g4 f4 f5 g4 e5 g4" # s "superpiano" # gain "0.7", n "[c3,g4,c4]" # s "superpiano"# gain "0.7" ] ), ("b", stack [n "d4 c5 g4 f4 f5 g4 e5 g4" # s "superpiano" # gain "0.7", n "[d3,a4,d4]" # s "superpiano"# gain "0.7" ] ), ("c", stack [n "f4 c5 g4 f4 f5 g4 e5 g4" # s "superpiano" # gain "0.7", n "[f4,c5,f4]" # s "superpiano"# gain "0.7" ] ) ] in d1 $ ur 12 "a b c" pats []
inhabit :: [(String, Pattern a)] -> Pattern String -> Pattern a Source #
A simpler version of ur
that just provides name-value bindings that are reflected in the provided pattern.
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
.
layer :: [a -> Pattern b] -> a -> Pattern b Source #
layer
takes a list of Pattern
-returning functions and a seed element,
stacking the result of applying the seed element to each function in the list.
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.
arp :: Pattern String -> Pattern a -> Pattern a Source #
The arp
function takes an additional pattern of arpeggiate modes. For example:
d1 $ sound "superpiano" # n (arp "down diverge" "e'7sus4'8")
The different arpeggiate modes are:
up down updown downup up&down down&up converge
diverge disconverge pinkyup pinkyupdown
thumbup thumbupdown-
rolled :: Pattern a -> Pattern a Source #
rolled
plays each note of a chord quickly in order, as opposed to simultaneously; to give a chord a harp-like effect.
This will played from the lowest note to the highest note of the chord:
rolled $ n "c
maj
4" # s "superpiano"
rolled = rolledBy (1/4)
ply :: Pattern Rational -> Pattern a -> Pattern a Source #
ply n
repeats each event n
times within its arc.
plyWith :: (Ord t, Num t) => Pattern t -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
As ply
, but applies a function each time. The applications are compounded.
press :: Pattern a -> Pattern a Source #
Syncopates a rhythm, shifting each event halfway into its arc (aka timespan), e.g. "a b [c d] e"
becomes the equivalent of "[~ a] [~ b] [[~ c] [~ d]] [~ e]"
pressBy :: Pattern Time -> Pattern a -> Pattern a Source #
Like press
, but allows you to specify the amount in which each event is shifted. pressBy 0.5
is the same as press
, while pressBy (1/3)
shifts each event by a third of its arc.
sew :: Pattern Bool -> Pattern a -> Pattern a -> Pattern a Source #
Uses the first (binary) pattern to switch between the following
two patterns. The resulting structure comes from the source patterns, not the
binary pattern. See also stitch
.
stitch :: Pattern Bool -> Pattern a -> Pattern a -> Pattern a Source #
Uses the first (binary) pattern to switch between the following
two patterns. The resulting structure comes from the binary
pattern, not the source patterns. See also sew
.
while :: Pattern Bool -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
A binary pattern is used to conditionally apply a function to a
source pattern. The function is applied when a True
value is
active, and the pattern is let through unchanged when a False
value is active. No events are let through where no binary values
are active.
jux :: (Pattern ValueMap -> Pattern ValueMap) -> Pattern ValueMap -> Pattern ValueMap 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 ValueMap] -> t -> Pattern ValueMap 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 ValueMap -> Pattern ValueMap) -> Pattern ValueMap -> Pattern ValueMap Source #
Multichannel variant of jux
, _not sure what it does_
juxBy :: Pattern Double -> (Pattern ValueMap -> Pattern ValueMap) -> Pattern ValueMap -> Pattern ValueMap 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.
pick :: String -> Int -> String Source #
Given a sample's directory name and number, this generates a string
suitable to pass to fromString
to create a 'Pattern String'.
samples
is a Pattern
-compatible interface to this function.
pick name n = name ++ ":" ++ show n
samples :: Applicative f => f String -> f Int -> f String Source #
Given a pattern of sample directory names and a of pattern indices create a pattern of strings corresponding to the sample at each name-index pair.
An example:
samples "jvbass [~ latibro] [jvbass [latibro jvbass]]" ((1%2)
rotL
slow 6 "[1 6 8 7 3]")
The type signature is more general here, but you can consider this to be a function of type @Pattern String -> Pattern Int -> Pattern String.
samples = liftA2 pick
samples' :: Applicative f => f String -> f Int -> f String Source #
Equivalent to samples
, though the sample specifier pattern
(the f Int
) will be evaluated first. Not a large difference
in the majority of cases.
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)
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 #
Deprecated backwards-compatible alias for ghostWith
.
ghostWith :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
Like ghost'
, but a user-supplied function describes how to alter the pattern.
ghost :: Pattern ValueMap -> Pattern ValueMap Source #
As ghost
, but with the copies set to appear one-eighth of a cycle afterwards.
ghost = ghost' 0.125
tabby :: Int -> Pattern a -> Pattern a -> Pattern a Source #
A more literal weaving than the weave
function. Given tabby threads p1 p
,
parameters representing the threads per cycle and the patterns to weave, 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)
selectF :: Pattern Double -> [Pattern a -> Pattern a] -> Pattern a -> Pattern a Source #
chooses between a list of functions, using a pattern of floats (from 0-1)
pickF :: Pattern Int -> [Pattern a -> Pattern a] -> Pattern a -> Pattern a Source #
chooses between a list of functions, using a pattern of integers
contrast :: (ControlPattern -> ControlPattern) -> (ControlPattern -> ControlPattern) -> ControlPattern -> ControlPattern -> ControlPattern Source #
contrast p f f' p'
splits the control pattern 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 (# crush 3) (# vowel "a") (n "1") $ n "0 1" # s "bd sn" # speed 3
,
the first event will have the vowel effect applied and the second
will have the crush applied.
contrastBy :: (a -> Value -> Bool) -> (ControlPattern -> Pattern b) -> (ControlPattern -> Pattern b) -> Pattern (Map String a) -> Pattern (Map String Value) -> Pattern b Source #
contrastRange :: (ControlPattern -> Pattern a) -> (ControlPattern -> Pattern a) -> Pattern (Map String (Value, Value)) -> ControlPattern -> Pattern a Source #
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.
fixRange :: (ControlPattern -> Pattern ValueMap) -> Pattern (Map String (Value, Value)) -> ControlPattern -> ControlPattern Source #
unfixRange :: (ControlPattern -> Pattern ValueMap) -> Pattern (Map String (Value, Value)) -> ControlPattern -> ControlPattern Source #
quantise :: (Functor f, RealFrac b) => b -> f b -> f b Source #
Limits values in a Pattern (or other Functor) to n equally spaced divisions of 1.
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.
smooth :: Fractional a => Pattern a -> Pattern a Source #
smooth
receives a pattern of numbers and linearly goes from one to the next, passing through all of them. As time is cycle-based, after reaching the last number in the pattern, it will smoothly go to the first one again.
d1 $ sound "bd*4" # pan (slow 4 $ smooth "0 1 0.5 1")
This sound will pan gradually from left to right, then to the center, then to the right again, and finally comes back to the left.
swap :: Eq a => [(a, b)] -> Pattern a -> Pattern b Source #
Looks up values from a list of tuples, in order to swap values in the given pattern
snowball :: Int -> (Pattern a -> Pattern a -> Pattern a) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
snowball
takes a function that can combine patterns (like +
),
a function that transforms a pattern (like slow
),
a depth, and a starting pattern,
it will then transform the pattern and combine it with the last transformation until the depth is reached.
This is like putting an effect (like a filter) in the feedback of a delay line; each echo is more affected.
d1 $ note (scale "hexDorian" $ snowball 8 (+) (slow 2 . rev) "0 ~ . -1 . 5 3 4 . ~ -2") # s "gtr"
deconstruct :: Int -> Pattern String -> String Source #
construct n p
breaks p
into pieces and then reassembles them
so that it fits into n
steps.
bite :: Pattern Int -> Pattern Int -> Pattern a -> Pattern a Source #
bite n ipat pat
slices a pattern pat
into n
pieces, then uses the
ipat
pattern of integers to index into those slices. So bite 4 "0 2*2" (run
8)
is the same as "[0 1] [4 5]*2"
.
squeeze :: Pattern Int -> [Pattern a] -> Pattern a Source #
squeeze
uses a pattern of integers to index into a list of patterns.
_chew :: Int -> Pattern Int -> ControlPattern -> ControlPattern Source #
chew :: Pattern Int -> Pattern Int -> ControlPattern -> ControlPattern Source #
chew
works the same as bite
, but speeds up/slows down playback of sounds as well as squeezing/contracting the slices of the provided pattern.
necklace :: Rational -> [Int] -> Pattern Bool Source #
For specifying a boolean pattern according to a list of offsets (aka inter-onset intervals). For example `necklace 12 [4,2]` is the same as "t f f f t f t f f f t f". That is, 12 steps per cycle, with true values alternating between every 4 and every 2 steps.