hsc3-lang-0.13: Haskell SuperCollider Language

Safe HaskellNone

Sound.SC3.Lang.Control.OverlapTexture

Description

SC2 OverlapTexture related functions.

Generate sequences of overlapping instances of a UGen graph or family of graphs. The OverlapTexture functions add an Envelope and calculate inter-onset times and durations. There are variants for different graph constructors, and to allow for a post-processing stage.

Synopsis

Documentation

mk_env :: UGen -> UGen -> UGenSource

Make an envGen UGen with envLinen' structure with given sustain and transition times.

with_env_u :: 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_u where envelope parameters are lifted from Double to UGen.

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

Control parameters for overlapTextureU and related functions. Components are: 1. sustain time, 2. transition time, 3. number of overlaping (simultaneous) nodes and 4. number of nodes altogether.

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

Extract envelope parameters (sustain and transition times) for with_env from OverlapTexture.

type Texture_DT = (Double, Double)Source

(legato,duration) parameters. The duration is the inter-offset time, legato is the scalar giving the sounding time in relation to the inter-offset time.

overlapTexture_dt :: OverlapTexture -> Texture_DTSource

Extract legato (duration of sound proportional to inter-offset time) and duration (inter-offset time) parameters from OverlapTexture.

 overlapTexture_dt (3,1,5,maxBound) == (5,1)

type XFadeTexture = (Double, Double, Int)Source

Control parameters for xfadeTextureU and related functions. Components are: 1. sustain time, 2. transition time, 3. number of nodes instatiated altogether.

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

Extract envelope parameters for with_env from XFadeTexture.

xfadeTexture_dt :: XFadeTexture -> Texture_DTSource

Extract legato and duration paramaters from XFadeTexture.

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

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

overlapTextureP :: 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 overlapTextureP.

 import Sound.SC3.ID
 import Sound.SC3.Lang.Control.OverlapTexture

 let {o = sinOsc AR (rand 'α' 440 880) 0
     ;u = pan2 o (rand 'β' (-1) 1) (rand 'γ' 0.1 0.2)}
 in overlapTextureU (3,1,6,9) u

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

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

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

Audition Event pattern with specified post-processing function.

type PPF = UGen -> UGenSource

Post processing function.

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

Variant of overlapTextureU with post-processing stage.

xfadeTextureP :: 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 xfadeTextureP.

 let {o = sinOsc AR (rand 'α' 440 880) 0
     ;u = pan2 o (rand 'β' (-1) 1) (rand 'γ' 0.1 0.2)}
 in xfadeTextureU (1,3,6) u

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

Variant of xfadeTextureU with post-processing stage.

type USTF st = st -> (UGen, st)Source

UGen generating state transform function.

overlapTextureP_st :: OverlapTexture -> USTF st -> st -> P EventSource

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

overlapTextureS :: OverlapTexture -> USTF st -> st -> IO ()Source

Audition pattern given by overlapTextureP_st.

overlapTextureS_pp :: OverlapTexture -> USTF st -> st -> Int -> PPF -> IO ()Source

Variant of overlapTextureS with post-processing stage.

type MSTF st m = st -> m (Maybe st)Source

Monadic state transform function.

dt_rescheduler_m :: MonadIO m => MSTF (st, Time) m -> (st, Time) -> m ()Source

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

overlapTextureR :: Transport m => OverlapTexture -> IO UGen -> MSTF (Int, Time) mSource

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.