Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Pattern a = Pattern {}
- noOv :: String -> a
- showTime :: (Show a, Integral a) => Ratio a -> String
- showArc :: Arc -> String
- showEvent :: Show a => Event a -> String
- unwrap :: Pattern (Pattern a) -> Pattern a
- atom :: a -> Pattern a
- silence :: Pattern a
- withQueryArc :: (Arc -> Arc) -> Pattern a -> Pattern a
- withQueryTime :: (Time -> Time) -> Pattern a -> Pattern a
- withResultArc :: (Arc -> Arc) -> Pattern a -> Pattern a
- withResultTime :: (Time -> Time) -> Pattern a -> Pattern a
- withEvent :: (Event a -> Event b) -> Pattern a -> Pattern b
- timedValues :: Pattern a -> Pattern (Arc, a)
- overlay :: Pattern a -> Pattern a -> Pattern a
- stack :: [Pattern a] -> Pattern a
- append :: Pattern a -> Pattern a -> Pattern a
- append' :: Pattern a -> Pattern a -> Pattern a
- fastcat :: [Pattern a] -> Pattern a
- splitAtSam :: Pattern a -> Pattern a
- slowcat :: [Pattern a] -> Pattern a
- cat :: [Pattern a] -> Pattern a
- listToPat :: [a] -> Pattern a
- patToList :: Pattern a -> [a]
- maybeListToPat :: [Maybe a] -> Pattern a
- run :: (Enum a, Num a) => Pattern a -> Pattern a
- _run :: (Enum a, Num a) => a -> Pattern a
- scan :: (Enum a, Num a) => Pattern a -> Pattern a
- _scan :: (Enum a, Num a) => a -> Pattern a
- temporalParam :: (a -> Pattern b -> Pattern c) -> Pattern a -> Pattern b -> Pattern c
- temporalParam2 :: (a -> b -> Pattern c -> Pattern d) -> Pattern a -> Pattern b -> Pattern c -> Pattern d
- temporalParam3 :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e
- temporalParam' :: (a -> Pattern b -> Pattern c) -> Pattern a -> Pattern b -> Pattern c
- temporalParam2' :: (a -> b -> Pattern c -> Pattern d) -> Pattern a -> Pattern b -> Pattern c -> Pattern d
- temporalParam3' :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e
- fast :: Pattern Time -> Pattern a -> Pattern a
- _fast :: Time -> Pattern a -> Pattern a
- fast' :: Pattern Time -> Pattern a -> Pattern a
- density :: Pattern Time -> Pattern a -> Pattern a
- _density :: Time -> Pattern a -> Pattern a
- fastGap :: Time -> Pattern a -> Pattern a
- densityGap :: Time -> Pattern a -> Pattern a
- slow :: Pattern Time -> Pattern a -> Pattern a
- sparsity :: Pattern Time -> Pattern a -> Pattern a
- slow' :: Pattern Time -> Pattern a -> Pattern a
- _slow :: Time -> Pattern a -> Pattern a
- rotL :: Time -> Pattern a -> Pattern a
- (<~) :: Pattern Time -> Pattern a -> Pattern a
- rotR :: Time -> Pattern a -> Pattern a
- (~>) :: Pattern Time -> 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
- rev :: Pattern a -> Pattern a
- palindrome :: Pattern a -> Pattern a
- when :: (Int -> Bool) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- whenT :: (Time -> Bool) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- playWhen :: (Time -> Bool) -> Pattern a -> Pattern a
- playFor :: Time -> Time -> Pattern a -> Pattern a
- seqP :: [(Time, Time, Pattern a)] -> Pattern a
- every :: Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _every :: Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- every' :: Pattern Int -> Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _every' :: Int -> Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- foldEvery :: [Int] -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- sig :: (Time -> a) -> Pattern a
- sinewave :: Pattern Double
- sine :: Pattern Double
- cosine :: Pattern Double
- sinerat :: Pattern Rational
- ratsine :: Pattern Rational
- sineAmp :: Double -> Pattern Double
- sawwave :: Pattern Double
- saw :: Pattern Double
- sawrat :: Pattern Rational
- triwave :: Pattern Double
- tri :: Pattern Double
- trirat :: Pattern Rational
- squarewave :: Pattern Double
- square :: Pattern Double
- sinewave1 :: Pattern Double
- sine1 :: Pattern Double
- sinerat1 :: Pattern Rational
- sineAmp1 :: Double -> Pattern Double
- sawwave1 :: Pattern Double
- saw1 :: Pattern Double
- sawrat1 :: Pattern Rational
- triwave1 :: Pattern Double
- tri1 :: Pattern Double
- trirat1 :: Pattern Rational
- squarewave1 :: Pattern Double
- square1 :: Pattern Double
- envL :: Pattern Double
- envLR :: Pattern Double
- envEq :: Pattern Double
- envEqR :: Pattern Double
- fadeOut :: Time -> Pattern a -> Pattern a
- fadeOut' :: Time -> Time -> Pattern a -> Pattern a
- fadeIn' :: Time -> Time -> Pattern a -> Pattern a
- fadeIn :: 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
- filterValues :: (a -> Bool) -> Pattern a -> Pattern a
- filterJust :: Pattern (Maybe a) -> Pattern a
- filterOnsets :: Pattern a -> Pattern a
- filterStartInRange :: Pattern a -> Pattern a
- filterOnsetsInRange :: Pattern a -> Pattern a
- seqToRelOnsetDeltas :: Arc -> Pattern a -> [(Double, Double, a)]
- segment :: Pattern a -> Pattern [a]
- segment' :: [Event a] -> [Event a]
- split :: Time -> [Event a] -> [Event a]
- points :: [Event a] -> [Time]
- groupByTime :: [Event a] -> [Event [a]]
- ifp :: (Int -> Bool) -> (Pattern a -> Pattern a) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- rand :: Pattern Double
- timeToRand :: RealFrac r => r -> Double
- irand :: Num a => Int -> Pattern a
- choose :: [a] -> Pattern a
- degradeBy :: Pattern Double -> Pattern a -> Pattern a
- _degradeBy :: 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 :: Double -> (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
- rarely :: (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
- never :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- always :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- someCyclesBy :: Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- somecyclesBy :: Double -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- someCycles :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- degrade :: Pattern a -> Pattern a
- wedge :: Time -> Pattern a -> Pattern a -> Pattern a
- timeCat :: [(Time, Pattern a)] -> Pattern a
- whenmod :: Int -> Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- superimpose :: (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- splitQueries :: 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
- zoom :: Arc -> Pattern a -> Pattern a
- compress :: Arc -> Pattern a -> Pattern a
- sliceArc :: Arc -> Pattern a -> Pattern a
- within :: Arc -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- revArc :: Arc -> Pattern a -> Pattern a
- e :: Int -> Int -> Pattern a -> Pattern a
- e' :: Int -> Int -> Pattern a -> Pattern a
- index :: Real b => b -> Pattern b -> Pattern c -> Pattern c
- prrw :: (a -> b -> c) -> Int -> (Time, Time) -> Pattern a -> Pattern b -> Pattern c
- prr :: Int -> (Time, Time) -> Pattern String -> Pattern b -> Pattern b
- preplace :: (Time, Time) -> Pattern String -> Pattern b -> Pattern b
- prep :: (Time, Time) -> Pattern String -> Pattern b -> Pattern b
- preplace1 :: Pattern String -> Pattern b -> Pattern b
- preplaceWith :: (a -> b -> c) -> (Time, Time) -> Pattern a -> Pattern b -> Pattern c
- prw :: (a -> b -> c) -> (Time, Time) -> Pattern a -> Pattern b -> Pattern c
- preplaceWith1 :: (a -> b -> c) -> Pattern a -> Pattern b -> Pattern c
- prw1 :: (a -> b -> c) -> Pattern a -> Pattern b -> Pattern c
- (<~>) :: Pattern String -> Pattern b -> Pattern b
- protate :: Time -> Int -> Pattern a -> Pattern a
- prot :: Time -> Int -> Pattern a -> Pattern a
- prot1 :: Int -> Pattern a -> Pattern a
- (<<~) :: Int -> Pattern a -> Pattern a
- (~>>) :: Int -> Pattern a -> Pattern a
- pequal :: Ord a => Time -> Pattern a -> Pattern a -> Bool
- discretise :: Time -> Pattern a -> Pattern a
- discretise' :: Time -> Pattern a -> Pattern a
- _discretise :: Time -> Pattern a -> Pattern a
- randcat :: [Pattern a] -> Pattern a
- fit :: Int -> [a] -> Pattern Int -> Pattern a
- permstep :: RealFrac b => Int -> [a] -> Pattern b -> Pattern a
- struct :: Pattern String -> Pattern a -> Pattern a
- substruct :: Pattern String -> Pattern b -> Pattern b
- compressTo :: Arc -> Pattern a -> Pattern a
- 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
- unwrap' :: Pattern (Pattern a) -> Pattern a
- mask :: Pattern a -> Pattern b -> Pattern b
- enclosingArc :: [Arc] -> Arc
- stretch :: Pattern a -> Pattern a
- fit' :: Pattern Time -> Int -> Pattern Int -> Pattern Int -> Pattern a -> Pattern a
- chunk :: Integer -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b
- runWith :: Integer -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b
- chunk' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b
- runWith' :: Integral a => a -> (Pattern b -> Pattern b) -> Pattern b -> Pattern b
- inside :: Pattern Time -> (Pattern a1 -> Pattern a) -> Pattern a1 -> Pattern a
- outside :: Pattern 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' :: Int -> [Int] -> Pattern Int -> Pattern Int
- toScale :: [Int] -> Pattern Int -> Pattern Int
- swingBy :: Pattern Time -> Pattern Time -> Pattern a -> Pattern a
- swing :: Pattern Time -> Pattern a -> Pattern a
- cycleChoose :: [a] -> Pattern a
- shuffle :: Int -> Pattern a -> Pattern a
- scramble :: Int -> Pattern a -> Pattern a
- ur :: Time -> Pattern String -> [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
- repeatCycles :: Int -> Pattern a -> Pattern a
- spaceOut :: [Time] -> Pattern a -> Pattern a
- flatpat :: Pattern [a] -> Pattern a
- layer :: [a -> Pattern b] -> a -> Pattern b
- breakUp :: Pattern a -> Pattern a
- fill :: Pattern a -> Pattern a -> Pattern a
Documentation
The pattern datatype, a function from a time Arc
to Event
values. For discrete patterns, this returns the events which are
active during that time. For continuous patterns, events with
values for the midpoint of the given Arc
is returned.
Monad Pattern Source # | |
Functor Pattern Source # | |
Applicative Pattern Source # |
|
Enum a => Enum (Pattern a) Source # | |
Eq (Pattern a) Source # | |
Floating a => Floating (Pattern a) Source # | |
Fractional a => Fractional (Pattern a) Source # | |
Integral a => Integral (Pattern a) Source # | |
Num a => Num (Pattern a) Source # | |
Ord a => Ord (Pattern a) Source # | |
(Num a, Ord a) => Real (Pattern a) Source # | |
RealFloat a => RealFloat (Pattern a) Source # | |
RealFrac a => RealFrac (Pattern a) Source # | |
Show a => Show (Pattern a) Source # |
|
Monoid (Pattern a) Source # |
|
showTime :: (Show a, Integral a) => Ratio a -> String Source #
converts a ratio into human readable string, e.g. 1/3
showEvent :: Show a => Event a -> String Source #
converts an event into human readable string, e.g. ("bd" 14 23)
withQueryArc :: (Arc -> Arc) -> Pattern a -> Pattern a Source #
withQueryArc f p
returns a new Pattern
with function f
applied to the Arc
values passed to the original Pattern
p
.
withQueryTime :: (Time -> Time) -> Pattern a -> Pattern a Source #
withQueryTime f p
returns a new Pattern
with function f
applied to the both the start and end Time
of the Arc
passed to
Pattern
p
.
withResultArc :: (Arc -> Arc) -> Pattern a -> Pattern a Source #
withResultArc f p
returns a new Pattern
with function f
applied to the Arc
values in the events returned from the
original Pattern
p
.
withResultTime :: (Time -> Time) -> Pattern a -> Pattern a Source #
withResultTime f p
returns a new Pattern
with function f
applied to the both the start and end Time
of the Arc
values in
the events returned from the original Pattern
p
.
withEvent :: (Event a -> Event b) -> Pattern a -> Pattern b Source #
withEvent f p
returns a new Pattern
with events mapped over
function f
.
timedValues :: Pattern a -> Pattern (Arc, a) Source #
timedValues p
returns a new Pattern
where values are turned
into tuples of Arc
and value.
overlay :: Pattern a -> Pattern a -> Pattern a Source #
overlay
combines two Pattern
s into a new pattern, so that
their events are combined over time. This is the same as the infix
operator <>
.
stack :: [Pattern a] -> Pattern a Source #
stack
combines a list of Pattern
s into a new pattern, so that
their events are combined over time.
append :: Pattern a -> Pattern a -> Pattern a Source #
append
combines two patterns Pattern
s into a new pattern, so
that the events of the second pattern are appended to those of the
first pattern, within a single cycle
append' :: Pattern a -> Pattern a -> Pattern a Source #
append'
does the same as append
, but over two cycles, so that
the cycles alternate between the two patterns.
fastcat :: [Pattern a] -> Pattern a Source #
fastcat
returns a new pattern which interlaces the cycles of the
given patterns, within a single cycle. It's the equivalent of
append
, but with a list of patterns.
splitAtSam :: Pattern a -> Pattern a Source #
slowcat :: [Pattern a] -> Pattern a Source #
slowcat
does the same as fastcat
, but maintaining the duration of
the original patterns. It is the equivalent of append'
, but with
a list of patterns.
listToPat :: [a] -> Pattern a Source #
listToPat
turns the given list of values to a Pattern, which
cycles through the list.
maybeListToPat :: [Maybe a] -> Pattern a Source #
maybeListToPat
is similar to listToPat
, but allows values to
be optional using the Maybe
type, so that Nothing
results in
gaps in the pattern.
run :: (Enum a, Num a) => Pattern a -> Pattern a Source #
run
n
returns a pattern representing a cycle of numbers from 0
to n-1
.
temporalParam2 :: (a -> b -> Pattern c -> Pattern d) -> Pattern a -> Pattern b -> Pattern c -> Pattern d Source #
temporalParam3 :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e Source #
temporalParam2' :: (a -> b -> Pattern c -> Pattern d) -> Pattern a -> Pattern b -> Pattern c -> Pattern d Source #
temporalParam3' :: (a -> b -> c -> Pattern d -> Pattern e) -> Pattern a -> Pattern b -> Pattern c -> Pattern d -> Pattern e Source #
fast :: Pattern Time -> Pattern a -> Pattern a Source #
fast
(also known as density
) returns the given pattern with speed
(or density) increased by the given Time
factor. Therefore fast 2 p
will return a pattern that is twice as fast, and fast (1/3) p
will return one three times as slow.
density :: Pattern Time -> Pattern a -> Pattern a Source #
density
is an alias of fast
. fast
is quicker to type, but
density
is its old name so is used in a lot of examples.
fastGap :: Time -> Pattern a -> Pattern a Source #
fastGap
(also known as densityGap
is similar to fast
but maintains its cyclic
alignment. For example, fastGap 2 p
would squash the events in
pattern p
into the first half of each cycle (and the second
halves would be empty).
slow :: Pattern Time -> Pattern a -> Pattern a Source #
slow
does the opposite of fast
, i.e. slow 2 p
will return a
pattern that is half the speed.
rotL :: Time -> Pattern a -> Pattern a Source #
The <~
operator shifts (or rotates) a pattern to the left (or
counter-clockwise) by the given Time
value. For example
(1%16) <~ p
will return a pattern with all the events moved
one 16th of a cycle to the left.
rotR :: Time -> Pattern a -> Pattern a Source #
The ~>
operator does the same as <~
but shifts events to the
right (or clockwise) rather than to the left.
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.
rev :: Pattern a -> Pattern a Source #
rev p
returns p
with the event positions in each cycle
reversed (or mirrored).
palindrome :: Pattern a -> Pattern a Source #
palindrome p
applies rev
to p
every other cycle, so that
the pattern alternates between forwards and backwards.
when :: (Int -> Bool) -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
Only when
the given test function returns True
the given pattern transformation is applied. The test function will be called with the current cycle as a number.
d1 $ when ((elem '4').show) (striate 4) $ sound "hh hc"
The above will only apply `striate 4` to the pattern if the current cycle number contains the number 4. So the fourth cycle will be striated and the fourteenth and so on. Expect lots of striates after cycle number 399.
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))) ]
every :: Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
every n f p
applies the function f
to p
, but only affects
every n
cycles.
every' :: Pattern Int -> Pattern Int -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
every n o f'
is like every n f
with an offset of o
cycles
foldEvery :: [Int] -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
foldEvery ns f p
applies the function f
to p
, and is applied for
each cycle in ns
.
sig :: (Time -> a) -> Pattern a Source #
sig f
takes a function from time to values, and turns it into a
Pattern
.
sinewave :: Pattern Double Source #
sinewave
returns a Pattern
of continuous Double
values following a
sinewave with frequency of one cycle, and amplitude from 0 to 1.
sinerat :: Pattern Rational Source #
sinerat
is equivalent to sinewave
for Rational
values,
suitable for use as Time
offsets.
sineAmp :: Double -> Pattern Double Source #
sineAmp d
returns sinewave
with its amplitude offset by d
.
Deprecated, as these days you can simply do e.g. (sine + 0.5)
sawwave :: Pattern Double Source #
sawwave
is the equivalent of sinewave
for (ascending) sawtooth waves.
sawrat :: Pattern Rational Source #
sawrat
is the same as sawwave
but returns Rational
values
suitable for use as Time
offsets.
trirat :: Pattern Rational Source #
trirat
is the same as triwave
but returns Rational
values
suitable for use as Time
offsets.
squarewave :: Pattern Double Source #
squarewave1
is the equivalent of sinewave
for square waves.
envL :: Pattern Double Source #
envL
is a Pattern
of continuous Double
values, representing
a linear interpolation between 0 and 1 during the first cycle, then
staying constant at 1 for all following cycles. Possibly only
useful if you're using something like the retrig function defined
in tidal.el.
spread :: (a -> t -> Pattern b) -> [a] -> t -> Pattern b Source #
(The above is difficult to describe, if you don't understand Haskell, just ignore it and read the below..)
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
.
filterOnsets :: Pattern a -> Pattern a Source #
filterStartInRange :: Pattern a -> Pattern a Source #
filterOnsetsInRange :: Pattern a -> Pattern a Source #
groupByTime :: [Event a] -> [Event [a]] 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
.
rand :: Pattern Double Source #
rand
generates a continuous pattern of (pseudo-)random, floating point numbers between `0` and `1`.
d1 $ sound "bd*8" # pan rand
pans bass drums randomly
d1 $ sound "sn sn ~ sn" # gain rand
makes the snares' randomly loud and quiet.
Numbers coming from this pattern are random, but dependent on time. So if you reset time via `cps (-1)` 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:
d1 $ jux (|+| gain rand) $ sound "sn sn ~ sn" # gain rand
and with the juxed version shifted backwards for 1024 cycles:
d1 $ jux (|+| ((1024 <~) $ gain rand)) $ sound "sn sn ~ sn" # gain rand
timeToRand :: RealFrac r => r -> Double Source #
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"
choose :: [a] -> Pattern a Source #
Randomly picks an element from the given list
d1 $ sound (samples "xx(3,8)" (tom $ choose ["a", "e", "g", "c"]))
plays a melody randomly choosing one of the four notes "a", "e", "g", "c".
sometimesBy :: 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
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]"
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"
splitQueries :: Pattern a -> Pattern a Source #
splitQueries p
wraps p
to ensure that it does not get
queries that span arcs. For example `arc p (0.5, 1.5)` would be
turned into two queries, `(0.5,1)` and `(1,1.5)`, and the results
combined. Being able to assume queries don't span cycles often
makes transformations easier to specify.
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"
zoom :: Arc -> Pattern a -> Pattern a Source #
Plays a portion of a pattern, specified by a beginning and end arc of time. The new resulting pattern is played over the time period of the original pattern:
d1 $ zoom (0.25, 0.75) $ sound "bd*2 hh*3 [sn bd]*2 drum"
In the pattern above, zoom
is used with an arc from 25% to 75%. It is equivalent to this pattern:
d1 $ sound "hh*3 [sn bd]*2"
within :: Arc -> (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"
e :: Int -> 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.
prrw :: (a -> b -> c) -> Int -> (Time, Time) -> Pattern a -> Pattern b -> Pattern c Source #
prrw f rot (blen, vlen) beatPattern valuePattern
: pattern rotate/replace.
prr :: Int -> (Time, Time) -> Pattern String -> Pattern b -> Pattern b Source #
prr rot (blen, vlen) beatPattern valuePattern
: pattern rotate/replace.
preplace :: (Time, Time) -> Pattern String -> Pattern b -> Pattern b Source #
preplace (blen, plen) beats values
combines the timing of beats
with the values
of values
. Other ways of saying this are:
* sequential convolution
* values
quantized to beats
.
Examples:
d1 $ sound $ preplace (1,1) "x [~ x] x x" "bd sn" d1 $ sound $ preplace (1,1) "x(3,8)" "bd sn" d1 $ sound $ "x(3,8)" ~ "bd sn" d1 $ sound "[jvbass jvbass:5]*3" |+| (shape $ "1 1 1 1 1" ~ "0.2 0.9")
It is assumed the pattern fits into a single cycle. This works well with
pattern literals, but not always with patterns defined elsewhere. In those cases
use preplace
and provide desired pattern lengths:
@
let p = slow 2 $ "x x x"
d1 $ sound $ preplace (2,1) p "bd sn" @
prep :: (Time, Time) -> Pattern String -> Pattern b -> Pattern b Source #
prep
is an alias for preplace.
protate :: Time -> Int -> Pattern a -> Pattern a Source #
protate len rot p
rotates pattern p
by rot
beats to the left.
len
: length of the pattern, in cycles.
Example: d1 $ every 4 (protate 2 (-1)) $ slow 2 $ sound "bd hh hh hh"
(<<~) :: Int -> Pattern a -> Pattern a Source #
The <<~
operator rotates a unit pattern to the left, similar to <~
,
but by events rather than linear time. The timing of the pattern remains constant:
d1 $ (1 <<~) $ sound "bd ~ sn hh" -- will become d1 $ sound "sn ~ hh bd"
pequal :: Ord a => Time -> Pattern a -> Pattern a -> Bool Source #
pequal cycles p1 p2
: quickly test if p1
and p2
are the same.
discretise :: Time -> Pattern a -> Pattern a Source #
discretise n p
: samples
the pattern p
at a rate of n
events per cycle. Useful for turning a continuous pattern into a
discrete one.
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).
struct :: Pattern String -> Pattern a -> Pattern a Source #
struct a b
: structures pattern b
in terms of a
.
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 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.
for example:
lindenmayer 1 "a:b,b:ab" "ab" -> "bab"
mask :: Pattern a -> Pattern b -> Pattern b 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" :: Pattern Bool) (slowcat ["can*8", "[cp*4 sn*4, jvbass*16]"] )) # n (run 8)
Detail: It is currently needed to explicitly _tell_ Tidal that the mask itself is a `Pattern Bool` as it cannot infer this by itself, otherwise it will complain as it does not know how to interpret your input.
enclosingArc :: [Arc] -> Arc Source #
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 :: Integer -> (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]"
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.
toScale' :: Int -> [Int] -> Pattern Int -> Pattern Int 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"`
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
breakUp :: Pattern a -> Pattern a Source #
breakUp
finds events that share the same timespan, and spreads them out during that timespan, so for example breakUp "[bd,sn]"
gets turned into "bd sn"
fill :: Pattern a -> Pattern a -> Pattern a Source #
fill
'fills in' gaps in one pattern with events from another. For example fill "bd" "cp ~ cp"
would result in the equivalent of `"~ bd ~"`. This only finds gaps in a resulting pattern, in other words "[bd ~, sn]"
doesn't contain any gaps (because sn
covers it all), and "bd ~ ~ sn"
only contains a single gap that bridges two steps.