csound-expression-1.0.2: library to make electronic music

Safe HaskellNone

Csound.Base

Contents

Description

Basic types and functions.

Example (a concert A)

 module Main where
 
 import Csound.Base
 
 osc :: Sig -> Sig
 osc phs = oscil1 1 phs (genHigh 10 [1])
 
 instr :: D -> Out
 instr pch = out $ 0.5 * (osc $ kr pch)
 
 res = score instr [(0, 1, 440)]
 
 main :: IO ()
 main = writeFile "tmp.csd" $ renderCsd [res]

Now you can invoke Csound on tmp.csd and listen to the result with your favourite player.

 csound tmp.csd -o a.wav

Synopsis

Types

class Val a Source

Instances

Constants

A constant value doesn't change while instrument is playing a note. Only constants can be passed as arguments to the instruments.

data D Source

Doubles.

data I Source

Integers.

Instances

data Tab Source

Csound f-tables. You can make a value of Tab with the function gen.

Instances

data Str Source

Strings.

withInits :: (Val a, CsdTuple inits) => a -> inits -> SigSource

Appends initialisation arguments. It's up to you to supply arguments with the right types. For example:

 oscil 0.5 440 sinWave `withInits` (0.5 :: D)

Signals

Signals can be audio or control rate. Rate is derived from the code. If there are rate-collisions, values will be converted to the right rates. For example, if you are trying to apply an opcode that expects control rate signal to some audio rate signal, the signal will be downsampled behind the scenes.

data Sig Source

Audio or control rate signals.

data BoolSig Source

Boolean signals. Use functions from the module Data.Boolean to make boolean signals out of simple signals.

data Spec Source

Spectrum of the signal (see FFT and Spectral Processing in the Csound.Opcode.Advanced).

Instances

Side effects

data SE a Source

Csound's synonym for IO-monad. SE means Side Effect. You will bump into SE trying to read and write to delay lines, making random signals or trying to save your audio to file. Instrument is expected to return a value of SE [Sig]. So it's okay to do some side effects when playing a note.

Tuples

class CsdTuple a Source

Describes tuples of Csound values. It's used for functions that can return several results (such as soundin or diskin2). Tuples can be nested.

Instances

CsdTuple Spec 
CsdTuple Str 
CsdTuple D 
CsdTuple I 
CsdTuple Sig 
(CsdTuple a, CsdTuple b) => CsdTuple (a, b) 
(CsdTuple a, CsdTuple b, CsdTuple c) => CsdTuple (a, b, c) 
(CsdTuple a, CsdTuple b, CsdTuple c, CsdTuple d) => CsdTuple (a, b, c, d) 
(CsdTuple a, CsdTuple b, CsdTuple c, CsdTuple d, CsdTuple e) => CsdTuple (a, b, c, d, e) 
(CsdTuple a, CsdTuple b, CsdTuple c, CsdTuple d, CsdTuple e, CsdTuple f) => CsdTuple (a, b, c, d, e, f) 
(CsdTuple a, CsdTuple b, CsdTuple c, CsdTuple d, CsdTuple e, CsdTuple f, CsdTuple g) => CsdTuple (a, b, c, d, e, f, g) 
(CsdTuple a, CsdTuple b, CsdTuple c, CsdTuple d, CsdTuple e, CsdTuple f, CsdTuple g, CsdTuple h) => CsdTuple (a, b, c, d, e, f, g, h) 

Converters

class ToSig a whereSource

Values that can be converted to signals.

Methods

arSource

Arguments

:: a 
-> Sig

Forces signal to audio rate.

krSource

Arguments

:: a 
-> Sig

Forces signal to control rate.

ir :: Sig -> DSource

Converts signal to double.

int :: Int -> ISource

Converts Haskell's integers to Csound's integers

double :: Double -> DSource

Converts Haskell's doubles to Csound's doubles

str :: String -> StrSource

Converts Haskell's strings to Csound's strings

Making a sound

Let's make some noise. Sound is build from list of tracks (SigOut).

type Out = SE [Sig]Source

Output of the instrument.

data SigOut Source

The abstract type of musical tracks.

effect :: ([Sig] -> Out) -> SigOut -> SigOutSource

Applies a global effect function to the signal. With this function we can add reverb or panning to the mixed signal. The argument function takes a list of signals. Each cell of the list contains a signal on the given channel.

out :: Sig -> OutSource

Synonym for return . return.

outs :: [Sig] -> OutSource

Synonym for return.

Scores

We can define an instrument and tell it to play some notes.

score :: Arg a => (a -> Out) -> [(Double, Double, a)] -> SigOutSource

class Arg a whereSource

Describes all Csound values that can be used in the score section. Instruments are triggered with the values from this type class. Actual methods are hidden, but you can easily make instances for your own types with function makeArgMethods. You need to describe the new instance in terms of some existing one. For example:

 data Note = Note 
     { noteAmplitude    :: D
     , notePitch        :: D
     , noteVibrato      :: D
     , noteSample       :: S
     }
 
 instance Arg Note where
     argMethods = makeArgMethods to from
         where to (amp, pch, vibr, sample) = Note amp pch vibr sample
               from (Note amp pch vibr sample) = (amp, pch, vibr, sample)

Then you can use this type in an instrument definition.

 instr :: Note -> Out
 instr x = ...

Instances

Arg () 
Arg Tab 
Arg Str 
Arg D 
Arg I 
(Arg a, Arg b) => Arg (a, b) 
(Arg a, Arg b, Arg c) => Arg (a, b, c) 
(Arg a, Arg b, Arg c, Arg d) => Arg (a, b, c, d) 
(Arg a, Arg b, Arg c, Arg d, Arg e) => Arg (a, b, c, d, e) 
(Arg a, Arg b, Arg c, Arg d, Arg e, Arg f) => Arg (a, b, c, d, e, f) 
(Arg a, Arg b, Arg c, Arg d, Arg e, Arg f, Arg g) => Arg (a, b, c, d, e, f, g) 
(Arg a, Arg b, Arg c, Arg d, Arg e, Arg f, Arg g, Arg h) => Arg (a, b, c, d, e, f, g, h) 

data ArgMethods a Source

The abstract type of methods for the class Arg.

makeArgMethods :: Arg a => (a -> b) -> (b -> a) -> ArgMethods bSource

Defines instance of type class Arg for a new type in terms of an old one.

Midi

We can define a midi-instrument. Then we can trigger the instrument with a midi-keyboard.

data Msg Source

Midi messages.

Rendering

Now we are ready to create a csound-file. The function renderCsd creates a String that contains the description of our music. We can save it to a file and compile it with our csound wizard.

renderCsd :: [SigOut] -> StringSource

Renders Csound file.

Opcodes

Some colors to paint our soundscapes.

Options

We can set some csound options.

renderCsdBy :: CsdOptions -> [SigOut] -> StringSource

Renders Csound file with options.

data CsdOptions Source

Csound options. The default value is

 instance Default CsdOptions where
     def = CsdOptions 
             { csdFlags = ""
             , csdRate  = 44100
             , csdBlockSize = 64
             , csdSeed = Nothing
             , csdInitc7 = []
             , csdEffect = mixing
             , csdKrate  = ["linseg", "expseg", "linsegr", "expsegr"] }

Constructors

CsdOptions 

Instances

mixing :: [[Sig]] -> OutSource

Sums signals for every channel.

mixingBy :: ([Sig] -> Out) -> [[Sig]] -> OutSource

Sums signals for every channel and the processes the output with the given function.