reactive-midyim-0.2: Process MIDI events via reactive-banana

Safe HaskellNone

Reactive.Banana.MIDI.Process

Synopsis

Documentation

class Moment moment whereSource

Methods

liftMoment :: Moment t a -> moment t aSource

Instances

class (Moment reactor, Timed reactor) => Reactor reactor whereSource

Methods

reserveSchedule :: Frameworks t => reactor t ([AbsoluteTicks reactor] -> IO (), IO (), Event t (AbsoluteTicks reactor))Source

Provide a function for registering future beats and the return the reactive event list that results from the sent beats.

scheduleQueue :: (Reactor reactor, Frameworks t) => Behavior t (AbsoluteTicks reactor) -> Event t (Bundle reactor a) -> reactor t (Event t a)Source

initialEvent :: (Reactor reactor, Frameworks t) => a -> reactor t (Event t a)Source

Generate an event at the first time point.

beat :: (Reactor reactor, Frameworks t) => Behavior t (RelativeTicks reactor) -> reactor t (Event t (AbsoluteTicks reactor))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 :: (Reactor reactor, Frameworks t) => RelativeTicks reactor -> Behavior t (RelativeTicks reactor) -> reactor t (Event t (AbsoluteTicks reactor))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 :: (Reactor reactor, Frameworks t) => Behavior t (AbsoluteTicks reactor) -> Behavior t (RelativeTicks reactor) -> reactor t (Event t (AbsoluteTicks reactor))Source

Similar to beat but it reacts immediately to tempo changes. This requires the ability of the backend (e.g. 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.

delaySchedule :: (Reactor reactor, Frameworks t) => RelativeTicks reactor -> Behavior t (AbsoluteTicks reactor) -> Event t a -> reactor t (Event t a)Source

Demonstration of scheduleQueue. For real use with ALSA you should prefer delay, since this uses precisely timed delivery by ALSA.

delay :: RelativeTicks m -> Event t ev -> Event t (Future m ev)Source

delayAdd :: RelativeTicks m -> Event t ev -> Event t (Future m ev)Source

pressed :: (C set, Ord key) => set key value -> Event f (BoundaryExt key value) -> (Event f [Boundary key value], Behavior f (set key value))Source

register pressed keys

latch :: Ord key => Event f (Boundary key value) -> (Event f (Boundary key value), Behavior f (Map key value))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

snapSelect :: (Moment moment, Frameworks t, C set, C pitch, Eq pitch, Eq value) => Behavior t (set pitch value) -> Behavior t Int -> moment t (Event t [Boundary pitch value])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 are distinct distances between the pitches.

uniqueChanges :: (Moment moment, Frameworks t, Eq a) => Behavior t a -> moment t (Event t a)Source

sweep :: (Frameworks t, Reactor reactor) => RelativeSeconds reactor -> (Double -> Double) -> Behavior t Double -> reactor t (Event t (AbsoluteTicks reactor), Behavior t Double)Source

cyclePrograms :: (C msg, C msg) => [Program] -> Event t msg -> Event t (Maybe msg)Source

cycleProgramsDefer :: (C msg, C msg) => RelativeTicks m -> [Program] -> Behavior t (AbsoluteTicks m) -> Event t msg -> Event t (Maybe msg)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.

noteSequence :: C msg => RelativeTicks m -> Bool -> [Bool -> msg] -> Bundle m msgSource

guitar :: (C msg, C set) => RelativeTicks m -> Behavior t (set PitchChannel Velocity) -> Event t Bool -> Event t (Bundle m msg)Source

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 :: (Reactor reactor, Frameworks t, C msg, C msg, Quantity time) => Channel -> T reactor Relative time -> T reactor Relative time -> [([Pitch], [Pitch])] -> Behavior t (AbsoluteTicks reactor) -> Event t msg -> reactor t (Event t (Bundle reactor msg))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 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.