Safe Haskell | None |
---|
Auditor functions common to all sample libraries.
- type Amplitude = Double
- type Index = Int
- type NC = Int
- type Note = (Index, Amplitude)
- type Chord = [Note]
- type Duration = Double
- type Start_Time = Double
- type P = (Start_Time, Chord)
- type PP = [P]
- type Sample_Loader = [Index] -> [Message]
- to_p :: (a -> Index, a -> Amplitude) -> (Start_Time, [a]) -> P
- note_index :: Note -> Index
- note_amplitude :: Note -> Amplitude
- chord_indices :: Chord -> [Index]
- p_start_time :: P -> Start_Time
- p_chord :: P -> Chord
- pp_start_times :: PP -> [Start_Time]
- pp_chords :: PP -> [Chord]
- pp_duration :: PP -> Duration
- pp_indices :: PP -> [Index]
- chd_osc :: Chord -> [Message]
- p_osc :: P -> Bundle
- pp_nrt :: NC -> Sample_Loader -> PP -> NRT
- pp_nrt_write :: FilePath -> NC -> Sample_Loader -> PP -> IO ()
- instr_osc :: NC -> Message
- smplr :: NC -> UGen
- au_load_instr :: Transport m => NC -> m ()
- au_chd :: Transport m => (Chord, Duration) -> m ()
- pp_st_to_dur :: PP -> [(Chord, Duration)]
- pp_audition :: Transport m => PP -> m ()
Documentation
type Start_Time = DoubleSource
Start time
type P = (Start_Time, Chord)Source
Start_Time
and Chord
.
type Sample_Loader = [Index] -> [Message]Source
note_index :: Note -> IndexSource
chord_indices :: Chord -> [Index]Source
p_start_time :: P -> Start_TimeSource
pp_start_times :: PP -> [Start_Time]Source
pp_nrt :: NC -> Sample_Loader -> PP -> NRTSource
Generate set of OSC
given NC
, Sample_Loader
and PP
.
pp_nrt_write :: FilePath -> NC -> Sample_Loader -> PP -> IO ()Source
Variant of pp_osc
that writes NRT
score to named file using
writeNRT
.
Instrument
Audition
au_load_instr :: Transport m => NC -> m ()Source
Load sample playback instrument to scsynth
at Transport
.
pp_st_to_dur :: PP -> [(Chord, Duration)]Source