Safe Haskell | None |
---|
We can convert notes to sound signals with instruments. An instrument is a function:
(Arg a, Sigs b) => a -> SE b
It takes a tuple of primitive Csound values (number, string or array) and converts
it to the tuple of signals and it makes some side effects along the way so
the output is wrapped in the SE
-monad.
There are only three ways of making a sound with an instrument:
- Suplpy an instrument with notes (
Mix
-section). - Trigger an instrument with event stream (
Evt
-section). - By using midi-instruments (see
Csound.Control.Midi
).
Sometimes we don't want to produce any sound. Our instrument is just a procedure that makes something useful without being noisy about it. It's type is:
(Arg a) => a -> SE ()
To invoke the procedures there are functions with trailing underscore.
For example we have the function trig
to convert event stream to sound:
trig :: (Arg a, Sigs b) => (a -> SE b) -> Evts (D, D, a) -> b
and we have a trig
with underscore to convert the event stream to
the sequence of the procedure invkations:
trig_ :: (Arg a) => (a -> SE ()) -> Evts (D, D, a) -> SE ()
To invoke instruments from another instrumetnts we use artificial closures made with functions with trailing xxxBy. For example:
trigBy :: (Arg a, Arg c, Sigs b) => (a -> SE b) -> (c -> Evts (D, D, a)) -> (c -> b)
Notice that the event stream depends on the argument of the type c. Here goes all the parameters that we want to pass from the outer instrument. Unfortunately we can not just create the closure, because our values are not the real values. It's a text of the programm (a tiny snippet of it) to be executed. For a time being I don't know how to make it better. So we need to pass the values explicitly.
For example, if we want to make an arpeggiator:
pureTone :: D -> SE Sig pureTone cps = return $ mul env $ osc $ sig cps where env = linseg [0, 0.01, 1, 0.25, 0] majArpeggio :: D -> SE Sig majArpeggio = return . schedBy pureTone evts where evts cps = withDur 0.5 $ fmap (* cps) $ cycleE [1, 5/3, 3/2, 2] $ metroE 5 main = dac $ mul 0.5 $ midi $ onMsg majArpeggio
We should use schedBy
to pass the frequency as a parameter to the event stream.
- class Functor f => CsdSco f where
- toCsdEventList :: f a -> CsdEventList a
- singleCsdEvent :: CsdEvent a -> f a
- data Mix a
- sco :: (CsdSco f, Arg a, Sigs b) => (a -> SE b) -> f a -> f (Mix b)
- mix :: (Sigs a, CsdSco f) => f (Mix a) -> a
- eff :: (CsdSco f, Sigs a, Sigs b) => (a -> SE b) -> f (Mix a) -> f (Mix b)
- data CsdEventList a = CsdEventList {
- csdEventListDur :: Double
- csdEventListNotes :: [CsdEvent a]
- type CsdEvent a = (Double, Double, a)
- mixLoop :: (CsdSco f, Sigs a) => f (Mix a) -> a
- sco_ :: (CsdSco f, Arg a) => (a -> SE ()) -> f a -> f (Mix Unit)
- mix_ :: CsdSco f => f (Mix Unit) -> SE ()
- mixLoop_ :: CsdSco f => f (Mix Unit) -> SE ()
- mixBy :: (Arg a, Sigs b, CsdSco f) => (a -> f (Mix b)) -> a -> b
- trig :: (Arg a, Sigs b) => (a -> SE b) -> Evt (D, D, a) -> b
- sched :: (Arg a, Sigs b) => (a -> SE b) -> Evt (D, a) -> b
- schedHarp :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt a -> b
- schedUntil :: (Arg a, Sigs b) => (a -> SE b) -> Evt a -> Evt c -> b
- schedToggle :: Sigs b => SE b -> Evt D -> b
- trig_ :: Arg a => (a -> SE ()) -> Evt (D, D, a) -> SE ()
- sched_ :: Arg a => (a -> SE ()) -> Evt (D, a) -> SE ()
- schedUntil_ :: Arg a => (a -> SE ()) -> Evt a -> Evt c -> SE ()
- trigBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (D, D, a)) -> c -> b
- schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (D, a)) -> c -> b
- schedHarpBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt a) -> c -> b
- withDur :: D -> Evt a -> Evt (D, a)
- trigs :: (Arg a, Sigs b) => (a -> SE b) -> Evt [(D, D, a)] -> b
- scheds :: (Arg a, Sigs b) => (a -> SE b) -> Evt [(D, a)] -> b
- schedHarps :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b
- schedUntils :: (Arg a, Sigs b) => (a -> SE b) -> Evt [a] -> Evt c -> b
- trigs_ :: Arg a => (a -> SE ()) -> Evt [(D, D, a)] -> SE ()
- scheds_ :: Arg a => (a -> SE ()) -> Evt [(D, a)] -> SE ()
- schedUntils_ :: Arg a => (a -> SE ()) -> Evt [a] -> Evt c -> SE ()
- trigsBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt [(D, D, a)]) -> c -> b
- schedsBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt [(D, a)]) -> c -> b
- schedHarpsBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b
- withDurs :: D -> Evt [a] -> Evt [(D, a)]
- class Sigs (SigOuts a) => Outs a where
- onArg :: Outs b => (a -> b) -> a -> SE (SigOuts b)
- class AmpInstr a where
- type AmpInstrOut a :: *
- onAmp :: a -> D -> SE (AmpInstrOut a)
- class CpsInstr a where
- type CpsInstrOut a :: *
- onCps :: a -> (D, D) -> SE (CpsInstrOut a)
Mix
We can invoke instrument with specified notes. Eqch note happens at some time and lasts for some time. It contains the argument for the instrument.
We can invoke the instrument on the sequence of notes (sco
), process
the sequence of notes with an effect (eff
) and convert everything in
the plain sound signals (to send it to speakers or write to file or
use it in some another instrument).
The sequence of notes is represented with type class CsdSco
. Wich
has a very simple methods. So you can use your own favorite library
to describe the list of notes. If your type supports the scaling in
the time domain (stretching the timeline) you can do it in the Mix-version
(after the invokation of the instrument). All notes are rescaled all the
way down the Score-structure.
class Functor f => CsdSco f where
toCsdEventList :: f a -> CsdEventList a
singleCsdEvent :: CsdEvent a -> f a
data Mix a
data CsdEventList a
Functor CsdEventList | |
Foldable CsdEventList | |
Traversable CsdEventList | |
CsdSco CsdEventList | |
Eq a => Eq (CsdEventList a) | |
Show a => Show (CsdEventList a) |
Evt
Singlular
trig :: (Arg a, Sigs b) => (a -> SE b) -> Evt (D, D, a) -> bSource
Triggers an instrument with an event stream. The event stream contains triples:
(delay_after_event_is_fired, duration_of_the_event, argument_for_the_instrument)
sched :: (Arg a, Sigs b) => (a -> SE b) -> Evt (D, a) -> bSource
It's like the function trig
, but delay is set to zero.
schedHarp :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt a -> bSource
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.
schedUntil :: (Arg a, Sigs b) => (a -> SE b) -> Evt a -> Evt c -> bSource
Invokes an instrument with first event stream and holds the note until the second event stream is active.
schedToggle :: Sigs b => SE b -> Evt D -> bSource
Invokes an instrument with toggle event stream (1 stands for on and 0 stands for off).
trig_ :: Arg a => (a -> SE ()) -> Evt (D, D, a) -> SE ()Source
Triggers a procedure on the event stream.
sched_ :: Arg a => (a -> SE ()) -> Evt (D, a) -> SE ()Source
Triggers a procedure on the event stream. A delay time is set to zero.
schedUntil_ :: Arg a => (a -> SE ()) -> Evt a -> Evt c -> SE ()Source
Invokes an instrument with first event stream and holds the note until the second event stream is active.
trigBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (D, D, a)) -> c -> bSource
A closure to trigger an instrument inside the body of another instrument.
schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (D, a)) -> c -> bSource
A closure to trigger an instrument inside the body of another instrument.
schedHarpBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt a) -> c -> bSource
A closure to trigger an instrument inside the body of another instrument.
withDur :: D -> Evt a -> Evt (D, a)Source
Sets the same duration for all events. It's useful with the functions sched
, schedBy
, sched_
.
Plural
schedUntils :: (Arg a, Sigs b) => (a -> SE b) -> Evt [a] -> Evt c -> bSource
Invokes an instrument with first event stream and holds the note until the second event stream is active.
schedUntils_ :: Arg a => (a -> SE ()) -> Evt [a] -> Evt c -> SE ()Source
Invokes an instrument with first event stream and holds the note until the second event stream is active.
withDurs :: D -> Evt [a] -> Evt [(D, a)]Source
Sets the same duration for all events. It's useful with the functions scheds
, schedsBy
, scheds_
.
Overload
Converters to make it easier a construction of the instruments.
Constructs a drum-like instrument. Drum like instrument has a single argument that signifies an amplitude.
type AmpInstrOut a :: *Source
onAmp :: a -> D -> SE (AmpInstrOut a)Source
Constructs a simple instrument that takes in a tuple of two arguments. They are amplitude and the frequency (in Hz or cycles per second).
type CpsInstrOut a :: *Source
CpsInstr ((Sig, Sig) -> (Sig, Sig)) | |
CpsInstr ((Sig, Sig) -> Sig) | |
CpsInstr ((Sig, Sig) -> SE (Sig, Sig)) | |
CpsInstr ((Sig, Sig) -> SE Sig) | |
CpsInstr ((Sig, D) -> (Sig, Sig)) | |
CpsInstr ((Sig, D) -> Sig) | |
CpsInstr ((Sig, D) -> SE (Sig, Sig)) | |
CpsInstr ((Sig, D) -> SE Sig) | |
CpsInstr ((D, Sig) -> (Sig, Sig)) | |
CpsInstr ((D, Sig) -> Sig) | |
CpsInstr ((D, Sig) -> SE (Sig, Sig)) | |
CpsInstr ((D, Sig) -> SE Sig) | |
CpsInstr ((D, D) -> (Sig, Sig)) | |
CpsInstr ((D, D) -> Sig) | |
CpsInstr ((D, D) -> SE (Sig, Sig)) | |
CpsInstr ((D, D) -> SE Sig) | |
CpsInstr (Sig -> (Sig, Sig)) | |
CpsInstr (Sig -> Sig) | |
CpsInstr (Sig -> SE (Sig, Sig)) | |
CpsInstr (Sig -> SE Sig) | |
CpsInstr (D -> (Sig, Sig)) | |
CpsInstr (D -> Sig) | |
CpsInstr (D -> SE (Sig, Sig)) | |
CpsInstr (D -> SE Sig) |