hsc3-lang-0.11: Haskell SuperCollider Language

Sound.SC3.Lang.Control.OverlapTexture

Description

SC2 OverlapTexture related functions.

Synopsis

Documentation

mk_env :: UGen -> UGen -> UGenSource

Make an envGen UGen with envLinen' structure with given attack/delay and sustain times.

with_env' :: UGen -> UGen -> UGen -> UGenSource

Apply mk_env envelope to input signal and write to output bus 0.

with_env :: (Double, Double) -> UGen -> UGenSource

Variant of with_env' where envelope parameters are lifted from Double to UGen.

type OverlapTexture = (Double, Double, Double, Int)Source

Control parameters for overlapTextureU and related functions.

overlapTexture_env :: OverlapTexture -> (Double, Double)Source

Extract envelope parameters for with_env from OverlapTexture.

overlapTexture_dt :: OverlapTexture -> (Double, Double)Source

Extract duration and legato paramaters from OverlapTexture.

type XFadeTexture = (Double, Double, Int)Source

Control parameters for xfadeTextureU and related functions.

xfadeTexture_env :: XFadeTexture -> (Double, Double)Source

Extract envelope parameters for with_env from XFadeTexture.

xfadeTexture_dt :: XFadeTexture -> (Double, Double)Source

Extract duration and legato paramaters from XFadeTexture.

gen_synth :: (Double, Double) -> UGen -> SynthdefSource

Generate Synthdef from envelope parameters for with_env and a continuous signal.

overlapTextureU' :: OverlapTexture -> UGen -> P EventSource

Generate an Event pattern from OverlapTexture control parameters and a continuous signal.

overlapTextureU :: OverlapTexture -> UGen -> IO ()Source

Audition pattern given by overlapTextureU'.

post_process_s :: Int -> (UGen -> UGen) -> SynthdefSource

Generate Synthdef from a signal processing function over the indicated number of channels.

post_process_a :: Transport t => t -> P Event -> Int -> (UGen -> UGen) -> IO ()Source

Audition Event pattern with specified post-processing function.

overlapTextureU_pp :: OverlapTexture -> UGen -> Int -> (UGen -> UGen) -> IO ()Source

Variant of overlapTextureU with post-processing stage.

xfadeTextureU' :: XFadeTexture -> UGen -> P EventSource

Generate an Event pattern from XFadeTexture control parameters and a continuous signal.

xfadeTextureU :: XFadeTexture -> UGen -> IO ()Source

Audition pattern given by xfadeTextureU'.

xfadeTextureU_pp :: XFadeTexture -> UGen -> Int -> (UGen -> UGen) -> IO ()Source

Variant of xfadeTextureU with post-processing stage.

overlapTextureS' :: OverlapTexture -> (st -> (UGen, st)) -> st -> P EventSource

Variant of overlapTextureU' where the continuous signal for each Event is derived from a state transform function seeded with given initial state.

overlapTextureS :: OverlapTexture -> (st -> (UGen, st)) -> st -> IO ()Source

Audition pattern given by overlapTextureS'.

overlapTextureS_pp :: OverlapTexture -> (st -> (UGen, st)) -> st -> Int -> (UGen -> UGen) -> IO ()Source

Variant of overlapTextureS with post-processing stage.

at' :: st -> Double -> ((st, Time) -> IO (Maybe (st, Time))) -> IO ()Source

Run a state transforming function f that also operates with a delta Time indicating the duration to pause before re-running the function.

at :: st -> Time -> ((st, Time) -> IO (Maybe (st, Time))) -> IO ()Source

Variant of at' that pauses until initial Time.

overlapTextureM' :: Transport t => t -> OverlapTexture -> IO UGen -> IO ()Source

Underlying function of overlapTextureM with explicit Transport.

overlapTextureM :: OverlapTexture -> IO UGen -> IO ()Source

Variant of overlapTextureU where the continuous signal is in the IO monad.