csound-expression-typed-0.0.6.1: typed core for the library csound-expression

Safe HaskellNone
LanguageHaskell98

Csound.Typed.Control

Contents

Synopsis

SE

newtype SE a Source

The Csound's IO-monad. All values that produce side effects are wrapped in the SE-monad.

Constructors

SE 

Fields

unSE :: Dep a
 

data LocalHistory :: *

Constructors

LocalHistory 

runSE :: SE a -> GE a Source

evalSE :: SE a -> GE a Source

execGEinSE :: SE (GE a) -> SE a Source

hideGEinDep :: GE (Dep a) -> Dep a Source

fromDep :: Dep a -> SE (GE a) Source

fromDep_ :: Dep () -> SE () Source

geToSe :: GE a -> SE a Source

newLocalVars :: [Rate] -> GE [E] -> SE [Var] Source

newGlobalVars :: [Rate] -> GE [E] -> SE [Var] Source

SE reference

newtype SERef a Source

It describes a reference to mutable values.

Constructors

SERef [Var] 

writeSERef :: Tuple a => SERef a -> a -> SE () Source

readSERef :: Tuple a => SERef a -> SE a Source

newSERef :: Tuple a => a -> SE (SERef a) Source

Allocates a new local (it is visible within the instrument) mutable value and initializes it with value. A reference can contain a tuple of variables.

mixSERef :: (Num a, Tuple a) => SERef a -> a -> SE () Source

Adds the given signal to the value that is contained in the reference.

modifySERef :: Tuple a => SERef a -> (a -> a) -> SE () Source

Modifies the SERef value with given function.

sensorsSE :: Tuple a => a -> SE (SE a, a -> SE ()) Source

An alias for the function newSERef. It returns not the reference to mutable value but a pair of reader and writer functions.

newGlobalSERef :: Tuple a => a -> SE (SERef a) Source

Allocates a new global mutable value and initializes it with value. A reference can contain a tuple of variables.

globalSensorsSE :: Tuple a => a -> SE (SE a, a -> SE ()) Source

An alias for the function newSERef. It returns not the reference to mutable value but a pair of reader and writer functions.

Global settings

instr0 :: Tuple a => SE a -> SE a Source

getIns :: Sigs a => SE a Source

setDur :: Sigs a => D -> a -> a Source

Sets the global duration of the file or output signal to the given value. It should be used only once! The proper place is in the top-most expression before sending to dac or writeWav.

Score

data Mix a Source

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

Plays a bunch of notes with the given instrument.

res = sco instrument scores 

eff :: (CsdSco f, Sigs a, Sigs b) => (a -> SE b) -> f (Mix a) -> f (Mix b) Source

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!

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

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

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

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

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

Invokes a procedure for the given bunch of events.

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

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

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

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

class Functor f => 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 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)

Midi

data Msg Source

Instances

DirtyMulti b => DirtyMulti (Msg -> b) 
PureMulti b => PureMulti (Msg -> b) 
Procedure b => Procedure (Msg -> b) 
DirtySingle b => DirtySingle (Msg -> b) 
PureSingle b => PureSingle (Msg -> b) 

midi :: (Num a, Sigs a) => (Msg -> SE a) -> SE a Source

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

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

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

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

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

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

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

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

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

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

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

initMidiCtrl :: D -> D -> D -> SE () Source

OSC

type OscHost = String Source

The hostname of the computer. An empty string is for local machine.

type OscPort = Int Source

Port to listen OSC-messages.

type OscAddress = String Source

Path-like string ("foobar/baz")

type OscType = String Source

The string specifies the type of expected arguments. The string can contain the characters "bcdfilmst" which stand for Boolean, character, double, float, 32-bit integer, 64-bit integer, MIDI, string and timestamp.

initOsc :: OscPort -> SE OscRef Source

Initializes host client. The process starts to run in the background.

listenOsc :: forall a. Tuple a => OscRef -> OscAddress -> OscType -> Evt a Source

Listens for the OSC-messages. The first argument is OSC-reference. We can create it with the function oscInit. The next two arguments are strings. The former specifies the path-like address to listen the messages. It can be:

/foo/bar/baz

The latter specifies the type of expected arguments. The string can contain the characters "bcdfilmst" which stand for Boolean, character, double, float, 32-bit integer, 64-bit integer, MIDI, string and timestamp.

The result is an event of messages. We can run a callback on it with standard function runEvt:

runEvt :: Evt a -> (a -> SE ()) -> SE ()

sendOsc :: forall a. Tuple a => OscHost -> OscPort -> OscAddress -> OscType -> Evt a -> SE () Source

Sends OSC-messages. It takes in a name of the host computer (empty string is alocal machine), port on which the target machine is listening, OSC-addres and type. The last argument produces the values for OSC-messages.

Channel

Getters

chnGetD :: Str -> SE D Source

Reads a value of type double.

chnGetSig :: Str -> SE Sig Source

Reads an audio signal.

chnGetCtrl :: Str -> SE Sig Source

Reads a control signal. The control signals are updated at the lower rate.

chnGetStr :: Str -> SE Str Source

Reads a string.

Setters

chnSetD :: D -> Str -> SE () Source

Writes a value of type double.

chnSetSig :: Sig -> Str -> SE () Source

Writes an audio signal.

chnSetCtrl :: Sig -> Str -> SE () Source

Writes a control signal. The control signals are updated at the lower rate.

chnSetStr :: Str -> Str -> SE () Source

Writes a string.

Sf2

data Sf Source

The sf2 sound font preset. It is defined with file name, bank and program integers.

Constructors

Sf 

Fields

sfName :: String
 
sfBank :: Int
 
sfProg :: Int
 
SfId (GE E) 

Instances

unSf :: Sf -> GE E Source

Events

trigs :: (Arg a, Sigs b) => (a -> SE b) -> Evt [(D, D, a)] -> b Source

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)

scheds :: (Arg a, Sigs b) => (a -> SE b) -> Evt [(D, a)] -> b Source

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

schedHarps :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b Source

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.

trigsBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt [(D, D, a)]) -> c -> b Source

A closure to trigger an instrument inside the body of another instrument.

schedsBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt [(D, a)]) -> c -> b Source

A closure to trigger an instrument inside the body of another instrument.

schedHarpsBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b Source

A closure to trigger an instrument inside the body of another instrument.

trigs_ :: Arg a => (a -> SE ()) -> Evt [(D, D, a)] -> SE () Source

Triggers a procedure on the event stream.

scheds_ :: Arg a => (a -> SE ()) -> Evt [(D, a)] -> SE () Source

Triggers a procedure on the event stream. A delay time is set to zero.

Band-limited oscillators

saw :: Sig -> Sig Source

A sawtooth.

isaw :: Sig -> Sig Source

Integrated sawtooth: 4 * x * (1 - x).

pulse :: Sig -> Sig Source

Pulse (not normalized).

tri :: Sig -> Sig Source

A triangle wave.

sqr :: Sig -> Sig Source

A square wave.

blosc :: Tab -> Sig -> Sig Source

A band-limited oscillator with user defined waveform (it's stored in the table).