Safe Haskell | None |
---|---|
Language | Haskell2010 |
- stutter :: Integral i => i -> Time -> Pattern a -> Pattern a
- echo :: Time -> Pattern a -> Pattern a
- triple :: Time -> Pattern a -> Pattern a
- quad :: Time -> Pattern a -> Pattern a
- double :: Time -> Pattern a -> Pattern a
- jux :: (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap
- juxcut :: (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap
- juxcut' :: [t -> ParamPattern] -> t -> Pattern ParamMap
- jux' :: [t -> ParamPattern] -> t -> Pattern ParamMap
- jux4 :: (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap
- juxBy :: Double -> (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap
- smash :: Pattern Int -> [Pattern Time] -> ParamPattern -> Pattern ParamMap
- smash' :: Int -> [Pattern Time] -> ParamPattern -> Pattern ParamMap
- samples :: Applicative f => f String -> f Int -> f String
- samples' :: Applicative f => f String -> f Int -> f String
- spreadf :: t1 -> t -> [a -> Pattern b] -> a -> Pattern b
- spin :: Pattern Int -> ParamPattern -> ParamPattern
- _spin :: Int -> ParamPattern -> ParamPattern
- sawwave4 :: Pattern Double
- sinewave4 :: Pattern Double
- rand4 :: Pattern Double
- stackwith :: Pattern ParamMap -> [ParamPattern] -> Pattern ParamMap
- scale :: (Functor f, Num b) => b -> b -> f b -> f b
- scalex :: (Functor f, Floating b) => b -> b -> f b -> f b
- chop :: Pattern Int -> ParamPattern -> ParamPattern
- _chop :: Int -> ParamPattern -> ParamPattern
- gap :: Pattern Int -> ParamPattern -> ParamPattern
- _gap :: Int -> ParamPattern -> ParamPattern
- chopArc :: Arc -> Int -> [Arc]
- en :: [(Int, Int)] -> Pattern String -> Pattern String
- weave :: Rational -> ParamPattern -> [ParamPattern] -> ParamPattern
- weave' :: Rational -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a
- interlace :: ParamPattern -> ParamPattern -> ParamPattern
- step :: String -> String -> Pattern String
- steps :: [(String, String)] -> Pattern String
- step' :: [String] -> String -> Pattern String
- 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
- up :: Pattern Double -> ParamPattern
- ghost'' :: Time -> (Pattern a -> Pattern a) -> Pattern a -> Pattern a
- ghost' :: t -> Pattern ParamMap -> Pattern ParamMap
- ghost :: Pattern ParamMap -> Pattern ParamMap
- slice :: Int -> Int -> ParamPattern -> ParamPattern
- randslice :: Int -> ParamPattern -> ParamPattern
- loopAt :: Pattern Time -> ParamPattern -> ParamPattern
- tabby :: Integer -> Pattern a -> Pattern a -> Pattern a
- hurry :: Pattern Rational -> ParamPattern -> ParamPattern
Documentation
jux :: (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap 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) $ striate' 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) $ striate' 32 (1/16) $ sound "bev"
juxcut :: (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap Source #
jux' :: [t -> ParamPattern] -> t -> Pattern ParamMap 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 :: (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap Source #
Multichannel variant of jux
, _not sure what it does_
juxBy :: Double -> (ParamPattern -> Pattern ParamMap) -> ParamPattern -> Pattern ParamMap 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.
smash :: Pattern Int -> [Pattern Time] -> ParamPattern -> Pattern ParamMap 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"
spin :: Pattern Int -> ParamPattern -> ParamPattern 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 -> ParamPattern -> ParamPattern Source #
scale :: (Functor f, Num b) => b -> b -> f b -> f b Source #
scale
will take a pattern which goes from 0 to 1 (like sine1
), and scale it to a different range - between the first and second arguments. In the below example, `scale 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 $ scale 1 1.5 sine1)
chop :: Pattern Int -> ParamPattern -> ParamPattern 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 -> ParamPattern -> ParamPattern Source #
gap :: Pattern Int -> ParamPattern -> ParamPattern Source #
_gap :: Int -> ParamPattern -> ParamPattern Source #
weave :: Rational -> ParamPattern -> [ParamPattern] -> ParamPattern 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 ~"]
weave' :: Rational -> Pattern a -> [Pattern a -> Pattern a] -> Pattern a Source #
weave'
is similar in that it blends functions at the same time at different amounts over a pattern:
d1 $ weave' 3 (sound "bd [sn drum:2*2] bd*2 [sn drum:1]") [density 2, (# speed "0.5"), chop 16]
interlace :: ParamPattern -> ParamPattern -> ParamPattern Source #
(A function that takes two OscPatterns, and blends them together into a new OscPattern. An OscPattern 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")
step' :: [String] -> String -> Pattern String Source #
like step
, but allows you to specify an array of strings to use for 0,1,2...
slice :: Int -> Int -> ParamPattern -> ParamPattern Source #
randslice :: Int -> ParamPattern -> ParamPattern Source #
loopAt :: Pattern Time -> ParamPattern -> ParamPattern 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 -> ParamPattern -> ParamPattern Source #