hsc3-0.16: Haskell SuperCollider

Safe HaskellSafe
LanguageHaskell98

Sound.SC3.UGen.Type

Contents

Synopsis

Basic types

data UGenId Source #

Data type for internalised identifier at UGen.

Constructors

NoId 
UId Int 

no_id :: UGenId Source #

Alias of NoId, the UGenId used for deterministic UGens.

type Sample = Double Source #

SC3 samples are 32-bit Float. hsc3 represents data as 64-bit Double. If UGen values are used more generally (ie. see hsc3-forth) Float may be too imprecise, ie. for representing time stamps.

data C_Meta n Source #

Control meta-data.

Constructors

C_Meta 

Fields

Instances

Eq n => Eq (C_Meta n) Source # 

Methods

(==) :: C_Meta n -> C_Meta n -> Bool #

(/=) :: C_Meta n -> C_Meta n -> Bool #

Read n => Read (C_Meta n) Source # 
Show n => Show (C_Meta n) Source # 

Methods

showsPrec :: Int -> C_Meta n -> ShowS #

show :: C_Meta n -> String #

showList :: [C_Meta n] -> ShowS #

type C_Meta_T5 n = (n, n, String, n, String) Source #

5-tuple form of C_Meta data.

c_meta_t5 :: (n -> m) -> C_Meta_T5 n -> C_Meta m Source #

Lift C_Meta_5 to C_Meta allowing type coercion.

data Control Source #

Control inputs. It is an invariant that controls with equal names within a UGen graph must be equal in all other respects.

data Label Source #

Labels.

Constructors

Label 

Fields

type Output = Rate Source #

Unit generator output descriptor.

newtype Special Source #

Operating mode of unary and binary operators.

Constructors

Special Int 

data Proxy Source #

Proxy to multiple channel input.

Constructors

Proxy 

data MRG Source #

Multiple root graph.

Constructors

MRG 

Fields

Instances

data UGen Source #

Union type of Unit Generator forms.

Instances

Enum UGen Source #

Unit generators are enumerable.

Methods

succ :: UGen -> UGen #

pred :: UGen -> UGen #

toEnum :: Int -> UGen #

fromEnum :: UGen -> Int #

enumFrom :: UGen -> [UGen] #

enumFromThen :: UGen -> UGen -> [UGen] #

enumFromTo :: UGen -> UGen -> [UGen] #

enumFromThenTo :: UGen -> UGen -> UGen -> [UGen] #

Eq UGen Source # 

Methods

(==) :: UGen -> UGen -> Bool #

(/=) :: UGen -> UGen -> Bool #

Floating UGen Source #

Unit generators are floating point.

Methods

pi :: UGen #

exp :: UGen -> UGen #

log :: UGen -> UGen #

sqrt :: UGen -> UGen #

(**) :: UGen -> UGen -> UGen #

logBase :: UGen -> UGen -> UGen #

sin :: UGen -> UGen #

cos :: UGen -> UGen #

tan :: UGen -> UGen #

asin :: UGen -> UGen #

acos :: UGen -> UGen #

atan :: UGen -> UGen #

sinh :: UGen -> UGen #

cosh :: UGen -> UGen #

tanh :: UGen -> UGen #

asinh :: UGen -> UGen #

acosh :: UGen -> UGen #

atanh :: UGen -> UGen #

log1p :: UGen -> UGen #

expm1 :: UGen -> UGen #

log1pexp :: UGen -> UGen #

log1mexp :: UGen -> UGen #

Fractional UGen Source #

Unit generators are fractional.

Methods

(/) :: UGen -> UGen -> UGen #

recip :: UGen -> UGen #

fromRational :: Rational -> UGen #

Integral UGen Source #

Unit generators are integral.

Methods

quot :: UGen -> UGen -> UGen #

rem :: UGen -> UGen -> UGen #

div :: UGen -> UGen -> UGen #

mod :: UGen -> UGen -> UGen #

quotRem :: UGen -> UGen -> (UGen, UGen) #

divMod :: UGen -> UGen -> (UGen, UGen) #

toInteger :: UGen -> Integer #

Num UGen Source #

Unit generators are numbers.

Methods

(+) :: UGen -> UGen -> UGen #

(-) :: UGen -> UGen -> UGen #

(*) :: UGen -> UGen -> UGen #

negate :: UGen -> UGen #

abs :: UGen -> UGen #

signum :: UGen -> UGen #

fromInteger :: Integer -> UGen #

Ord UGen Source #

Unit generators are orderable (when Constants).

(constant 2 > constant 1) == True

Methods

compare :: UGen -> UGen -> Ordering #

(<) :: UGen -> UGen -> Bool #

(<=) :: UGen -> UGen -> Bool #

(>) :: UGen -> UGen -> Bool #

(>=) :: UGen -> UGen -> Bool #

max :: UGen -> UGen -> UGen #

min :: UGen -> UGen -> UGen #

Read UGen Source # 
Real UGen Source #

Unit generators are real.

Methods

toRational :: UGen -> Rational #

RealFrac UGen Source # 

Methods

properFraction :: Integral b => UGen -> (b, UGen) #

truncate :: Integral b => UGen -> b #

round :: Integral b => UGen -> b #

ceiling :: Integral b => UGen -> b #

floor :: Integral b => UGen -> b #

Show UGen Source # 

Methods

showsPrec :: Int -> UGen -> ShowS #

show :: UGen -> String #

showList :: [UGen] -> ShowS #

Bits UGen Source #

UGens are bit patterns.

Random UGen Source #

Unit generators are stochastic.

Methods

randomR :: RandomGen g => (UGen, UGen) -> g -> (UGen, g) #

random :: RandomGen g => g -> (UGen, g) #

randomRs :: RandomGen g => (UGen, UGen) -> g -> [UGen] #

randoms :: RandomGen g => g -> [UGen] #

randomRIO :: (UGen, UGen) -> IO UGen #

randomIO :: IO UGen #

MulAdd UGen Source # 

Methods

mul_add :: UGen -> UGen -> UGen -> UGen Source #

BinaryOp UGen Source # 
UnaryOp UGen Source # 
RealFracE UGen Source # 
OrdE UGen Source # 

Methods

(<*) :: UGen -> UGen -> UGen Source #

(<=*) :: UGen -> UGen -> UGen Source #

(>*) :: UGen -> UGen -> UGen Source #

(>=*) :: UGen -> UGen -> UGen Source #

EqE UGen Source # 

Methods

(==*) :: UGen -> UGen -> UGen Source #

(/=*) :: UGen -> UGen -> UGen Source #

Audible UGen Source # 

Methods

play_id :: Transport t => Int -> t -> UGen -> IO () Source #

play :: Transport t => t -> UGen -> IO () Source #

Audible UGen Source # 

Methods

play_at :: Transport m => Play_Opt -> UGen -> m () Source #

play :: Transport m => UGen -> m () Source #

Parser

Accessors

u_constant_err :: UGen -> Sample Source #

Erroring variant.

MRG

mrg :: [UGen] -> UGen Source #

Multiple root graph constructor.

mrg_leftmost :: UGen -> UGen Source #

See into MRG_U, follows leftmost rule until arriving at non-MRG node.

Predicates

isConstant :: UGen -> Bool Source #

Constant node predicate.

isSink :: UGen -> Bool Source #

True if input is a sink UGen, ie. has no outputs. Sees into MRG.

MCE

mce :: [UGen] -> UGen Source #

Multiple channel expansion node constructor.

mceProxies :: MCE UGen -> [UGen] Source #

Type specified mce_elem.

isMCE :: UGen -> Bool Source #

Multiple channel expansion node (MCE_U) predicate. Sees into MRG.

mceChannels :: UGen -> [UGen] Source #

Output channels of UGen as a list. If required, preserves the RHS of and MRG node in channel 0.

mceDegree :: UGen -> Maybe Int Source #

Number of channels to expand to. This function sees into MRG, and is defined only for MCE nodes.

mceDegree_err :: UGen -> Int Source #

Erroring variant.

mceExtend :: Int -> UGen -> [UGen] Source #

Extend UGen to specified degree. Follows "leftmost" rule for MRG nodes.

mceInputTransform :: [UGen] -> Maybe [[UGen]] Source #

Apply MCE transform to a list of inputs.

mceBuild :: ([UGen] -> UGen) -> [UGen] -> UGen Source #

Build a UGen after MCE transformation of inputs.

mce_is_direct_proxy :: MCE UGen -> Bool Source #

True if MCE is an immediate proxy for a multiple-out Primitive. This is useful when disassembling graphs, ie. ugen_graph_forth_pp at hsc3-db.

Validators

checkInput :: UGen -> UGen Source #

Ensure input UGen is valid, ie. not a sink.

Constructors

constant :: Real n => n -> UGen Source #

Constant value node constructor.

int_to_ugen :: Int -> UGen Source #

Type specialised constant.

float_to_ugen :: Float -> UGen Source #

Type specialised constant.

double_to_ugen :: Double -> UGen Source #

Type specialised constant.

proxy :: UGen -> Int -> UGen Source #

Unit generator proxy node constructor.

rateOf :: UGen -> Rate Source #

Determine the rate of a UGen.

proxify :: UGen -> UGen Source #

Apply proxy transformation if required.

mkUGen :: Maybe ([Sample] -> Sample) -> [Rate] -> Either Rate [Int] -> String -> [UGen] -> Maybe UGen -> Int -> Special -> UGenId -> UGen Source #

Construct proxied and multiple channel expanded UGen.

cf = constant function, rs = rate set, r = rate, nm = name, i = inputs, o = outputs.

Operators

mkOperator :: ([Sample] -> Sample) -> String -> [UGen] -> Int -> UGen Source #

Operator UGen constructor.

mkUnaryOperator :: Unary -> (Sample -> Sample) -> UGen -> UGen Source #

Unary math constructor with constant optimization.

mkBinaryOperator_optimize :: Binary -> (Sample -> Sample -> Sample) -> (Either Sample Sample -> Bool) -> UGen -> UGen -> UGen Source #

Binary math constructor with constant optimization.

let o = sinOsc AR 440 0
o * 1 == o && 1 * o == o && o * 2 /= o
o + 0 == o && 0 + o == o && o + 1 /= o
o - 0 == o && 0 - o /= o
o / 1 == o && 1 / o /= o
o ** 1 == o && o ** 2 /= o

mkBinaryOperator :: Binary -> (Sample -> Sample -> Sample) -> UGen -> UGen -> UGen Source #

Binary math constructor with constant optimization.

Numeric instances