hsc3-0.19.1: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.SC3.UGen.Type

Description

Unit Generator (UGen) and associated types and instances.

Synopsis

Basic types

type UID_t = Int Source #

Type of unique identifier.

data UGenId Source #

Data type for the identifier at a Primitive UGen.

Constructors

NoId 
UId UID_t 

Instances

Instances details
Eq UGenId Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

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

Read UGenId Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show UGenId Source # 
Instance details

Defined in Sound.SC3.UGen.Type

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.

newtype Constant Source #

Constants.

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

Constructors

Constant 

Instances

Instances details
Eq Constant Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Ord Constant Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Read Constant Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show Constant Source # 
Instance details

Defined in Sound.SC3.UGen.Type

data Control_Meta n Source #

Control meta-data.

Constructors

Control_Meta 

Fields

Instances

Instances details
Eq n => Eq (Control_Meta n) Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Read n => Read (Control_Meta n) Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show n => Show (Control_Meta n) Source # 
Instance details

Defined in Sound.SC3.UGen.Type

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

3-tuple form of Control_Meta data.

control_meta_t3 :: Num m => (n -> m) -> Control_Meta_T3 n -> Control_Meta m Source #

Lift Control_Meta_T3 to Control_Meta allowing type coercion.

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

5-tuple form of Control_Meta data.

control_meta_t5 :: (n -> m) -> Control_Meta_T5 n -> Control_Meta m Source #

Lift Control_Meta_T5 to Control_Meta allowing type coercion.

data Control_Group Source #

Controls may form part of a control group.

control_group_degree :: Control_Group -> Int Source #

The number of elements in a control group.

control_group_suffixes :: Control_Group -> [String] Source #

Grouped controls have names that have equal prefixes and identifying suffixes. Range controls have two elements, minima and maxima, suffixes are [ and ]. Array controls have N elements and have IX suffixes. XY controls have two elements, X and Y coordinates, suffixes are X and Y.

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

Instances details
Eq Control Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

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

Read Control Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show Control Source # 
Instance details

Defined in Sound.SC3.UGen.Type

newtype Label Source #

Labels.

Constructors

Label 

Fields

Instances

Instances details
Eq Label Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

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

Read Label Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show Label Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

type Output = Rate Source #

Unit generator output descriptor.

newtype Special Source #

Operating mode of unary and binary operators.

Constructors

Special Int 

Instances

Instances details
Eq Special Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

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

Read Special Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show Special Source # 
Instance details

Defined in Sound.SC3.UGen.Type

data Primitive Source #

UGen primitives.

Instances

Instances details
Eq Primitive Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Read Primitive Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show Primitive Source # 
Instance details

Defined in Sound.SC3.UGen.Type

data Proxy Source #

Proxy indicating an output port at a multi-channel primitive.

Constructors

Proxy 

Instances

Instances details
Eq Proxy Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

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

Read Proxy Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show Proxy Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

showsPrec :: Int -> Proxy -> ShowS #

show :: Proxy -> String #

showList :: [Proxy] -> ShowS #

data MRG Source #

Multiple root graph.

Constructors

MRG 

Fields

Instances

Instances details
Eq MRG Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

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

Read MRG Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Show MRG Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

showsPrec :: Int -> MRG -> ShowS #

show :: MRG -> String #

showList :: [MRG] -> ShowS #

data UGen Source #

Union type of Unit Generator forms.

Instances

Instances details
Enum UGen Source #

Unit generators are enumerable.

Instance details

Defined in Sound.SC3.UGen.Type

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 # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

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

Floating UGen Source #

Unit generators are floating point.

Instance details

Defined in Sound.SC3.UGen.Type

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.

Instance details

Defined in Sound.SC3.UGen.Type

Methods

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

recip :: UGen -> UGen #

fromRational :: Rational -> UGen #

Integral UGen Source #

Unit generators are integral.

Instance details

Defined in Sound.SC3.UGen.Type

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.

Instance details

Defined in Sound.SC3.UGen.Type

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
Instance details

Defined in Sound.SC3.UGen.Type

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 # 
Instance details

Defined in Sound.SC3.UGen.Type

Real UGen Source #

Unit generators are real.

Instance details

Defined in Sound.SC3.UGen.Type

Methods

toRational :: UGen -> Rational #

RealFrac UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

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 # 
Instance details

Defined in Sound.SC3.UGen.Type

Methods

showsPrec :: Int -> UGen -> ShowS #

show :: UGen -> String #

showList :: [UGen] -> ShowS #

Bits UGen Source #

UGens are bit patterns.

Instance details

Defined in Sound.SC3.UGen.Type

Random UGen Source #

Unit generators are stochastic.

Instance details

Defined in Sound.SC3.UGen.Type

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] #

BinaryOp UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

UnaryOp UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

RealFracE UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

OrdE UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

EqE UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

Audible UGen Source # 
Instance details

Defined in Sound.SC3.Server.Transport.FD

Methods

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

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

Audible UGen Source # 
Instance details

Defined in Sound.SC3.Server.Transport.Monad

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.

mceRequired :: [UGen] -> Bool Source #

Is MCE required, ie. are any input values MCE?

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

Apply MCE transform to a list of inputs. The transform extends each input so all are of equal length, and then transposes the matrix.

mceInputTransform [mce2 1 2,mce2 3 4] == Just [[1,3],[2,4]]
mceInputTransform [mce2 1 2,mce2 3 4,mce3 5 6 7] == Just [[1,3,5],[2,4,6],[1,3,7]]

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.

mk_ugen_select_rate :: String -> [UGen] -> [Rate] -> Either Rate [Int] -> Rate Source #

Filters with DR inputs run at KR. This is a little unfortunate, it'd be nicer if the rate in this circumstance could be given.

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, i_mce = list of MCE inputs, o = outputs.

Operators

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

Operator UGen constructor.

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

Unary math constructor.

mkBinaryOperator_optimise_constants :: SC3_Binary_Op -> (Sample -> Sample -> Sample) -> (Either Sample Sample -> Bool) -> UGen -> UGen -> UGen Source #

Binary math constructor with constant optimisation.

constant 2 * constant 3 == constant 6
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 :: SC3_Binary_Op -> (Sample -> Sample -> Sample) -> UGen -> UGen -> UGen Source #

Plain (non-optimised) binary math constructor.

Numeric instances

is_math_binop :: Int -> UGen -> Bool Source #

Is u a binary math operator with SPECIAL of k.

is_add_operator :: UGen -> Bool Source #

Is u an ADD operator?

is_mul_operator :: UGen -> Bool Source #

Is u an MUL operator?

mul_add_optimise_direct :: UGen -> UGen Source #

MulAdd re-writer, applicable only directly at add operator UGen. The MulAdd UGen is very sensitive to input rates. ADD=AR with IN|MUL=IR|CONST will CRASH scsynth.

mul_add_optimise :: UGen -> UGen Source #

MulAdd optimiser, applicable at any UGen (ie. checks u is an ADD ugen)

import Sound.SC3
g1 = sinOsc AR 440 0 * 0.1 + control IR "x" 0.05
g2 = sinOsc AR 440 0 * control IR "x" 0.1 + 0.05
g3 = control IR "x" 0.1 * sinOsc AR 440 0 + 0.05
g4 = 0.05 + sinOsc AR 440 0 * 0.1

sum3_optimise_direct :: UGen -> UGen Source #

Sum3 re-writer, applicable only directly at add operator UGen.

sum3_optimise :: UGen -> UGen Source #

Sum3 optimiser, applicable at any u (ie. checks if u is an ADD operator).