Safe Haskell | None |
---|---|
Language | Haskell2010 |
Csound.Typed.Control
Contents
- newtype SE a = SE {
- unSE :: Dep a
- data LocalHistory :: * = LocalHistory {
- expDependency :: E
- newLineNum :: Int
- newLocalVarId :: Int
- runSE :: SE a -> GE a
- execSE :: SE () -> GE InstrBody
- evalSE :: SE a -> GE a
- execGEinSE :: SE (GE a) -> SE a
- hideGEinDep :: GE (Dep a) -> Dep a
- fromDep :: Dep a -> SE (GE a)
- fromDep_ :: Dep () -> SE ()
- geToSe :: GE a -> SE a
- newLocalVar :: Rate -> GE E -> SE Var
- newLocalVars :: [Rate] -> GE [E] -> SE [Var]
- newGlobalVars :: [Rate] -> GE [E] -> SE [Var]
- newtype Ref a = Ref [Var]
- writeRef :: Tuple a => Ref a -> a -> SE ()
- readRef :: Tuple a => Ref a -> SE a
- newRef :: Tuple a => a -> SE (Ref a)
- mixRef :: (Num a, Tuple a) => Ref a -> a -> SE ()
- modifyRef :: Tuple a => Ref a -> (a -> a) -> SE ()
- sensorsSE :: Tuple a => a -> SE (SE a, a -> SE ())
- newGlobalRef :: Tuple a => a -> SE (Ref a)
- globalSensorsSE :: Tuple a => a -> SE (SE a, a -> SE ())
- instr0 :: Tuple a => SE a -> SE a
- getIns :: Sigs a => SE a
- setDur :: Sigs a => D -> a -> a
- freshId :: SE D
- data Mix a
- sco :: (Arg a, Sigs b) => (a -> SE b) -> Sco a -> Sco (Mix b)
- eff :: (Sigs a, Sigs b) => (a -> SE b) -> Sco (Mix a) -> Sco (Mix b)
- mix :: Sigs a => Sco (Mix a) -> a
- mixBy :: (Arg a, Sigs b) => (a -> Sco (Mix b)) -> a -> b
- sco_ :: Arg a => (a -> SE ()) -> Sco a -> Sco (Mix Unit)
- mix_ :: Sco (Mix Unit) -> SE ()
- mixBy_ :: Arg a => (a -> Sco (Mix Unit)) -> a -> SE ()
- type Sco a = Track D a
- type CsdEventList a = Track D a
- type CsdEvent = (Double, Double, Note)
- data Msg
- type Channel = Int
- midi :: (Num a, Sigs a) => (Msg -> SE a) -> SE a
- midin :: (Num a, Sigs a) => Channel -> (Msg -> SE a) -> SE a
- pgmidi :: (Num a, Sigs a) => Maybe Int -> Channel -> (Msg -> SE a) -> SE a
- midi_ :: (Msg -> SE ()) -> SE ()
- midin_ :: Channel -> (Msg -> SE ()) -> SE ()
- pgmidi_ :: Maybe Int -> Channel -> (Msg -> SE ()) -> SE ()
- initMidiCtrl :: D -> D -> D -> SE ()
- data OscRef
- type OscHost = String
- type OscPort = Int
- type OscAddress = String
- type OscType = String
- initOsc :: OscPort -> SE OscRef
- listenOsc :: forall a. Tuple a => OscRef -> OscAddress -> OscType -> Evt a
- sendOsc :: forall a. Tuple a => OscHost -> OscPort -> OscAddress -> OscType -> Evt a -> SE ()
- chnGetD :: Str -> SE D
- chnGetSig :: Str -> SE Sig
- chnGetCtrl :: Str -> SE Sig
- chnGetStr :: Str -> SE Str
- chnSetD :: D -> Str -> SE ()
- chnSetSig :: Sig -> Str -> SE ()
- chnSetCtrl :: Sig -> Str -> SE ()
- chnSetStr :: Str -> Str -> SE ()
- data Sf
- unSf :: Sf -> GE E
- sched :: (Arg a, Sigs b) => (a -> SE b) -> Evt (Sco a) -> b
- sched_ :: Arg a => (a -> SE ()) -> Evt (Sco a) -> SE ()
- schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (Sco a)) -> c -> b
- schedHarp :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b
- schedHarpBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b
- retrigs :: (Arg a, Sigs b) => (a -> SE b) -> Evt [a] -> b
- evtLoop :: (Num a, Tuple a, Sigs a) => Maybe (Evt Unit) -> [SE a] -> [Evt Unit] -> a
- evtLoopOnce :: (Num a, Tuple a, Sigs a) => Maybe (Evt Unit) -> [SE a] -> [Evt Unit] -> a
- saw :: Sig -> Sig
- isaw :: Sig -> Sig
- pulse :: Sig -> Sig
- tri :: Sig -> Sig
- sqr :: Sig -> Sig
- blosc :: Tab -> Sig -> Sig
- saw' :: D -> Sig -> Sig
- isaw' :: D -> Sig -> Sig
- pulse' :: D -> Sig -> Sig
- tri' :: D -> Sig -> Sig
- sqr' :: D -> Sig -> Sig
- blosc' :: Tab -> D -> Sig -> Sig
SE
The Csound's IO
-monad. All values that produce side effects are wrapped
in the SE
-monad.
data LocalHistory :: *
Constructors
LocalHistory | |
Fields
|
Instances
execGEinSE :: SE (GE a) -> SE a Source
hideGEinDep :: GE (Dep a) -> Dep a Source
SE reference
newRef :: Tuple a => a -> SE (Ref a) Source
Allocates a new local (it is visible within the instrument) mutable value and initializes it with value. A reference can contain a tuple of variables.
mixRef :: (Num a, Tuple a) => Ref a -> a -> SE () Source
Adds the given signal to the value that is contained in the reference.
modifyRef :: Tuple a => Ref a -> (a -> a) -> SE () Source
Modifies the Ref value with given function.
sensorsSE :: Tuple a => a -> SE (SE a, a -> SE ()) Source
An alias for the function newRef
. It returns not the reference
to mutable value but a pair of reader and writer functions.
newGlobalRef :: Tuple a => a -> SE (Ref a) Source
Allocates a new global mutable value and initializes it with value. A reference can contain a tuple of variables.
globalSensorsSE :: Tuple a => a -> SE (SE a, a -> SE ()) Source
An alias for the function newRef
. It returns not the reference
to mutable value but a pair of reader and writer functions.
Global settings
setDur :: Sigs a => D -> a -> a Source
Sets the global duration of the file or output signal to the given value.
It should be used only once! The proper place is in the top-most
expression before sending to dac
or writeWav
.
Misc
Score
Special type that represents a scores of sound signals. If an instrument is triggered with the scores the result is wrapped in the value of this type.
sco :: (Arg a, Sigs b) => (a -> SE b) -> Sco a -> Sco (Mix b) Source
Plays a bunch of notes with the given instrument.
res = sco instrument scores
eff :: (Sigs a, Sigs b) => (a -> SE b) -> Sco (Mix a) -> Sco (Mix b) Source
Applies an effect to the sound. Effect is applied to the sound on the give track.
res = eff effect sco
effect
- a function that takes a tuple of signals and produces a tuple of signals.sco
- something that is constructed withsco
oreff
.
With the function eff
you can apply a reverb or adjust the
level of the signal. It functions like a mixing board but unlike mixing
board it produces the value that you can arrange with functions from your
favorite Score-generation library. You can delay it or mix with some other track and
apply some another effect on top of it!
mix :: Sigs a => Sco (Mix a) -> a Source
Renders a scores to the sound signals. we can use it inside the other instruments.
mixBy :: (Arg a, Sigs b) => (a -> Sco (Mix b)) -> a -> b Source
Imitates a closure for a bunch of notes to be played within another instrument.
sco_ :: Arg a => (a -> SE ()) -> Sco a -> Sco (Mix Unit) Source
Invokes a procedure for the given bunch of events.
mix_ :: Sco (Mix Unit) -> SE () Source
Converts a bunch of procedures scheduled with scores to a single procedure.
mixBy_ :: Arg a => (a -> Sco (Mix Unit)) -> a -> SE () Source
Imitates a closure for a bunch of procedures to be played within another instrument.
type CsdEventList a = Track D a Source
type CsdEvent = (Double, Double, Note)
The Csound note. It's a triple of
(startTime, duration, parameters)
Midi
Instances
DirtyMulti b => DirtyMulti (Msg -> b) Source | |
PureMulti b => PureMulti (Msg -> b) Source | |
Procedure b => Procedure (Msg -> b) Source | |
DirtySingle b => DirtySingle (Msg -> b) Source | |
PureSingle b => PureSingle (Msg -> b) Source |
midi :: (Num a, Sigs a) => (Msg -> SE a) -> SE a Source
Triggers a midi-instrument (aka Csound's massign) for all channels. It's useful to test a single instrument.
midin :: (Num a, Sigs a) => Channel -> (Msg -> SE a) -> SE a Source
Triggers a midi-instrument (aka Csound's massign) on the specified channel.
pgmidi :: (Num a, Sigs a) => Maybe Int -> Channel -> (Msg -> SE a) -> SE a Source
Triggers a midi-instrument (aka Csound's pgmassign) on the specified programm bank.
midi_ :: (Msg -> SE ()) -> SE () Source
Triggers a midi-procedure (aka Csound's massign) for all channels.
midin_ :: Channel -> (Msg -> SE ()) -> SE () Source
Triggers a midi-procedure (aka Csound's pgmassign) on the given channel.
pgmidi_ :: Maybe Int -> Channel -> (Msg -> SE ()) -> SE () Source
Triggers a midi-procedure (aka Csound's pgmassign) on the given programm bank.
OSC
type OscAddress = String Source
Path-like string ("foobar/baz")
The string specifies the type of expected arguments. The string can contain the characters "bcdfilmst" which stand for Boolean, character, double, float, 32-bit integer, 64-bit integer, MIDI, string and timestamp.
initOsc :: OscPort -> SE OscRef Source
Initializes host client. The process starts to run in the background.
listenOsc :: forall a. Tuple a => OscRef -> OscAddress -> OscType -> Evt a Source
Listens for the OSC-messages. The first argument is OSC-reference.
We can create it with the function oscInit
. The next two arguments are strings.
The former specifies the path-like address to listen the messages. It can be:
/foo/bar/baz
The latter specifies the type of expected arguments. The string can contain the characters "bcdfilmst" which stand for Boolean, character, double, float, 32-bit integer, 64-bit integer, MIDI, string and timestamp.
The result is an event of messages. We can run a callback on it
with standard function runEvt
:
runEvt :: Evt a -> (a -> SE ()) -> SE ()
sendOsc :: forall a. Tuple a => OscHost -> OscPort -> OscAddress -> OscType -> Evt a -> SE () Source
Sends OSC-messages. It takes in a name of the host computer (empty string is alocal machine), port on which the target machine is listening, OSC-addres and type. The last argument produces the values for OSC-messages.
Channel
Getters
chnGetCtrl :: Str -> SE Sig Source
Reads a control signal. The control signals are updated at the lower rate.
Setters
chnSetCtrl :: Sig -> Str -> SE () Source
Writes a control signal. The control signals are updated at the lower rate.
Sf2
The sf2 sound font preset. It is defined with file name, bank and program integers.
Events
sched_ :: Arg a => (a -> SE ()) -> Evt (Sco a) -> SE () Source
Triggers a procedure on the event stream.
schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (Sco a)) -> c -> b Source
A closure to trigger an instrument inside the body of another instrument.
schedHarp :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b Source
An instrument is triggered with event stream and delay time is set to zero (event fires immediately) and duration is set to inifinite time. The note is held while the instrument is producing something. If the instrument is silent for some seconds (specified in the first argument) then it's turned off.
schedHarpBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b Source
A closure to trigger an instrument inside the body of another instrument.
retrigs :: (Arg a, Sigs b) => (a -> SE b) -> Evt [a] -> b Source
Retriggers an instrument every time an event happens. The note is held until the next event happens.