hsc3-0.15.1: Haskell SuperCollider

Safe HaskellSafe-Inferred
LanguageHaskell98

Sound.SC3.UGen.Type

Contents

Synopsis

Basic types

data UGenId Source

Data type for internalised identifier at UGen.

Constructors

NoId 
UId Int 

Instances

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 Constant Source

Constants.

Constant 3 == Constant 3
(Constant 3 > Constant 1) == True

Constructors

Constant 

data C_Meta n Source

Control meta-data.

Constructors

C_Meta 

Fields

ctl_min :: n

Minimum

ctl_max :: n

Maximum

ctl_warp :: String

(0,1) (min,max) transfer function.

ctl_step :: n

The step to increment & decrement by.

ctl_units :: String

Unit of measure (ie hz, ms etc.).

Instances

Eq n => Eq (C_Meta n) 
Show n => Show (C_Meta n) 

type C_Meta' n = (n, n, String, n, String) Source

5-tuple form of C_Meta data.

c_meta' :: (n -> m) -> C_Meta' n -> C_Meta m Source

Lift C_Meta' 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.

Instances

data Label Source

Labels.

Constructors

Label 

Fields

ugenLabel :: String
 

Instances

type Output = Rate Source

Unit generator output descriptor.

newtype Special Source

Operating mode of unary and binary operators.

Constructors

Special Int 

Instances

data Primitive Source

UGen primitives.

data Proxy Source

Proxy to multiple channel input.

Constructors

Proxy 

Instances

data MRG Source

Multiple root graph.

Constructors

MRG 

Fields

mrgLeft :: UGen
 
mrgRight :: UGen
 

Instances

data UGen Source

Union type of Unit Generator forms.

Instances

Enum UGen

Unit generators are enumerable.

Eq UGen 
Floating UGen

Unit generators are floating point.

Fractional UGen

Unit generators are fractional.

Integral UGen

Unit generators are integral.

Num UGen

Unit generators are numbers.

Ord UGen

Unit generators are orderable (when Constants).

(constant 2 > constant 1) == True
Real UGen

Unit generators are real.

RealFrac UGen 
Show UGen 
Bits UGen

UGens are bit patterns.

Random UGen

Unit generators are stochastic.

TernaryOp UGen 
BinaryOp UGen 
UnaryOp UGen 
RealFracE UGen 
OrdE UGen 
EqE UGen 
Audible UGen 
Audible UGen 

Parser

Accessors

Predicates

isConstant :: UGen -> Bool Source

Constant node predicate.

isSink :: UGen -> Bool Source

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

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.

mce :: [UGen] -> UGen Source

Multiple channel expansion node constructor.

mrg :: [UGen] -> UGen Source

Multiple root graph constructor.

proxy :: UGen -> Int -> UGen Source

Unit generator proxy node constructor.

MCE

mceProxies :: MCE UGen -> [UGen] Source

Type specified mce_elem.

isMCE :: UGen -> Bool Source

Multiple channel expansion node (MCE_U) predicate.

mceChannels :: UGen -> [UGen] Source

Output channels of UGen as a list.

mceDegree :: UGen -> Int Source

Number of channels to expand to.

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

Extend UGen to specified degree.

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.

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