hsc3-0.16: Haskell SuperCollider

Safe HaskellSafe
LanguageHaskell98

Sound.SC3.UGen.UId

Contents

Description

Unique identifier class for use by non-deterministic (noise) and non-sharable (demand) unit generators.

Synopsis

Documentation

class (Functor m, Applicative m, Monad m) => UId m where Source #

A class indicating a monad (and functor and applicative) that will generate a sequence of unique integer identifiers.

Minimal complete definition

generateUId

Methods

generateUId :: m Int Source #

uid_st_eval :: UId_ST t -> t Source #

evalState with initial state of zero.

uid_st_eval (replicateM 3 generateUId) == [0,1,2]

uid_st_seq :: [UId_ST t] -> ([t], Int) Source #

Thread state through sequence of runState.

uid_st_seq_ :: [UId_ST t] -> [t] Source #

fst of uid_st_seq.

uid_st_seq_ (replicate 3 generateUId) == [0,1,2]

Lift

type Fn1 a b = a -> b Source #

Unary function.

type Fn2 a b c = a -> b -> c Source #

Binary function.

type Fn3 a b c d = a -> b -> c -> d Source #

Ternary function.

type Fn4 a b c d e = a -> b -> c -> d -> e Source #

Quaternary function.

liftUId :: UId m => (Int -> Fn1 a b) -> Fn1 a (m b) Source #

Unary UId lift.

liftUId2 :: UId m => (Int -> Fn2 a b c) -> Fn2 a b (m c) Source #

Binary UId lift.

liftUId3 :: UId m => (Int -> Fn3 a b c d) -> Fn3 a b c (m d) Source #

Ternary UId lift.

liftUId4 :: UId m => (Int -> Fn4 a b c d e) -> Fn4 a b c d (m e) Source #

Quaternary UId lift.

Clone

clone :: UId m => Int -> m UGen -> m UGen Source #

Clone a unit generator (mce . replicateM).