Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
Synopsis
- type Sco a = Track Sig a
- data Mix a
- sco :: (Arg a, Sigs b) => (a -> SE b) -> Sco a -> Sco (Mix b)
- mix :: Sigs a => Sco (Mix a) -> a
- eff :: (Sigs a, Sigs b) => (a -> SE b) -> Sco (Mix a) -> Sco (Mix b)
- monoSco :: Sigs a => (MonoArg -> SE a) -> Sco (D, D) -> Sco (Mix a)
- mixLoop :: Sigs a => Sco (Mix a) -> a
- sco_ :: Arg a => (a -> SE ()) -> Sco a -> Sco (Mix Unit)
- mix_ :: Sco (Mix Unit) -> SE ()
- mixLoop_ :: Sco (Mix Unit) -> SE ()
- mixBy :: (Arg a, Sigs b) => (a -> Sco (Mix b)) -> a -> b
- infiniteDur :: Num a => a
- data Event t a = Event {
- eventStart :: t
- eventDur :: t
- eventContent :: a
- str :: Stretch a => DurOf a -> a -> a
- dur :: Duration a => a -> DurOf a
- temp :: Num t => a -> Track t a
- mapEvents :: Num t => (Event t a -> Event t b) -> Track t a -> Track t b
- sched :: (Arg a, Sigs b) => (a -> SE b) -> Evt (Sco a) -> b
- retrig :: (Arg a, Sigs b) => (a -> SE b) -> Evt 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
- sched_ :: Arg a => (a -> SE ()) -> Evt (Sco a) -> SE ()
- schedUntil_ :: Arg a => (a -> SE ()) -> Evt a -> Evt c -> SE ()
- schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (Sco a)) -> c -> b
- schedHarpBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b
- schedStream :: (Arg a, Sigs b) => D -> D -> (a -> SE b) -> Evt a -> SE b
- withDur :: Sig -> Evt a -> Evt (Sco a)
- monoSched :: Evt (Sco (D, D)) -> SE MonoArg
- trigByName :: (Arg a, Sigs b) => Text -> (a -> SE b) -> SE b
- trigByName_ :: Arg a => Text -> (a -> SE ()) -> SE ()
- trigByNameMidi :: (Arg a, Sigs b) => Text -> ((D, D, a) -> SE b) -> SE b
- trigByNameMidi_ :: Arg a => Text -> ((D, D, a) -> SE ()) -> SE ()
- turnoffByName :: String -> Sig -> Sig -> SE ()
- alwaysOn :: SE () -> SE ()
- playWhen :: forall a b. Sigs a => BoolSig -> (b -> SE a) -> b -> SE a
- class Sigs (SigOuts a) => Outs a where
- onArg :: Outs b => (a -> b) -> a -> SE (SigOuts b)
- class AmpInstr a where
- type AmpInstrOut a :: Type
- onAmp :: a -> D -> SE (AmpInstrOut a)
- class CpsInstr a where
- type CpsInstrOut a :: Type
- onCps :: a -> (D, D) -> SE (CpsInstrOut a)
- data InstrRef a
- newInstr :: Arg a => (a -> SE ()) -> SE (InstrRef a)
- scheduleEvent :: Arg a => InstrRef a -> D -> D -> a -> SE ()
- turnoff2 :: InstrRef a -> Sig -> Sig -> SE ()
- negateInstrRef :: InstrRef a -> InstrRef a
- addFracInstrRef :: D -> D -> InstrRef a -> InstrRef a
- newOutInstr :: (Arg a, Sigs b) => (a -> SE b) -> SE (InstrRef a, b)
- noteOn :: Arg a => D -> D -> InstrRef a -> a -> SE ()
- noteOff :: (Default a, Arg a) => D -> D -> InstrRef a -> SE ()
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.
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.
Instances
sco :: (Arg a, Sigs b) => (a -> SE b) -> Sco a -> Sco (Mix b) #
Plays a bunch of notes with the given instrument.
res = sco instrument scores
mix :: Sigs a => Sco (Mix a) -> a #
Renders a scores to the sound signals. we can use it inside the other instruments.
eff :: (Sigs a, Sigs b) => (a -> SE b) -> Sco (Mix a) -> Sco (Mix b) #
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!
monoSco :: Sigs a => (MonoArg -> SE a) -> Sco (D, D) -> Sco (Mix a) #
Plays a bunch of notes with the given monophonic instrument. See details on type MonoArg
.
The scores contain the pairs of amplitude (0 to 1) and frequency (in Hz).
res = monoSco instrument scores
sco_ :: Arg a => (a -> SE ()) -> Sco a -> Sco (Mix Unit) #
Invokes a procedure for the given bunch of events.
mix_ :: Sco (Mix Unit) -> SE () #
Converts a bunch of procedures scheduled with scores to a single procedure.
mixBy :: (Arg a, Sigs b) => (a -> Sco (Mix b)) -> a -> b #
Imitates a closure for a bunch of notes to be played within another instrument.
infiniteDur :: Num a => a #
Constant time events. Value a
starts at some time
and lasts for some time.
Event | |
|
temp :: Num t => a -> Track t a #
temp
constructs just an event.
Value of type a lasts for one time unit and starts at zero.
mapEvents :: Num t => (Event t a -> Event t b) -> Track t a -> Track t b #
General mapping. Maps not only values but events.
Evt
schedHarp :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b #
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 -> b Source #
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 -> b Source #
Invokes an instrument with toggle event stream (1 stands for on and 0 stands for off).
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.
schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (Sco a)) -> c -> b #
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 -> b #
A closure to trigger an instrument inside the body of another instrument.
schedStream :: (Arg a, Sigs b) => D -> D -> (a -> SE b) -> Evt a -> SE b Source #
Plays infinite notes for a given instrument with event stream. It allows for note overlap on release. We can specify release time on seconds in the first argument.
schedStream releaseTime instr evt
withDur :: Sig -> Evt a -> Evt (Sco a) Source #
Sets the same duration for all events. It's useful with the functions sched
, schedBy
, sched_
.
Api
We can create named instruments. then we can trigger the named instruments with Csound API. Csound can be used not as a text to audio converter but also as a shared C-library. There are many bindings to many languages. For example we can use Python or Android SDK to create UI and under the hood we can use the audio engine created with Haskell. The concept of named instruments is the bridge for other lnguages to use our haskell-generated code.
trigByName :: (Arg a, Sigs b) => Text -> (a -> SE b) -> SE b #
Creates an instrument that can be triggered by name with Csound API.
The arguments are determined from the structure of the input for the instrument.
If we have a tuple of arguments: (D, D, Tab)
The would be rendered to instrument arguments that strts from p4
.
p1
is the name of teh instrument, p2
is the start time of the note,
p3
is the duration of the note. Then p4
and p5
are going to be doubles and p6
is an integer that denotes a functional table.
trigByName_ :: Arg a => Text -> (a -> SE ()) -> SE () #
Creates an instrument that can be triggered by name with Csound API. The arguments are determined from the structure of the input for the instrument.
With Csound API we can send messages
i "name" time duration arg1 arg2 arg3
trigByNameMidi :: (Arg a, Sigs b) => Text -> ((D, D, a) -> SE b) -> SE b #
Creates an instrument that can be triggered by name with Csound API.
It's intended to be used like a midi instrument. It simulates a simplified midi protocol. We can trigger notes:
i "givenName" delay duration 1 pitchKey volumeKey auxParams -- note on i "givenName" delay duration 0 pitchKey volumeKey auxParams -- note off
The arguments are
trigByNameMidi name instrument
The instrument takes a triplet of (pitchKey, volumeKey, auxilliaryTuple)
.
The order does matter. Please don't pass the volumeKey
as the first argument.
The instrument expects the pitch key to be a first argument.
trigByNameMidi_ :: Arg a => Text -> ((D, D, a) -> SE ()) -> SE () #
It behaves just like the function trigByNameMidi
. Only it doesn't produce an audio
signal. It performs some procedure on note on and stops doing the precedure on note off.
turnoffByName :: String -> Sig -> Sig -> SE () Source #
Turns off named instruments.
turnoffNamedInstr name kmode krelease
name of the instrument (should be defined with trigByName
or smth like that).
kmode -- sum of the following values:
0, 1, or 2: turn off all instances (0), oldest only (1), or newest only (2)
4: only turn off notes with exactly matching (fractional) instrument number, rather than ignoring fractional part
8: only turn off notes with indefinite duration (p3 < 0 or MIDI)
krelease -- if non-zero, the turned off instances are allowed to release, otherwise are deactivated immediately (possibly resulting in clicks)
Misc
playWhen :: forall a b. Sigs a => BoolSig -> (b -> SE a) -> b -> SE a Source #
Transforms an instrument from always on to conditional one. The routput instrument plays only when condition is true otherwise it produces silence.
Overload
Converters to make it easier a construction of the instruments.
class AmpInstr a where Source #
Constructs a drum-like instrument. Drum like instrument has a single argument that signifies an amplitude.
type AmpInstrOut a :: Type Source #
Instances
AmpInstr Sig Source # | |
Defined in Csound.Control.Overload.SpecInstr type AmpInstrOut Sig Source # | |
AmpInstr (SE Sig) Source # | |
AmpInstr (SE (Sig, Sig)) Source # | |
AmpInstr (Sig, Sig) Source # | |
AmpInstr (D -> SE Sig) Source # | |
AmpInstr (D -> SE (Sig, Sig)) Source # | |
AmpInstr (D -> Sig) Source # | |
AmpInstr (D -> (Sig, Sig)) Source # | |
AmpInstr (Sig -> SE Sig) Source # | |
AmpInstr (Sig -> SE (Sig, Sig)) Source # | |
AmpInstr (Sig -> Sig) Source # | |
AmpInstr (Sig -> (Sig, Sig)) Source # | |
class CpsInstr a where 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 :: Type Source #
Instances
CpsInstr (D -> SE Sig) Source # | |
CpsInstr (D -> SE (Sig, Sig)) Source # | |
CpsInstr (D -> Sig) Source # | |
CpsInstr (D -> (Sig, Sig)) Source # | |
CpsInstr (Sig -> SE Sig) Source # | |
CpsInstr (Sig -> SE (Sig, Sig)) Source # | |
CpsInstr (Sig -> Sig) Source # | |
CpsInstr (Sig -> (Sig, Sig)) Source # | |
CpsInstr ((D, D) -> SE Sig) Source # | |
CpsInstr ((D, D) -> SE (Sig, Sig)) Source # | |
CpsInstr ((D, D) -> Sig) Source # | |
CpsInstr ((D, D) -> (Sig, Sig)) Source # | |
CpsInstr ((D, Sig) -> SE Sig) Source # | |
CpsInstr ((D, Sig) -> SE (Sig, Sig)) Source # | |
CpsInstr ((D, Sig) -> Sig) Source # | |
CpsInstr ((D, Sig) -> (Sig, Sig)) Source # | |
CpsInstr ((Sig, D) -> SE Sig) Source # | |
CpsInstr ((Sig, D) -> SE (Sig, Sig)) Source # | |
CpsInstr ((Sig, D) -> Sig) Source # | |
CpsInstr ((Sig, D) -> (Sig, Sig)) Source # | |
CpsInstr ((Sig, Sig) -> SE Sig) Source # | |
CpsInstr ((Sig, Sig) -> SE (Sig, Sig)) Source # | |
CpsInstr ((Sig, Sig) -> Sig) Source # | |
CpsInstr ((Sig, Sig) -> (Sig, Sig)) Source # | |
Imperative instruments
newInstr :: Arg a => (a -> SE ()) -> SE (InstrRef a) #
Creates a new instrument and generates a unique identifier.
scheduleEvent :: Arg a => InstrRef a -> D -> D -> a -> SE () #
Schedules an event for the instrument.
scheduleEvent instrRef delay duration args
The arguments for time values are set in seconds.
turnoff2 :: InstrRef a -> Sig -> Sig -> SE () #
Turns off the note played on the given instrument. Use fractional instrument reference to turn off specific instance.
turnoff2 instrRef mode releaseTime
The mode is sum of the following values:
- 0, 1, or 2: turn off all instances (0), oldest only (1), or newest only (2)
- 4: only turn off notes with exactly matching (fractional) instrument number, rather than ignoring fractional part
- 8: only turn off notes with indefinite duration (idur < 0 or MIDI)
releaseTime
if non-zero, the turned off instances are allowed to release, otherwise are deactivated immediately (possibly resulting in clicks).
negateInstrRef :: InstrRef a -> InstrRef a #
Negates the instrument identifier. This trick is used in Csound to update the instrument arguments while instrument is working.
addFracInstrRef :: D -> D -> InstrRef a -> InstrRef a #
Adds fractional part to the instrument reference. This trick is used in Csound to identify the notes (or specific instrument invokation).
newOutInstr :: (Arg a, Sigs b) => (a -> SE b) -> SE (InstrRef a, b) #
Creates an insturment that produces a value.