reactive-balsa-0.1.1: Programmatically edit MIDI events via ALSA and reactive-banana

Safe HaskellNone

Reactive.Banana.ALSA.Sequencer

Contents

Synopsis

make ALSA reactive

newtype Reactor t a Source

Constructors

Reactor 

run :: Events ev => (forall t. Frameworks t => Event t Data -> Event t ev) -> ReaderT Handle IO ()Source

runM :: Events ev => (forall t. Frameworks t => Behavior t Abs -> Event t Data -> Reactor t (Event t ev)) -> ReaderT Handle IO ()Source

outputEvents :: Events evs => Handle -> Abs -> evs -> IO ()Source

reactimate :: Frameworks t => Event t (IO ()) -> Reactor t ()Source

bypass :: (Events a, Events c) => (a -> Maybe b) -> (Event f b -> Event f c) -> Event f a -> Event f [Future Data]Source

examples

pressed :: C set => set -> Event f NoteBoundaryExt -> (Event f [NoteBoundary], Behavior f set)Source

register pressed keys

delaySchedule :: Frameworks t => T -> Behavior t Abs -> Event t Data -> Reactor t (Event t Data)Source

Demonstration of scheduleQueue, but for real use prefer delay, since this uses precisely timed delivery by ALSA.

delay :: T -> Event t ev -> Event t (Future ev)Source

delayAdd :: T -> Event t ev -> Event t (Future ev)Source

beat :: Frameworks t => Behavior t T -> Reactor t (Event t Abs)Source

Generate a beat according to the tempo control. The input signal specifies the period between two beats. The output events hold the times, where they occur.

beatQuant :: Frameworks t => T -> Behavior t T -> Reactor t (Event t Abs)Source

Similar to beat but warrants a maximum reaction time to tempo changes. This way you can alter slow tempos to faster one more quickly.

beatVar :: Frameworks t => Behavior t Abs -> Behavior t T -> Reactor t (Event t Abs)Source

Similar to beat but it reacts immediately to tempo changes. This requires the ability of ALSA to cancel sent Echo messages and it requires to know the precise time points of tempo changes, thus we need the Discrete input instead of Behaviour and we need a behaviour for the current time.

tempoCtrl :: C ev => Channel -> Controller -> T -> (T, T) -> Event t ev -> (Behavior t T, Event t ev)Source

controllerExponential :: (Floating a, C ev) => Channel -> Controller -> a -> (a, a) -> Event t ev -> Behavior t aSource

controllerLinear :: (Fractional a, C ev) => Channel -> Controller -> a -> (a, a) -> Event t ev -> Behavior t aSource

cycleProgramsDefer :: T -> [Program] -> Behavior t Abs -> Event t Data -> Event t (Maybe Data)Source

 cycleProgramsDefer t

After a note that triggers a program change, we won't change the program in the next t seconds. This is in order to allow chords being played and in order to skip accidentally played notes.

guitar :: C set => T -> Behavior t set -> Event t Bool -> Event t EventDataBundleSource

This process simulates playing chords on a guitar. If you press some keys like C, E, G on the keyboard, then this process figures out what tones would be played on a guitar.

Call it like guitar stepTime chords triggers.

stepTime is the delay between to successive notes. A good value is 0.03 (seconds). The chords to be played are passed in by chords. This should be the output of pressed. Further on the function needs events that trigger playing the chord in trigger argument. The trigger consists of the trigger time and the direction to be played (True = down from high to low pitches, False = up from low to high pitches). The trigger may be derived from a specific key that is pressed and released, or two keys, one for each direction.

trainer :: Frameworks t => Channel -> T -> T -> [([Pitch], [Pitch])] -> Behavior t Abs -> Event t Data -> Reactor t (Event t EventDataBundle)Source

Audio perception trainer

Play sets of notes and let the human player answer to them according to a given scheme. Repeat playing the notes sets until the trainee answers correctly. Then continue with other sequences, maybe more complicated ones.

possible tasks:

  • replay a RBU.sequence of pitches on the keyboard: single notes for training abolute pitches, intervals all with the same base notes, intervals with different base notes
  • transpose a set of pitches: tranpose to a certain base note, transpose by a certain interval
  • play a set of pitches in a different order: reversed order, in increasing pitch
  • replay a set of simultaneously pressed keys

The difficulty can be increased by not connecting the keyboard directly with the sound generator. This way, the trainee cannot verify, how the pressed keys differ from the target keys.

Sometimes it seems that you are catched in an infinite loop. This happens if there were too many keys pressed. The trainer collects all key press events, not only the ones that occur after the target set is played. This way you can correct yourself immediately, before the target is repeatedly played. The downside is, that there may be key press events hanging around. You can get rid of them by pressing a key again and again, but slowly, until the target is played, again. Then the queue of registered keys should be empty and you can proceed training.

snapSelect :: (Frameworks t, C set) => Behavior t set -> Behavior t Int -> Reactor t (Event t [Data])Source

Use a MIDI controller for selecting a note from a key set. Only the pitch class of the keys is respected. The controller behavior must be in the range 0-127. This way, it accesses the whole range of MIDI notes. The output note is stopped and a new note is played whenever turning the knob alters the note pitch. The advantage of the effect is that the pitch range of the knob does not depend on the number of pressed keys. The disadvantage is that there a distinct distances between the pitches.