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

Safe HaskellNone
LanguageHaskell2010

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

Instances

Monad SE Source # 

Methods

(>>=) :: SE a -> (a -> SE b) -> SE b #

(>>) :: SE a -> SE b -> SE b #

return :: a -> SE a #

fail :: String -> SE a #

Functor SE Source # 

Methods

fmap :: (a -> b) -> SE a -> SE b #

(<$) :: a -> SE b -> SE a #

Applicative SE Source # 

Methods

pure :: a -> SE a #

(<*>) :: SE (a -> b) -> SE a -> SE b #

(*>) :: SE a -> SE b -> SE b #

(<*) :: SE a -> SE b -> SE a #

Procedure (SE ()) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> SE ()

DirtySingle (SE (GE E)) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE (GE E)

DirtySingle (SE Tab) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Tab

DirtySingle (SE Wspec) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Wspec

DirtySingle (SE Spec) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Spec

DirtySingle (SE Str) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Str

DirtySingle (SE D) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE D

DirtySingle (SE Sig) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Sig

data LocalHistory :: * #

Constructors

LocalHistory 

Instances

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

data Ref a Source #

It describes a reference to mutable values.

writeRef :: Tuple a => Ref a -> a -> SE () Source #

readRef :: Tuple a => Ref a -> SE a Source #

newRef :: Tuple a => a -> SE (Ref 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.

mixRef :: (Num a, Tuple a) => Ref a -> a -> SE () Source #

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

modifyRef :: Tuple a => Ref a -> (a -> a) -> SE () Source #

Modifies the Ref value with given function.

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

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

newGlobalRef :: Tuple a => a -> SE (Ref a) Source #

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

newCtrlRef :: Tuple a => a -> SE (Ref 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. It contains control signals (k-rate) and constants for numbers (i-rates).

newGlobalCtrlRef :: Tuple a => a -> SE (Ref a) Source #

Allocates a new global mutable value and initializes it with value. A reference can contain a tuple of variables. It contains control signals (k-rate) and constants for numbers (i-rates).

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

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

newClearableGlobalRef :: Tuple a => a -> SE (Ref a) Source #

Allocates a new clearable global mutable value and initializes it with value. A reference can contain a tuple of variables. The variable is set to zero at the end of every iteration. It's useful for accumulation of audio values from several instruments.

newTab :: D -> SE Tab Source #

Creates a new table. The Tab could be used while the instrument is playing. When the instrument is retriggered the new tab is allocated.

newTab size

newGlobalTab :: Int -> SE Tab Source #

Creates a new global table. It's generated only once. It's persisted between instrument calls.

newGlobalTab identifier size

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.

Misc

freshId :: SE D Source #

Gets new id.

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 :: (Arg a, Sigs b) => (a -> SE b) -> Sco a -> Sco (Mix b) Source #

Plays a bunch of notes with the given instrument.

res = sco instrument scores 

eff :: (Sigs a, Sigs b) => (a -> SE b) -> Sco (Mix a) -> Sco (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 => Sco (Mix a) -> a Source #

Renders a scores to the sound signals. we can use it inside the other instruments.

mixBy :: (Arg a, Sigs b) => (a -> Sco (Mix b)) -> a -> b Source #

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

sco_ :: Arg a => (a -> SE ()) -> Sco a -> Sco (Mix Unit) Source #

Invokes a procedure for the given bunch of events.

mix_ :: Sco (Mix Unit) -> SE () Source #

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

mixBy_ :: Arg a => (a -> Sco (Mix Unit)) -> a -> SE () Source #

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

type Sco a = Track D a Source #

type CsdEvent = (Double, Double, Note) #

The Csound note. It's a triple of

(startTime, duration, parameters)

Midi

data Msg Source #

Instances

DirtyMulti b => DirtyMulti (Msg -> b) Source # 

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Msg -> b

PureMulti b => PureMulti (Msg -> b) Source # 

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Msg -> b

Procedure b => Procedure (Msg -> b) Source # 

Methods

procedureGE :: GE ([E] -> Dep ()) -> Msg -> b

DirtySingle b => DirtySingle (Msg -> b) Source # 

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Msg -> b

PureSingle b => PureSingle (Msg -> b) Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> 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 #

Named instruments (API)

trigByName :: (Arg a, Sigs b) => String -> (a -> SE b) -> SE b Source #

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 => String -> (a -> SE ()) -> SE () Source #

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) => String -> ((D, D, a) -> SE b) -> SE b Source #

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_ :: forall a. Arg a => String -> ((D, D, a) -> SE ()) -> SE () Source #

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.

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

SfId (GE E) 

Instances

IfB Sf Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Sf) => bool -> Sf -> Sf -> Sf #

Default Sf Source # 

Methods

def :: Sf #

Val Sf Source # 

Methods

fromGE :: GE E -> Sf Source #

toGE :: Sf -> GE E Source #

fromE :: E -> Sf Source #

type BooleanOf Sf Source # 

unSf :: Sf -> GE E Source #

Events

sched :: (Arg a, Sigs b) => (a -> SE b) -> Evt (Sco a) -> b Source #

sched_ :: Arg a => (a -> SE ()) -> Evt (Sco a) -> SE () Source #

Triggers a procedure on the event stream.

schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (Sco a)) -> c -> b Source #

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

schedHarp :: (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.

schedHarpBy :: (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.

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

Retriggers an instrument every time an event happens. The note is held until the next event happens.

evtLoop :: (Num a, Tuple a, Sigs a) => Maybe (Evt Unit) -> [SE a] -> [Evt Unit] -> a Source #

evtLoopOnce :: (Num a, Tuple a, Sigs a) => Maybe (Evt Unit) -> [SE a] -> [Evt Unit] -> a Source #

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

saw' :: D -> Sig -> Sig Source #

A sawtooth.

isaw' :: D -> Sig -> Sig Source #

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

pulse' :: D -> Sig -> Sig Source #

Pulse (not normalized).

tri' :: D -> Sig -> Sig Source #

A triangle wave.

sqr' :: D -> Sig -> Sig Source #

A square wave.

blosc' :: Tab -> D -> Sig -> Sig Source #

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