temporal-csound-0.4.1: library to make electronic music, brings together temporal-music-notation and csound-expression packages

Safe HaskellNone
LanguageHaskell98

Csound

Contents

Description

Defines instance of CsdSco for Score and reexports all functions from packages csound-expression and temporal-music-notation-western.

We can trigger Csound orchestra with Score.

How to put the values in the container Score? There are many functions to construct the Score.

They live in the module Temporal.Music.Score. If you are not familiar with it, you can start with six basic functions.

  • rest -- makes a pause that lasts for some time (in seconds).
  • temp -- makes a score of one note that lasts for one second.
  • mel -- plays a list of notes in sequence (one after the other, short for melody).
  • har -- plays a list of notes in parallel (at the same time, short for harmony).
  • del -- delays all notes for some time (short for delay).
  • str -- change the tempo for all notes by the given ratio (short for stretch).

Let's play something:

res = str 0.5 $ mel [ temp a, str 2 $ temp b, rest 1, har [temp a, temp b] ]

There are two handy infix operators for delay and stretch: (+|) and (*|). So we can write the previous score:

res = 0.5 *| mel [ temp a, 2 *| temp b, 1 +| har [temp a, temp b] ]

There are shortcuts for notes in western notation (a is 440 Hz).

a, b, c, d, e, f, g

Notes reside in the same octave. To get the notes in higher or lower octaves we can apply the functions:

  • high, low -- take note an octaver higher or lower
  • higher n, lower n -- take note for n octaves higher or lower

There are shortcuts for stretching the notes and rests:

bn, wn, qn, en, sn -- brevis, whole, quarter, eight, sixteenth notes

and for rests

bnr, wnr, qnr, enr, snr

These functions transform the melodies with given factors. We can construct melodies:

melody = mel [qn $ mel [c, e, g], bn $ har [c, e, g, high c], wnr]

Then we can apply a csound instrument to the melody to get the signal.

res = notes someInstr melody

Now let's mix it to the signal and send the output to speakers:

dac $ mix res 

WARNING: The function dac spawns a csound process in the background which can run forever. If your haskell build tool doesn't kills the child processes with haskell-runing process (As far as I know Sublime Editor doesn't, but vim does) it's better to run the program from ghci and to stop it press Ctrl+C:

% ghci MyMusic
MyMusic> main 

   ... The programm runs ... press Ctrl+C to stop it

runhaskell doesn't stop the child process. So it's better to use the dac function with terminal.

If signal is to loud or to quiet we can scale it:

dac $ mul factor $ mix res 

We can make it brighter with reverb (smallRoom, smallHall, largeHall, reverTime)

dac $ mul 0.2 $ smallHall $ mix res 

Synopsis

Converters

type CsdNote a = (D, D, a) Source

Contains amplitude, frequency and auxiliary parameters.

(amplitude, frequencyInHz, timbralParameters)

csdNote :: Default a => Note a -> CsdNote a Source

Converts the Note to low level CsdNote.

type CsdDrum a = (D, a) Source

Contains amplitude and auxiliary parameters.

(amplitude, timbralParameters)

csdDrum :: Default a => Drum a -> CsdDrum a Source

Converts the Note to low level CsdNote.

Scores

Funxtions that apply instruments to scores.

Notes on signatures:

  • The class Outs includes the tuples of signals that have side effects or have no side effects.
  • SigOuts -- means an underlying tuple of signals. For instance, it can be Sig or SE Sig, the SigOuts converts it to the Sig. The SigOuts removes the prefix SE if it is present.
  • To get the final signal out of the type Score (Mix (SigOuts b)) we should apply the function mix to it:
mix :: (CsdSco f, Sigs a) => f (Mix a) -> a

Or we can continue to build the track of signals with functions loke mel, har, str.

notes :: (Arg a, Default a, Outs b) => (CsdNote a -> b) -> Score (Note a) -> Score (Mix (SigOuts b)) Source

Plays the notes with csound instrument.

drums :: (Arg a, Default a, Outs b) => (CsdDrum a -> b) -> Score (Drum a) -> Score (Mix (SigOuts b)) Source

Plays the drum notes with csound instrument.

Midis

Plays instruments with midi devices.

import Csound 
import Csound.Patch(vibraphone2)

-- | Plays with virtual midi device (if you have a midi device
-- you can substitute @vdac@ for @dac@).
main = vdac $ mul 0.1 $ largeHall $ onMidi vibraphone2

onMidi :: (Default a, Outs b) => (CsdNote a -> b) -> SigOuts b Source

Triggers an instrument on all midi-channels.

onMidin :: (Default a, Outs b) => Channel -> (CsdNote a -> b) -> SigOuts b Source

Triggers an instrument on the given midi-channel.

onPgmidi :: (Default a, Outs b) => Maybe Int -> Channel -> (CsdNote a -> b) -> SigOuts b Source

Triggers an instrument on channel and programm bank.

onMidiWith :: Outs b => a -> (CsdNote a -> b) -> SigOuts b Source

Just like onMidi but takes a value for default auxiliary parameters.

onMidinWith :: Outs b => a -> Channel -> (CsdNote a -> b) -> SigOuts b Source

Just like onMidin but takes a value for default auxiliary parameters.

onPgmidiWith :: Outs b => a -> Maybe Int -> Channel -> (CsdNote a -> b) -> SigOuts b Source

Just like onPgmidi but takes a value for default auxiliary parameters.