Safe Haskell | None |
---|
- newtype SE a = SE {
- unSE :: Dep a
- data LocalHistory = LocalHistory {
- expDependency :: Maybe E
- newLocalVarId :: Int
- runSE :: SE a -> GE (a, LocalHistory)
- execSE :: SE () -> GE InstrBody
- evalSE :: SE a -> GE a
- execGEinSE :: SE (GE a) -> SE a
- hideGEinDep :: GE (Dep a) -> Dep a
- fromDep :: Dep a -> SE (GE a)
- fromDep_ :: Dep () -> SE ()
- geToSe :: GE a -> SE a
- newLocalVar :: Rate -> GE E -> SE Var
- newLocalVars :: [Rate] -> GE [E] -> SE [Var]
- data SERef a = SERef {
- writeSERef :: a -> SE ()
- readSERef :: SE a
- newSERef :: Tuple a => a -> SE (SERef a)
- sensorsSE :: Tuple a => a -> SE (SE a, a -> SE ())
- instr0 :: Tuple a => SE a -> SE a
- getIns :: Sigs a => SE a
- setDur :: Sigs a => D -> a -> a
- data Mix a
- sco :: (CsdSco f, Arg a, Sigs b) => (a -> SE b) -> f a -> f (Mix b)
- eff :: (CsdSco f, Sigs a, Sigs b) => (a -> SE b) -> f (Mix a) -> f (Mix b)
- mix :: (Sigs a, CsdSco f) => f (Mix a) -> a
- mixBy :: (Arg a, Sigs b, CsdSco f) => (a -> f (Mix b)) -> a -> b
- sco_ :: (CsdSco f, Arg a) => (a -> SE ()) -> f a -> f (Mix Unit)
- mix_ :: CsdSco f => f (Mix Unit) -> SE ()
- mixBy_ :: (Arg a, CsdSco f) => (a -> f (Mix Unit)) -> a -> SE ()
- class Functor f => CsdSco f where
- toCsdEventList :: f a -> CsdEventList a
- singleCsdEvent :: CsdEvent a -> f a
- data CsdEventList a = CsdEventList {
- csdEventListDur :: Double
- csdEventListNotes :: [CsdEvent a]
- type CsdEvent a = (Double, Double, a)
- data Msg
- type Channel = Int
- midi :: Sigs a => (Msg -> SE a) -> a
- midin :: Sigs a => Channel -> (Msg -> SE a) -> a
- pgmidi :: Sigs a => Maybe Int -> Channel -> (Msg -> SE a) -> a
- midi_ :: (Msg -> SE ()) -> SE ()
- midin_ :: Channel -> (Msg -> SE ()) -> SE ()
- pgmidi_ :: Maybe Int -> Channel -> (Msg -> SE ()) -> SE ()
- trigs :: (Arg a, Sigs b) => (a -> SE b) -> Evt [(D, D, a)] -> b
- scheds :: (Arg a, Sigs b) => (a -> SE b) -> Evt [(D, a)] -> b
- schedHarps :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b
- trigsBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt [(D, D, a)]) -> c -> b
- schedsBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt [(D, a)]) -> c -> b
- schedHarpsBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b
- trigs_ :: Arg a => (a -> SE ()) -> Evt [(D, D, a)] -> SE ()
- scheds_ :: Arg a => (a -> SE ()) -> Evt [(D, a)] -> SE ()
- saw :: Sig -> Sig
- isaw :: Sig -> Sig
- pulse :: Sig -> Sig
- tri :: Sig -> Sig
- sqr :: Sig -> Sig
- blosc :: Tab -> Sig -> Sig
SE
The Csound's IO
-monad. All values that produce side effects are wrapped
in the SE
-monad.
Monad SE | |
Functor SE | |
Applicative SE | |
Procedure (SE ()) | |
DirtySingle (SE (GE E)) | |
DirtySingle (SE Tab) | |
DirtySingle (SE Wspec) | |
DirtySingle (SE Spec) | |
DirtySingle (SE Str) | |
DirtySingle (SE D) | |
DirtySingle (SE Sig) |
runSE :: SE a -> GE (a, LocalHistory)Source
execGEinSE :: SE (GE a) -> SE aSource
hideGEinDep :: GE (Dep a) -> Dep aSource
SE reference
It describes a reference to mutable values.
SERef | |
|
newSERef :: Tuple a => a -> SE (SERef a)Source
Allocates a new mutable value and initializes it with value. A reference can contain a tuple of variables.
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.
Global settings
setDur :: Sigs a => D -> a -> aSource
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
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 withsco
oreff
.
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) -> aSource
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 -> bSource
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)]
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.
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).
Functor CsdEventList | |
Foldable CsdEventList | |
Traversable CsdEventList | |
CsdSco CsdEventList | |
Eq a => Eq (CsdEventList a) | |
Show a => Show (CsdEventList a) |
type CsdEvent a = (Double, Double, a)
The Csound note. It's a triple of
(startTime, duration, parameters)
Midi
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 :: Sigs a => (Msg -> SE a) -> aSource
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) -> aSource
Triggers a midi-instrument (aka Csound's massign) on the specified channel.
pgmidi :: Sigs a => Maybe Int -> Channel -> (Msg -> SE a) -> aSource
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.
Events
trigs :: (Arg a, Sigs b) => (a -> SE b) -> Evt [(D, D, a)] -> bSource
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)] -> bSource
It's like the function trigs
, but delay is set to zero.
schedHarps :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> bSource
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 -> bSource
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 -> bSource
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 -> bSource
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.