| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Sound.Tidal.Control
Synopsis
- spin :: Pattern Int -> ControlPattern -> ControlPattern
- _spin :: Int -> ControlPattern -> ControlPattern
- chop :: Pattern Int -> ControlPattern -> ControlPattern
- chopArc :: Arc -> Int -> [Arc]
- _chop :: Int -> ControlPattern -> ControlPattern
- striate :: Pattern Int -> ControlPattern -> ControlPattern
- _striate :: Int -> ControlPattern -> ControlPattern
- mergePlayRange :: (Double, Double) -> ValueMap -> ValueMap
- striateBy :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern
- striate' :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern
- _striateBy :: Int -> Double -> ControlPattern -> ControlPattern
- gap :: Pattern Int -> ControlPattern -> ControlPattern
- _gap :: Int -> ControlPattern -> ControlPattern
- weave :: Time -> ControlPattern -> [ControlPattern] -> ControlPattern
- weaveWith :: Time -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a
- weave' :: Time -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a
- interlace :: ControlPattern -> ControlPattern -> ControlPattern
- slice :: Pattern Int -> Pattern Int -> ControlPattern -> ControlPattern
- _slice :: Int -> Int -> ControlPattern -> ControlPattern
- randslice :: Pattern Int -> ControlPattern -> ControlPattern
- _splice :: Int -> Pattern Int -> ControlPattern -> Pattern (Map String Value)
- splice :: Pattern Int -> Pattern Int -> ControlPattern -> Pattern (Map String Value)
- loopAt :: Pattern Time -> ControlPattern -> ControlPattern
- hurry :: Pattern Rational -> ControlPattern -> ControlPattern
- smash :: Pattern Int -> [Pattern Time] -> ControlPattern -> Pattern ValueMap
- smash' :: Int -> [Pattern Time] -> ControlPattern -> ControlPattern
- echo :: Pattern Integer -> Pattern Rational -> Pattern Double -> ControlPattern -> ControlPattern
- _echo :: Integer -> Rational -> Double -> ControlPattern -> ControlPattern
- echoWith :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _echoWith :: (Num n, Ord n) => n -> Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- stut :: Pattern Integer -> Pattern Double -> Pattern Rational -> ControlPattern -> ControlPattern
- _stut :: Integer -> Double -> Rational -> ControlPattern -> ControlPattern
- stutWith :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- _stutWith :: (Num n, Ord n) => n -> Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- stut' :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- sec :: Fractional a => Pattern a -> Pattern a
- msec :: Fractional a => Pattern a -> Pattern a
- trigger :: Pattern a -> Pattern a
- qtrigger :: Pattern a -> Pattern a
- qt :: Pattern a -> Pattern a
- ctrigger :: Pattern a -> Pattern a
- rtrigger :: Pattern a -> Pattern a
- ftrigger :: Pattern a -> Pattern a
- mtrigger :: Int -> Pattern a -> Pattern a
- mt :: Int -> Pattern a -> Pattern a
- triggerWith :: (Time -> Time) -> Pattern a -> Pattern a
- splat :: Pattern Int -> ControlPattern -> ControlPattern -> ControlPattern
Documentation
spin :: Pattern Int -> ControlPattern -> ControlPattern Source #
spin will "spin" a layer up a pattern the given number of times,
with each successive layer offset in time by an additional `1/n` of a
cycle, and panned by an additional `1/n`. The result is a pattern that
seems to spin around. This function works best on multichannel
systems.
d1 $ slow 3 $ spin 4 $ sound "drum*3 tabla:4 [arpy:2 ~ arpy] [can:2 can:3]"
_spin :: Int -> ControlPattern -> ControlPattern Source #
chop :: Pattern Int -> ControlPattern -> ControlPattern Source #
chop granualizes every sample in place as it is played, turning a pattern of samples into a pattern of sample parts. Use an integer value to specify how many granules each sample is chopped into:
d1 $ chop 16 $ sound "arpy arp feel*4 arpy*4"
Different values of chop can yield very different results, depending
on the samples used:
d1 $ chop 16 $ sound (samples "arpy*8" (run 16)) d1 $ chop 32 $ sound (samples "arpy*8" (run 16)) d1 $ chop 256 $ sound "bd*4 [sn cp] [hh future]*2 [cp feel]"
_chop :: Int -> ControlPattern -> ControlPattern Source #
striate :: Pattern Int -> ControlPattern -> ControlPattern Source #
Striate is a kind of granulator, for example:
d1 $ striate 3 $ sound "ho ho:2 ho:3 hc"
This plays the loop the given number of times, but triggering progressive portions of each sample. So in this case it plays the loop three times, the first time playing the first third of each sample, then the second time playing the second third of each sample, etc.. With the highhat samples in the above example it sounds a bit like reverb, but it isn't really.
You can also use striate with very long samples, to cut it into short chunks and pattern those chunks. This is where things get towards granular synthesis. The following cuts a sample into 128 parts, plays it over 8 cycles and manipulates those parts by reversing and rotating the loops.
d1 $ slow 8 $ striate 128 $ sound "bev"
_striate :: Int -> ControlPattern -> ControlPattern Source #
striateBy :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern Source #
The striateBy function is a variant of striate with an extra
parameter, which specifies the length of each part. The striateBy
function still scans across the sample over a single cycle, but if
each bit is longer, it creates a sort of stuttering effect. For
example the following will cut the bev sample into 32 parts, but each
will be 1/16th of a sample long:
d1 $ slow 32 $ striateBy 32 (1/16) $ sound "bev"
Note that striate uses the begin and end parameters
internally. This means that if you're using striate (or striateBy)
you probably shouldn't also specify begin or end. 
striate' :: Pattern Int -> Pattern Double -> ControlPattern -> ControlPattern Source #
DEPRECATED, use striateBy instead.
_striateBy :: Int -> Double -> ControlPattern -> ControlPattern Source #
gap :: Pattern Int -> ControlPattern -> ControlPattern Source #
_gap :: Int -> ControlPattern -> ControlPattern Source #
weave :: Time -> ControlPattern -> [ControlPattern] -> ControlPattern Source #
weave applies a function smoothly over an array of different patterns. It uses an OscPattern to
apply the function at different levels to each pattern, creating a weaving effect.
d1 $ weave 3 (shape $ sine1) [sound "bd [sn drum:2*2] bd*2 [sn drum:1]", sound "arpy*8 ~"]
weaveWith :: Time -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a Source #
weaveWith is similar in that it blends functions at the same time at different amounts over a pattern:
d1 $ weaveWith 3 (sound "bd [sn drum:2*2] bd*2 [sn drum:1]") [density 2, (# speed "0.5"), chop 16]
interlace :: ControlPattern -> ControlPattern -> ControlPattern Source #
(A function that takes two ControlPatterns, and blends them together into a new ControlPattern. An ControlPattern is basically a pattern of messages to a synthesiser.)
Shifts between the two given patterns, using distortion.
Example:
d1 $ interlace (sound "bd sn kurt") (every 3 rev $ sound "bd sn:2")
slice :: Pattern Int -> Pattern Int -> ControlPattern -> ControlPattern Source #
_slice :: Int -> Int -> ControlPattern -> ControlPattern Source #
randslice :: Pattern Int -> ControlPattern -> ControlPattern Source #
loopAt :: Pattern Time -> ControlPattern -> ControlPattern Source #
loopAt makes a sample fit the given number of cycles. Internally, it
works by setting the unit parameter to "c", changing the playback
speed of the sample with the speed parameter, and setting setting
the density of the pattern to match.
d1 $ loopAt 4 $ sound "breaks125" d1 $ juxBy 0.6 (|* speed "2") $ slowspread (loopAt) [4,6,2,3] $ chop 12 $ sound "fm:14"
hurry :: Pattern Rational -> ControlPattern -> ControlPattern Source #
smash :: Pattern Int -> [Pattern Time] -> ControlPattern -> Pattern ValueMap Source #
Smash is a combination of spread and striate - it cuts the samples
into the given number of bits, and then cuts between playing the loop
at different speeds according to the values in the list.
So this:
d1 $ smash 3 [2,3,4] $ sound "ho ho:2 ho:3 hc"
Is a bit like this:
d1 $ spread (slow) [2,3,4] $ striate 3 $ sound "ho ho:2 ho:3 hc"
This is quite dancehall:
d1 $ (spread' slow "1%4 2 1 3" $ spread (striate) [2,3,4,1] $ sound "sn:2 sid:3 cp sid:4") # speed "[1 2 1 1]/2"
smash' :: Int -> [Pattern Time] -> ControlPattern -> ControlPattern Source #
echo :: Pattern Integer -> Pattern Rational -> Pattern Double -> ControlPattern -> ControlPattern Source #
Applies a type of delay to a pattern. It has three parameters, which could be called depth, time and feedback.
This adds a bit of echo:
    
    d1 $ echo 4 0.2 0.5 $ sound "bd sn"
    
The above results in 4 echos, each one 50% quieter than the last, with 1/5th of a cycle between them.
It is possible to reverse the echo:
    
    d1 $ echo 4 (-0.2) 0.5 $ sound "bd sn"
    
_echo :: Integer -> Rational -> Double -> ControlPattern -> ControlPattern Source #
echoWith :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
Allows to apply a function for each step and overlays the result delayed by the given time.
   d1 $ echoWith 2 "1%3" (# vowel "{a e i o u}%2") $ sound "bd sn"
   In this case there are two _overlays_ delayed by 1/3 of a cycle, where each has the vowel filter applied.
_echoWith :: (Num n, Ord n) => n -> Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
stut :: Pattern Integer -> Pattern Double -> Pattern Rational -> ControlPattern -> ControlPattern Source #
DEPRECATED, use echo instead
_stut :: Integer -> Double -> Rational -> ControlPattern -> ControlPattern Source #
stutWith :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
DEPRECATED, use echoWith instead
_stutWith :: (Num n, Ord n) => n -> Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
stut' :: Pattern Int -> Pattern Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a Source #
DEPRECATED, use echoWith instead
sec :: Fractional a => Pattern a -> Pattern a Source #
Turns a pattern of seconds into a pattern of (rational) cycle durations
msec :: Fractional a => Pattern a -> Pattern a Source #
Turns a pattern of milliseconds into a pattern of (rational) cycle durations, according to the current cps.
trigger :: Pattern a -> Pattern a Source #
Align the start of a pattern with the time a pattern is evaluated, rather than the global start time. Because of this, the pattern will probably not be aligned to the pattern grid.
qtrigger :: Pattern a -> Pattern a Source #
(Alias qt) Quantise trigger. Aligns the start of the pattern
 with the next cycle boundary. For example, this pattern will fade in
 starting with the next cycle after the pattern is evaluated:
d1 $ qtrigger $ s "hh(5, 8)" # amp envL
Note that the pattern will start playing immediately. The start of the pattern aligns with the next cycle boundary, but events will play before if the pattern has events at negative timestamps (which most loops do). These events can be filtered out, for example:
d1 $ qtrigger $ filterWhen (>= 0) $ s "hh(5, 8)"
ctrigger :: Pattern a -> Pattern a Source #
Ceiling trigger. Aligns the start of a pattern to the next cycle
 boundary, just like qtrigger.
rtrigger :: Pattern a -> Pattern a Source #
Rounded trigger. Aligns the start of a pattern to the nearest cycle boundary, either next or previous.
ftrigger :: Pattern a -> Pattern a Source #
Floor trigger. Aligns the start of a pattern to the previous cycle boundary.
mtrigger :: Int -> Pattern a -> Pattern a Source #
(Alias mt) Mod trigger. Aligns the start of a pattern to the
 next cycle boundary where the cycle is evenly divisible by a given
 number. qtrigger is equivalent to mtrigger 1.
triggerWith :: (Time -> Time) -> Pattern a -> Pattern a Source #
This aligns the start of a pattern to some value relative to the
 time the pattern is evaluated. The provided function maps the evaluation
 time (on the global cycle clock) to a new time, and then triggerWith
 aligns the pattern's start to the time that's returned.
splat :: Pattern Int -> ControlPattern -> ControlPattern -> ControlPattern Source #