csound-expression-3.1.0: library to make electronic music

Safe HaskellNone

Csound.Control.Instr

Contents

Description

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 (Midi-section).

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

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 CsdSco f where

A class that represents Csound scores. All functions that use score are defined in terms of this class. If you want to use your own score representation, just define two methods of the class.

The properties:

 forall a . toCsdEventList (singleCsdEvent a) === CsdEventList 1 [(0, 1, a)]

Methods

toCsdEventList :: f a -> CsdEventList a

Converts a given score representation to the canonical one.

singleCsdEvent :: CsdEvent a -> f a

Constructs a scores that contains only one event. The event happens immediately and lasts for 1 second.

Instances

data Mix a

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 :: (CsdSco f, Arg a, Sigs b) => (a -> SE b) -> f a -> f (Mix b)

Plays a bunch of notes with the given instrument.

 res = sco instrument scores 

mix :: (Sigs a, CsdSco f) => f (Mix a) -> a

Renders a scores to the sound signals. we can use it inside the other instruments. Warning: if we use a score that lasts for an hour in the note that lasts for 5 seconds all the events would be generated, though we will hear only first five seconds. So the semantics is good but implementation is inefficient for such a cases (consider event streams for such cases).

eff :: (CsdSco f, Sigs a, Sigs b) => (a -> SE b) -> f (Mix a) -> f (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 with sco or eff.

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!

data CsdEventList a

CsdEventList is a canonical representation of the Csound scores. A scores is a list of events and we should know the total duration of the scores. It's not meant to be used directly. We can use a better alternative. More convenient type that belongs to CsdSco type class (see temporal-csound package).

type CsdEvent a = (Double, Double, a)

The Csound note. It's a triple of

 (startTime, duration, parameters)

mixLoop :: (CsdSco f, Sigs a) => f (Mix a) -> aSource

Mixes the scores and plays them in the loop.

sco_ :: (CsdSco f, Arg a) => (a -> SE ()) -> f a -> f (Mix Unit)

Invokes a procedure for the given bunch of events.

mix_ :: CsdSco f => f (Mix Unit) -> SE ()

Converts a bunch of procedures scheduled with scores to a single procedure.

mixLoop_ :: CsdSco f => f (Mix Unit) -> SE ()Source

Mixes the procedures and plays them in the loop.

mixBy :: (Arg a, Sigs b, CsdSco f) => (a -> f (Mix b)) -> a -> b

Imitates a closure for a bunch of notes to be played within another instrument.

Midi

data Msg

Instances

MidiInstr (Msg -> (Sig, Sig)) 
MidiInstr (Msg -> (Sig, Sig, Sig)) 
MidiInstr (Msg -> (Sig, Sig, Sig, Sig)) 
MidiInstr (Msg -> Sig) 
MidiInstr (Msg -> SE (Sig, Sig)) 
MidiInstr (Msg -> SE (Sig, Sig, Sig)) 
MidiInstr (Msg -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr (Msg -> SE Sig) 

type Channel = Int

midi :: Sigs a => (Msg -> SE a) -> a

Triggers a midi-instrument (aka Csound's massign) for all channels. It's useful to test a single instrument.

midin :: Sigs a => Channel -> (Msg -> SE a) -> a

Triggers a midi-instrument (aka Csound's massign) on the specified channel.

pgmidi :: Sigs a => Maybe Int -> Channel -> (Msg -> SE a) -> a

Triggers a midi-instrument (aka Csound's pgmassign) on the specified programm bank.

ampCps :: Msg -> (D, D)Source

midi_ :: (Msg -> SE ()) -> SE ()

Triggers a midi-procedure (aka Csound's massign) for all channels.

midin_ :: Channel -> (Msg -> SE ()) -> SE ()

Triggers a midi-procedure (aka Csound's pgmassign) on the given channel.

pgmidi_ :: Maybe Int -> Channel -> (Msg -> SE ()) -> SE ()

Triggers a midi-procedure (aka Csound's pgmassign) on the given programm bank.

Reading midi note parameters

cpsmidi :: Msg -> D

Get the note number of the current MIDI event, expressed in cycles-per-second.

 icps  cpsmidi  

csound doc: http://www.csounds.com/manual/html/cpsmidi.html

ampmidi :: Msg -> D -> D

Get the velocity of the current MIDI event.

 iamp  ampmidi  iscal [, ifn]

csound doc: http://www.csounds.com/manual/html/ampmidi.html

Evt

trig :: (Arg a, Sigs b) => (a -> SE b) -> Evt (D, D, a) -> b

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) -> b

It's like the function trig, but delay is set to zero.

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 -> 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 ()

Triggers a procedure on the event stream.

sched_ :: Arg a => (a -> SE ()) -> Evt (D, a) -> SE ()

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 -> b

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 -> 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.

withDur :: D -> Evt a -> Evt (D, a)Source

Sets the same duration for all events. It's useful with the functions sched, schedBy, sched_.

 withDur dur events === fmap (\x -> (dur, x)) events

Overload

Converters to make it easier a construction of the instruments.

class Instr a whereSource

Converts a value to the instrument that is used with the functions sco or eff.

Associated Types

type InstrIn a :: *Source

type InstrOut a :: *Source

Methods

onArg :: a -> InstrIn a -> SE (InstrOut a)Source

Instances

Instr (a -> SE (Sig, Sig, Sig, Sig, Sig)) 
Instr (a -> SE (Sig, Sig, Sig, Sig)) 
Instr (a -> SE (Sig, Sig, Sig)) 
Instr (a -> SE (Sig, Sig)) 
Instr (a -> SE Sig) 
Instr (a -> (Sig, Sig, Sig, Sig, Sig)) 
Instr (a -> (Sig, Sig, Sig, Sig)) 
Instr (a -> (Sig, Sig, Sig)) 
Instr (a -> (Sig, Sig)) 
Instr (a -> Sig) 

class MidiInstr a whereSource

Converts a value to the midi-instrument. It's used with the functions midi, midin.

Associated Types

type MidiInstrOut a :: *Source

Methods

onMsg :: a -> Msg -> SE (MidiInstrOut a)Source

Instances

MidiInstr ((Sig, Sig) -> (Sig, Sig)) 
MidiInstr ((Sig, Sig) -> (Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> Sig) 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig)) 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> SE Sig) 
MidiInstr ((Sig, D) -> (Sig, Sig)) 
MidiInstr ((Sig, D) -> (Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> Sig) 
MidiInstr ((Sig, D) -> SE (Sig, Sig)) 
MidiInstr ((Sig, D) -> SE (Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> SE Sig) 
MidiInstr ((D, Sig) -> (Sig, Sig)) 
MidiInstr ((D, Sig) -> (Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> Sig) 
MidiInstr ((D, Sig) -> SE (Sig, Sig)) 
MidiInstr ((D, Sig) -> SE (Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> SE Sig) 
MidiInstr ((D, D) -> (Sig, Sig)) 
MidiInstr ((D, D) -> (Sig, Sig, Sig)) 
MidiInstr ((D, D) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, D) -> Sig) 
MidiInstr ((D, D) -> SE (Sig, Sig)) 
MidiInstr ((D, D) -> SE (Sig, Sig, Sig)) 
MidiInstr ((D, D) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, D) -> SE Sig) 
MidiInstr (Sig -> (Sig, Sig)) 
MidiInstr (Sig -> (Sig, Sig, Sig)) 
MidiInstr (Sig -> (Sig, Sig, Sig, Sig)) 
MidiInstr (Sig -> Sig) 
MidiInstr (Sig -> SE (Sig, Sig)) 
MidiInstr (Sig -> SE (Sig, Sig, Sig)) 
MidiInstr (Sig -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr (Sig -> SE Sig) 
MidiInstr (D -> (Sig, Sig)) 
MidiInstr (D -> (Sig, Sig, Sig)) 
MidiInstr (D -> (Sig, Sig, Sig, Sig)) 
MidiInstr (D -> Sig) 
MidiInstr (D -> SE (Sig, Sig)) 
MidiInstr (D -> SE (Sig, Sig, Sig)) 
MidiInstr (D -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr (D -> SE Sig) 
MidiInstr (Msg -> (Sig, Sig)) 
MidiInstr (Msg -> (Sig, Sig, Sig)) 
MidiInstr (Msg -> (Sig, Sig, Sig, Sig)) 
MidiInstr (Msg -> Sig) 
MidiInstr (Msg -> SE (Sig, Sig)) 
MidiInstr (Msg -> SE (Sig, Sig, Sig)) 
MidiInstr (Msg -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr (Msg -> SE Sig) 

class AmpInstr a whereSource

Constructs a drum-like instrument. Drum like instrument has a single argument that signifies an amplitude.

Associated Types

type AmpInstrOut a :: *Source

Methods

onAmp :: a -> D -> SE (AmpInstrOut a)Source

Instances

class CpsInstr a whereSource

Constructs a simple instrument that takes in a tuple of two arguments. They are amplitude and the frequency (in Hz or cycles per second).

Associated Types

type CpsInstrOut a :: *Source

Methods

onCps :: a -> (D, D) -> SE (CpsInstrOut a)Source

Instances

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)