haskore-supercollider-0.0.2: Haskore back-end for SuperColliderSource codeContentsIndex
Haskore.Interface.SuperCollider.Schedule.Install
Description
This is a variant of the Haskore.Interface.SuperCollider.Schedule module. Instead of an abstract Instrument type and a Haskore.Interface.SuperCollider.SoundMap, we attach SuperCollider instrument information to each note.
Synopsis
newtype Environment a = Environment {
unwrapEnvironment :: Writer [OSC] a
}
writeOSC :: [OSC] -> Environment ()
data Sound params attr = Sound {
nameFromSound :: String
flattenAttrFromSound :: attr -> AttributeList
}
type Instrument attr = Sound InstrumentParameters attr
type Drum attr = Sound DrumParameters attr
installSound :: SoundParameters params => (parameterTuple -> AttributeList, graph -> Sound params) -> String -> graph -> Environment (Sound params parameterTuple)
installSound0 :: SoundParameters params => String -> Sound params -> Environment (Sound params ())
installSound1 :: SoundParameters params => String -> (UGen -> Sound params) -> Environment (Sound params Double)
installSound2 :: SoundParameters params => String -> (UGen -> UGen -> Sound params) -> Environment (Sound params (Double, Double))
data SoundAttributes params = SoundAttributes AttributeList String
type DrumAttributes = SoundAttributes DrumParameters
type InstrumentAttributes = SoundAttributes InstrumentParameters
rhythmicMusicFromDynamicMelody :: Instrument attr -> T (Rational, attr) -> T DrumAttributes InstrumentAttributes
rhythmicMusicFromMelody :: Instrument attr -> T attr -> T DrumAttributes InstrumentAttributes
rhythmicMusicFromRhythm :: Drum () -> Dur -> String -> T DrumAttributes InstrumentAttributes
rhythmicMusicFromDrum :: Drum () -> Dur -> T DrumAttributes InstrumentAttributes
fromRhythmicMusic :: Environment (T DrumAttributes InstrumentAttributes) -> T
example :: IO ()
Documentation
newtype Environment a Source
The [OSC] state is used for messages for installing the instruments. We cannot use a Writer monad for this purpose because we have to read the generated messages for playMusic.
Constructors
Environment
unwrapEnvironment :: Writer [OSC] a
show/hide Instances
writeOSC :: [OSC] -> Environment ()Source
data Sound params attr Source
Constructors
Sound
nameFromSound :: String
flattenAttrFromSound :: attr -> AttributeList
type Instrument attr = Sound InstrumentParameters attrSource
type Drum attr = Sound DrumParameters attrSource
installSound :: SoundParameters params => (parameterTuple -> AttributeList, graph -> Sound params) -> String -> graph -> Environment (Sound params parameterTuple)Source
installSound0 :: SoundParameters params => String -> Sound params -> Environment (Sound params ())Source
installSound1 :: SoundParameters params => String -> (UGen -> Sound params) -> Environment (Sound params Double)Source
installSound2 :: SoundParameters params => String -> (UGen -> UGen -> Sound params) -> Environment (Sound params (Double, Double))Source
data SoundAttributes params Source
Constructors
SoundAttributes AttributeList String
show/hide Instances
type DrumAttributes = SoundAttributes DrumParametersSource
type InstrumentAttributes = SoundAttributes InstrumentParametersSource
rhythmicMusicFromDynamicMelody :: Instrument attr -> T (Rational, attr) -> T DrumAttributes InstrumentAttributesSource
rhythmicMusicFromMelody :: Instrument attr -> T attr -> T DrumAttributes InstrumentAttributesSource
rhythmicMusicFromRhythm :: Drum () -> Dur -> String -> T DrumAttributes InstrumentAttributesSource
rhythmicMusicFromDrum :: Drum () -> Dur -> T DrumAttributes InstrumentAttributesSource
fromRhythmicMusic :: Environment (T DrumAttributes InstrumentAttributes) -> TSource
example :: IO ()Source
Produced by Haddock version 2.3.0