Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Unit generator (Ugen) type and instances.
Synopsis
- type Sample = Double
- data Ugen
- ugen_user_name :: String -> Special -> String
- 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 Ugen)
- isProxy :: Ugen -> Bool
- ugenPrimitive :: Ugen -> Maybe (Primitive Ugen)
- isPrimitive :: 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
- bracketUgen :: Ugen -> Brackets -> Ugen
- ugenBrackets :: Ugen -> Brackets
- 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_primitive_for :: String -> Ugen -> Bool
- is_constant_of :: Sample -> Ugen -> Bool
- 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
Union type of Unit Generator forms.
Constant_U Constant | |
Control_U Control | |
Label_U Label | |
Primitive_U (Primitive Ugen) | |
Proxy_U (Proxy Ugen) | |
Mce_U (Mce Ugen) | |
Mrg_U (Mrg Ugen) |
Instances
Name
ugen_user_name :: String -> Special -> String Source #
Lookup operator name for operator Ugens, else Ugen name.
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.
ugenPrimitive :: Ugen -> Maybe (Primitive Ugen) Source #
Get Primitive from Ugen if Ugen is a Primitive.
Mce
mceProxies :: Mce Ugen -> [Ugen] Source #
Type specified mce_to_list
.
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]] mceInputTransform [mce2 (mce2 1 2) (mce2 3 4),mce2 5 6] == Just [[mce2 1 2,5],[mce2 3 4,6]]
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. It's also useful when editing a Primitive after it is constructed, as in bracketUgen.
Bracketed
bracketUgen :: Ugen -> Brackets -> Ugen Source #
Attach Brackets (initialisation and cleanup message sequences) to Ugen. For simplicity and clarity, brackets can only be attached to Primitive, Constant and Control nodes. This will look into the direct (immediate) proxies of a Primitive.
ugenBrackets :: Ugen -> Brackets Source #
Retrieve Brackets from Ugen.
Validators
Constructors
mk_ugen_select_rate :: String -> [Ugen] -> [Rate] -> Either Rate [Int] -> Rate Source #
Filters with DemandRate inputs run at ControlRate. 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=AudioRate with In|Mul=InitialisationRate|Const will crash scsynth. This only considers primitives that do not have bracketing messages.
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. This only considers nodes that have no bracketing messages.
sum3_optimise :: Ugen -> Ugen Source #
Sum3 optimiser, applicable at any u (ie. checks if u is an ADD operator).
add_optimise :: Ugen -> Ugen Source #