hsc3-lang-0.15: Haskell SuperCollider Language

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Lang.Control.OverlapTexture

Contents

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.

Here the implementation of texture adds sumOut nodes at bus 0 to the head of group 1, post-processing adds a replaceOut node at bus 0 to the tail of group 1.

Synopsis

Envelope

type Env_ST n = (n, n) Source

Envelope defined by sustain and transition times.

type Loc_GB = (Int, UGen) Source

Location in node tree, given as (group,bus).

mk_env :: Env_ST UGen -> UGen Source

Make an envGen UGen with envLinen' structure with given by Env_ST.

with_env_u :: UGen -> UGen -> Env_ST UGen -> UGen Source

Add multiplier stage and out UGen writing to bus.

with_env :: UGen -> Env_ST Double -> UGen -> UGen Source

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

gen_synth :: UGen -> Maybe (Env_ST Double) -> UGen -> Synthdef Source

Generate Synthdef, perhaps with envelope parameters for with_env, and a continuous signal.

gen_synth' :: UGen -> Env_ST Double -> UGen -> Synthdef Source

Require envelope.

nrt_sy1 :: Int -> Synthdef -> [Double] -> NRT Source

Schedule Synthdef at indicated intervals. Synthdef is sent once at time zero.

nrt_sy :: Int -> [Synthdef] -> [Time] -> NRT Source

Schedule Synthdefs at indicated intervals. Synthdef is sent in activation bundle.

Overlap texture

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 -> Env_ST Double Source

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

overlapTexture_iot :: OverlapTexture -> Double Source

Inter-offset time given OverlapTexture.

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

overlapTexture_nrt :: Loc_GB -> OverlapTexture -> UGen -> NRT Source

Generate an NRT score from OverlapTexture control parameters and a continuous signal.

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

audition of overlapTexture_nrt.

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

XFade texture

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 instantiated altogether.

xfadeTexture_env :: XFadeTexture -> Env_ST Double Source

Extract envelope parameters for with_env from XFadeTexture.

xfadeTexture_nrt :: Loc_GB -> XFadeTexture -> UGen -> NRT Source

Generate an NRT score from XFadeTexture control parameters and a continuous signal.

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

audition of xfadeTexture_nrt.

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

Spawn texture

type Spawn_Texture = (Int -> Double, Int) Source

Duration a function of the iteration number.

spawnTexture_nrt :: Loc_GB -> Spawn_Texture -> UGen -> NRT Source

Generate an NRT score from OverlapTexture control parameters and a continuous signal.

Post-process

post_process_s :: Int -> PP_Bus -> (UGen -> UGen) -> Synthdef Source

Generate Synthdef from a signal processing function over the indicated number of channels. If there is a single bus, writes using replaceOut, else using out.

post_process :: Transport m => Int -> PP_Bus -> Int -> (UGen -> UGen) -> m () Source

Run post-processing function.

post_process_nrt :: Transport m => Loc_GB -> NRT -> Int -> (UGen -> UGen) -> m () Source

Audition NRT with specified post-processing function.

type PPF = UGen -> UGen Source

Post processing function.

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

Variant of overlapTextureU with post-processing stage.

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

Variant of xfadeTextureU with post-processing stage.

State

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

UGen generating state transform function.

overlapTexture_nrt_st :: Loc_GB -> OverlapTexture -> USTF st -> st -> NRT Source

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

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) m 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.