Safe Haskell | None |
---|---|
Language | Haskell2010 |
- dirt :: Shape
- dirtSlang :: OscSlang
- superDirtSlang :: OscSlang
- superDirtBackend :: Int -> IO (Backend a)
- superDirtState :: Int -> IO (MVar (ParamPattern, [ParamPattern]))
- dirtBackend :: IO (Backend a)
- dirtStream :: IO (ParamPattern -> IO ())
- dirtState :: IO (MVar (ParamPattern, [ParamPattern]))
- dirtSetters :: IO Time -> IO (ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ())
- superDirtSetters :: IO Time -> IO (ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ())
- superDirts :: [Int] -> IO [(ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ())]
- dirtstream :: t -> IO (ParamPattern -> IO ())
- dirtToColour :: ParamPattern -> Pattern ColourD
- showToColour :: Show a => a -> ColourD
- datumToColour :: Value -> ColourD
- stringToColour :: String -> ColourD
- pick :: String -> Int -> String
- striate :: Pattern Int -> ParamPattern -> ParamPattern
- _striate :: Int -> ParamPattern -> ParamPattern
- striate' :: Int -> Double -> ParamPattern -> ParamPattern
- striateO :: Int -> Double -> ParamPattern -> ParamPattern
- striateL :: Int -> Int -> ParamPattern -> ParamPattern
- striateL' :: Integral a => Int -> Double -> a -> ParamPattern -> ParamPattern
- metronome :: Pattern ParamMap
- clutchIn :: Time -> Time -> [Pattern a] -> Pattern a
- clutch :: Time -> [Pattern a] -> Pattern a
- xfadeIn :: Time -> Time -> [ParamPattern] -> ParamPattern
- xfade :: Time -> [ParamPattern] -> ParamPattern
- stut :: Pattern Integer -> Pattern Double -> Pattern Rational -> ParamPattern -> ParamPattern
- _stut :: Integer -> Double -> Rational -> ParamPattern -> ParamPattern
- stut' :: Integer -> Time -> (ParamPattern -> ParamPattern) -> ParamPattern -> ParamPattern
- anticipateIn :: Time -> Time -> [ParamPattern] -> ParamPattern
- anticipate :: Time -> [ParamPattern] -> ParamPattern
- nToOrbit :: ParamPattern -> ParamPattern
- soundToOrbit :: [String] -> ParamPattern -> ParamPattern
Documentation
superDirtState :: Int -> IO (MVar (ParamPattern, [ParamPattern])) Source #
dirtBackend :: IO (Backend a) Source #
dirtStream :: IO (ParamPattern -> IO ()) Source #
dirtState :: IO (MVar (ParamPattern, [ParamPattern])) Source #
dirtSetters :: IO Time -> IO (ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ()) Source #
superDirtSetters :: IO Time -> IO (ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ()) Source #
superDirts :: [Int] -> IO [(ParamPattern -> IO (), (Time -> [ParamPattern] -> ParamPattern) -> ParamPattern -> IO ())] Source #
dirtstream :: t -> IO (ParamPattern -> IO ()) Source #
showToColour :: Show a => a -> ColourD Source #
datumToColour :: Value -> ColourD Source #
stringToColour :: String -> ColourD Source #
striate :: Pattern Int -> ParamPattern -> ParamPattern 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 -> ParamPattern -> ParamPattern Source #
striate' :: Int -> Double -> ParamPattern -> ParamPattern Source #
The striate'
function is a variant of striate
with an extra
parameter, which specifies the length of each part. The striate'
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 $ striate' 32 (1/16) $ sound "bev"
Note that striate
uses the begin
and end
parameters
internally. This means that if you're using striate
(or striate'
)
you probably shouldn't also specify begin
or end
.
striateO :: Int -> Double -> ParamPattern -> ParamPattern Source #
like striate
, but with an offset to the begin and end values
striateL :: Int -> Int -> ParamPattern -> ParamPattern Source #
Just like striate
, but also loops each sample chunk a number of times specified in the second argument.
The primed version is just like striate'
, where the loop count is the third argument. For example:
d1 $ striateL' 3 0.125 4 $ sound "feel sn:2"
Like striate
, these use the begin
and end
parameters internally, as well as the loop
parameter for these versions.
striateL' :: Integral a => Int -> Double -> a -> ParamPattern -> ParamPattern Source #
clutchIn :: Time -> Time -> [Pattern a] -> Pattern a Source #
Also degrades the current pattern and undegrades the next.
To change the number of cycles the transition takes, you can use clutchIn
like so:
d1 $ sound "bd(5,8)" t1 (clutchIn 8) $ sound "[hh*4, odx(3,8)]"
will take 8 cycles for the transition.
clutch :: Time -> [Pattern a] -> Pattern a Source #
Degrades the current pattern while undegrading the next.
This is like xfade
but not by gain of samples but by randomly removing events from the current pattern and slowly adding back in missing events from the next one.
d1 $ sound "bd(3,8)" t1 clutch $ sound "[hh*4, odx(3,8)]"
clutch
takes two cycles for the transition, essentially this is clutchIn 2
.
xfadeIn :: Time -> Time -> [ParamPattern] -> ParamPattern Source #
crossfades between old and new pattern over given number of cycles, e.g.:
d1 $ sound "bd sn" t1 (xfadeIn 16) $ sound "jvbass*3"
Will fade over 16 cycles from "bd sn" to "jvbass*3"
xfade :: Time -> [ParamPattern] -> ParamPattern Source #
stut :: Pattern Integer -> Pattern Double -> Pattern Rational -> ParamPattern -> ParamPattern Source #
Stut applies a type of delay to a pattern. It has three parameters, which could be called depth, feedback and time. Depth is an integer and the others floating point. This adds a bit of echo:
d1 $ stut 4 0.5 0.2 $ 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 $ stut 4 0.5 (-0.2) $ sound "bd sn"
_stut :: Integer -> Double -> Rational -> ParamPattern -> ParamPattern Source #
stut' :: Integer -> Time -> (ParamPattern -> ParamPattern) -> ParamPattern -> ParamPattern Source #
Instead of just decreasing volume to produce echoes, stut'
allows to apply a function for each step and overlays the result delayed by the given time.
d1 $ stut' 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.
anticipateIn :: Time -> Time -> [ParamPattern] -> ParamPattern Source #
same as anticipate
though it allows you to specify the number of cycles until dropping to the new pattern, e.g.:
d1 $ sound "jvbass(3,8)" t1 (anticipateIn 4) $ sound "jvbass(5,8)"
anticipate :: Time -> [ParamPattern] -> ParamPattern Source #
anticipate
is an increasing comb filter.
Build up some tension, culminating in a _drop_ to the new pattern after 8 cycles.
nToOrbit :: ParamPattern -> ParamPattern Source #
Copies the n
parameter to the orbit
parameter, so different sound variants or notes go to different orbits in SuperDirt.
soundToOrbit :: [String] -> ParamPattern -> ParamPattern Source #
Maps the sample or synth names to different orbit
s, using indexes from the given list. E.g. soundToOrbit ["bd", "sn", "cp"] $ sound "bd [cp sn]"
would cause the bd, sn and cp smamples to be sent to orbit 0, 1, 2 respectively.