Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Unit Generator (UGen
) and associated types and instances.
Synopsis
- type UID_t = Int
- data UGenId
- no_id :: UGenId
- type Sample = Double
- newtype Constant = Constant {}
- data Control_Meta n = Control_Meta {
- ctl_min :: n
- ctl_max :: n
- ctl_warp :: String
- ctl_step :: n
- ctl_units :: String
- controlGroup :: Maybe Control_Group
- type Control_Meta_T3 n = (n, n, String)
- control_meta_t3 :: Num m => (n -> m) -> Control_Meta_T3 n -> Control_Meta m
- type Control_Meta_T5 n = (n, n, String, n, String)
- control_meta_t5 :: (n -> m) -> Control_Meta_T5 n -> Control_Meta m
- data Control_Group
- control_group_degree :: Control_Group -> Int
- control_group_suffixes :: Control_Group -> [String]
- data Control = Control {}
- newtype Label = Label {}
- type Output = Rate
- newtype Special = Special Int
- data Primitive = Primitive {
- ugenRate :: Rate
- ugenName :: String
- ugenInputs :: [UGen]
- ugenOutputs :: [Output]
- ugenSpecial :: Special
- ugenId :: UGenId
- data Proxy = Proxy {}
- data MRG = MRG {}
- data UGen
- roundTo :: UGen -> UGen -> UGen
- parse_constant :: String -> Maybe UGen
- un_constant :: UGen -> Maybe Constant
- u_constant :: UGen -> Maybe Sample
- u_constant_err :: UGen -> Sample
- mrg :: [UGen] -> UGen
- mrg_leftmost :: UGen -> UGen
- isConstant :: UGen -> Bool
- isSink :: UGen -> Bool
- un_proxy :: UGen -> Maybe Proxy
- isProxy :: UGen -> Bool
- mce :: [UGen] -> UGen
- mceProxies :: MCE UGen -> [UGen]
- isMCE :: UGen -> Bool
- mceChannels :: UGen -> [UGen]
- mceDegree :: UGen -> Maybe Int
- mceDegree_err :: UGen -> Int
- mceExtend :: Int -> UGen -> [UGen]
- mceRequired :: [UGen] -> Bool
- mceInputTransform :: [UGen] -> Maybe [[UGen]]
- mceBuild :: ([UGen] -> UGen) -> [UGen] -> UGen
- mce_is_direct_proxy :: MCE UGen -> Bool
- checkInput :: UGen -> UGen
- constant :: Real n => n -> UGen
- int_to_ugen :: Int -> UGen
- float_to_ugen :: Float -> UGen
- double_to_ugen :: Double -> UGen
- proxy :: UGen -> Int -> UGen
- rateOf :: UGen -> Rate
- proxify :: UGen -> UGen
- mk_ugen_select_rate :: String -> [UGen] -> [Rate] -> Either Rate [Int] -> Rate
- mkUGen :: Maybe ([Sample] -> Sample) -> [Rate] -> Either Rate [Int] -> String -> [UGen] -> Maybe [UGen] -> Int -> Special -> UGenId -> UGen
- mkOperator :: ([Sample] -> Sample) -> String -> [UGen] -> Int -> UGen
- mkUnaryOperator :: SC3_Unary_Op -> (Sample -> Sample) -> UGen -> UGen
- mkBinaryOperator_optimise_constants :: SC3_Binary_Op -> (Sample -> Sample -> Sample) -> (Either Sample Sample -> Bool) -> UGen -> UGen -> UGen
- mkBinaryOperator :: SC3_Binary_Op -> (Sample -> Sample -> Sample) -> UGen -> UGen -> UGen
- is_math_binop :: Int -> UGen -> Bool
- is_add_operator :: UGen -> Bool
- assert_is_add_operator :: String -> UGen -> UGen
- is_mul_operator :: UGen -> Bool
- mul_add_optimise_direct :: UGen -> UGen
- mul_add_optimise :: UGen -> UGen
- sum3_optimise_direct :: UGen -> UGen
- sum3_optimise :: UGen -> UGen
- add_optimise :: UGen -> UGen
Basic types
Constants.
Constant 3 == Constant 3 (Constant 3 > Constant 1) == True
data Control_Meta n Source #
Control meta-data.
Control_Meta | |
|
Instances
Eq n => Eq (Control_Meta n) Source # | |
Defined in Sound.SC3.UGen.Type (==) :: Control_Meta n -> Control_Meta n -> Bool # (/=) :: Control_Meta n -> Control_Meta n -> Bool # | |
Read n => Read (Control_Meta n) Source # | |
Defined in Sound.SC3.UGen.Type readsPrec :: Int -> ReadS (Control_Meta n) # readList :: ReadS [Control_Meta n] # readPrec :: ReadPrec (Control_Meta n) # readListPrec :: ReadPrec [Control_Meta n] # | |
Show n => Show (Control_Meta n) Source # | |
Defined in Sound.SC3.UGen.Type showsPrec :: Int -> Control_Meta n -> ShowS # show :: Control_Meta n -> String # showList :: [Control_Meta n] -> ShowS # |
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.
Instances
Eq Control_Group Source # | |
Defined in Sound.SC3.UGen.Type (==) :: Control_Group -> Control_Group -> Bool # (/=) :: Control_Group -> Control_Group -> Bool # | |
Read Control_Group Source # | |
Defined in Sound.SC3.UGen.Type readsPrec :: Int -> ReadS Control_Group # readList :: ReadS [Control_Group] # | |
Show Control_Group Source # | |
Defined in Sound.SC3.UGen.Type showsPrec :: Int -> Control_Group -> ShowS # show :: Control_Group -> String # showList :: [Control_Group] -> ShowS # |
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.
Control inputs. It is an invariant that controls with equal names within a UGen graph must be equal in all other respects.
Control | |
|
Operating mode of unary and binary operators.
UGen primitives.
Primitive | |
|
Proxy indicating an output port at a multi-channel primitive.
Proxy | |
|
Union type of Unit Generator forms.
Constant_U Constant | |
Control_U Control | |
Label_U Label | |
Primitive_U Primitive | |
Proxy_U Proxy | |
MCE_U (MCE UGen) | |
MRG_U MRG |
Instances
Parser
Accessors
un_constant :: UGen -> Maybe Constant Source #
See into Constant_U
.
u_constant :: UGen -> Maybe Sample Source #
Value of Constant_U
Constant
.
u_constant_err :: UGen -> Sample Source #
Erroring variant.
MRG
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.
MCE
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
Constructors
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_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).
add_optimise :: UGen -> UGen Source #