essence-of-live-coding-vivid-0.2.7: General purpose live coding framework - vivid backend
Safe HaskellSafe-Inferred
LanguageHaskell2010

LiveCoding.Vivid

Description

Support for vivid, a Haskell library for SuperCollider.

With this module, you can create cells corresponding to synthesizers.

The synthesizers automatically start and stop on reload.

Synopsis

Documentation

data SynthState Source #

Whether a synthesizer should currently be running or not.

Typically, you will either statically supply the value and change it in the code to start and stop the synth, or you can connect another cell to it.

Constructors

Started 
Stopped 

Instances

Instances details
Data SynthState Source # 
Instance details

Defined in LiveCoding.Vivid

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SynthState -> c SynthState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SynthState #

toConstr :: SynthState -> Constr #

dataTypeOf :: SynthState -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SynthState) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SynthState) #

gmapT :: (forall b. Data b => b -> b) -> SynthState -> SynthState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SynthState -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SynthState -> r #

gmapQ :: (forall d. Data d => d -> u) -> SynthState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SynthState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SynthState -> m SynthState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthState -> m SynthState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SynthState -> m SynthState #

Eq SynthState Source # 
Instance details

Defined in LiveCoding.Vivid

vividHandleParametrised :: (VividAction m, Eq params, VarList params, Subset (InnerVars params) args, Elem "gate" args) => ParametrisedHandle (params, SynthDef args, SynthState) m (Maybe (Synth args)) Source #

A ParametrisedHandle corresponding to one vivid/SuperCollider synthesizer.

Usually, you will want to use liveSynth instead, it is easier to handle.

liveSynth :: (VividAction m, Eq params, Typeable params, VarList params, Typeable (InnerVars params), Subset (InnerVars params) (InnerVars params), Elem "gate" (InnerVars params), Data params) => Cell (HandlingStateT m) (params, SDBody' (InnerVars params) [Signal], SynthState) (Maybe (Synth (InnerVars params))) Source #

Create a synthesizer.

When you add liveSynth to your live program, it will be started upon reload immediately.

Feed the definition of the synthesizer and its current intended state to this cell. The input has the form (params, sdbody, synthState).

  • A change in params will reload the synthesizer quickly, unless the types of the parameters change.
  • A change in the sdbody :: SDBody ... or the _types_ of the params will release the synthesizer and start a new one.
  • The input synthState :: SynthState represent whether the synthesizer should currently be running or not. Changes in it quickly start or stop it.
  • When it is started, Just synth is returned, where synth represents the running synthesizer.
  • When it is stopped, Nothing is returned.

You have to use envGate in your sdbody, or another way of gating your output signals in order to ensure release of the synths without clipping.

For an example, have a look at the source code of sine.

sine :: VividAction m => Cell (HandlingStateT m) Float () Source #

Example sine synthesizer that creates a sine wave at the given input frequency.

Orphan instances

KnownSymbol a => Data (I a) Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> I a -> c (I a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (I a) #

toConstr :: I a -> Constr #

dataTypeOf :: I a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (I a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (I a)) #

gmapT :: (forall b. Data b => b -> b) -> I a -> I a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> I a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> I a -> r #

gmapQ :: (forall d. Data d => d -> u) -> I a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> I a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> I a -> m (I a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> I a -> m (I a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> I a -> m (I a) #