Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Event and Ctl systems for external control interfaces.
Synopsis
- type REvent t = (t, t, t, t, t, t, t, t, t, t)
- rEvent_from_list :: Num t => [t] -> REvent t
- rEventAddr :: UGen -> UGen -> UGen -> REvent UGen
- rEventVoicerAddr :: UGen -> UGen -> UGen -> Int -> (Int -> REvent UGen -> UGen) -> UGen
- rEvent :: REvent UGen
- rEventVoicer :: Int -> (Int -> REvent UGen -> UGen) -> UGen
- rEventGateReset :: UGen -> UGen -> (UGen, UGen)
- type RCtl = (UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen)
- rCtlAddr :: UGen -> UGen -> RCtl
- rCtlVoicerAddr :: UGen -> UGen -> Int -> (Int -> RCtl -> UGen) -> UGen
- rCtl :: RCtl
- rCtlVoicer :: Int -> (Int -> RCtl -> UGen) -> UGen
- type RCtl8 = (UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen)
- rCtl_to_rCtl8 :: RCtl -> RCtl8
- rCtl8Voicer :: Int -> (Int -> RCtl8 -> UGen) -> UGen
- sc3_control_spec :: Fractional t => [(String, (t, t, String))]
- kyma_event_value_ranges :: Fractional t => [(String, (t, t, String))]
Event
type REvent t = (t, t, t, t, t, t, t, t, t, t) Source #
(wgate,x,y,zforce,orientation,radius-x,radius-y,pitch,pitch-x,pitch-y)
rEvent_from_list :: Num t => [t] -> REvent t Source #
Translate list to REvent.
rEventAddr :: UGen -> UGen -> UGen -> REvent UGen Source #
k0 = index of control bus zero for event system, stp = voice index incremennt, c = event channel or voice (zero indexed)
rEventVoicerAddr :: UGen -> UGen -> UGen -> Int -> (Int -> REvent UGen -> UGen) -> UGen Source #
c0 = index of voice (channel) zero for event set, n = number of voices (channels)
rEvent :: REvent UGen Source #
rEventAddr
with control
inputs for eventAddr, eventIncr and eventZero.
rEventVoicer :: Int -> (Int -> REvent UGen -> UGen) -> UGen Source #
rEventVoicerAddr
with control
inputs for eventAddr, eventIncr and eventZero.
Ctl
type RCtl = (UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen, UGen) Source #
Sequence of 16 continous controller inputs in range (0-1).
rCtlAddr :: UGen -> UGen -> RCtl Source #
k0 = index of control bus zero for ctl system, c = ctl channel or voice (zero indexed)
rCtlVoicerAddr :: UGen -> UGen -> Int -> (Int -> RCtl -> UGen) -> UGen Source #
c0 = index of voice (channel) zero for ctl set, n = number of voices (channels)
rCtlVoicer :: Int -> (Int -> RCtl -> UGen) -> UGen Source #
rCtlVoicerAddr
with control
inputs for CtlAddr and CtlZero.
rCtl_to_rCtl8 :: RCtl -> RCtl8 Source #
Select first eight elements of RCtl.
Names
sc3_control_spec :: Fractional t => [(String, (t, t, String))] Source #
See SCClassLibraryCommonControl/Spec:ControlSpec.initClass
"ControlSpec defines the range and curve of a control"
kyma_event_value_ranges :: Fractional t => [(String, (t, t, String))] Source #
See Kyma X Revealed, p.403
"The following EventValue names are associated with initial ranges other than (0,1). EventValue names are not case-sensitive."
This list adds curve specifiers as strings.
let x = Data.List.intersect (map fst sc3_control_spec) (map fst kyma_event_value_ranges) x == ["beats","boostcut","freq","rate"] let c z = let (p,q) = unzip z in let f i = filter (flip elem i . fst) in zip (f p sc3_control_spec) (f q kyma_event_value_ranges) c (zip x x)
c [("lofreq","freqlow"),("midfreq","freqmid")] lookup "freqhigh" kyma_event_value_ranges