streamed-0.2: Programmatically edit MIDI event streams via ALSA

Safe HaskellSafe-Infered

Sound.MIDI.ALSA.Causal

Synopsis

Documentation

data T a b Source

The list of scheduled triggers must be finite.

This process cannot drop an incoming event. In order to do so, you must write something of type T a (Maybe b). For convenience you could wrap this in something like Ext a b.

Instances

lift :: (Applicative t, Traversable t) => T a b -> T (t a) (t b)Source

Here we abuse the Applicative constraint. Actually we only need pure.

liftPoint :: Traversable t => (b -> t b) -> T a b -> T (t a) (t b)Source

Typical instance for the traversable type t are '[]' and Maybe.

map :: (a -> b) -> T a bSource

parallel :: Monoid b => T a b -> T a b -> T a bSource

Run two stream processor in parallel. We cannot use the Arrow method &&& since we cannot define the first method of the Arrow class. Consider first :: arrow a b -> arrow (c,a) (c,b) and a trigger where arrow a b generates an event of type b. How could we generate additionally an event of type c without having an input event?

eitherIn :: T a c -> T b c -> T (Either a b) cSource

traverse :: s -> (a -> State s b) -> T a bSource

flatten :: T (Bundle a) (Maybe a)Source

input is most oftenly of type EventDataBundle

process :: T Data EventDataBundle -> ReaderT Handle IO ()Source

TODO: We should allow the process to access and modify the ALSA port number.

reverse :: T Data (Maybe Data)Source

Swap order of keys. This is a funny effect and a new challenge to playing a keyboard.

partition :: (a -> Bool) -> T a (Maybe a, Maybe a)Source

guide :: (a -> Bool) -> T a b -> T a b -> T a bSource

guideWithMode :: Monoid b => (Data -> Bool) -> T Data b -> T Data b -> T Data bSource

cycleProgramsDefer :: Time -> [Program] -> T Data [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.

groupLatch :: T Data [Data]Source

All pressed keys are latched until a key is pressed after a pause (i.e. all keys released). For aborting the pattern you have to send a AllNotesOff or AllSoundOff message.

serialLatch :: Int -> T Data [Data]Source

A key is hold until n times further keys are pressed. The n-th pressed key replaces the current one.

guitar :: Time -> Time -> T Data EventDataBundleSource

Try for instance guitar 0.05 0.03.

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 and plays them one after another with short delays. If you release the keys then the chord is played in reverse order. This simulates the hand going up and down on the guitar strings. Unfortunatley it is not possible to go up twice or go down twice this way. The octaves of the pressed keys are ignored.

In detail calling guitar collectTime stepTime means: If a key is pressed, then collect all key-press events for the next collectTime seconds. After this period, send out a guitar-like chord pattern for the pressed keys with a delay of stepTime between the notes. Now wait until all keys are released. Note that in the meantime keys could have been pressed or released. They are registered, but not played. If all keys are released then send out the reverse chord.

On an AllSoundOff message, release all played tones.

I don't know whether emitted key-events are always consistent.

trainer :: Channel -> Time -> Time -> [([Pitch], [Pitch])] -> T Data EventDataBundleSource

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.