streamed-0.2: Programmatically edit MIDI event streams via ALSA

Safe HaskellNone

Sound.MIDI.ALSA.Common

Contents

Synopsis

helper functions

data Handle Source

Constructors

Handle 

Fields

sequ :: T DuplexMode
 
client :: T
 
portPublic :: T
 
portPrivate :: T
 
queue :: T
 

setTimeStamping :: ReaderT Handle IO ()Source

make ALSA set the time stamps in incoming events

send single events

constructors

time

type TimeAbs = RationalSource

The Time types are used instead of floating point types, because the latter ones caused unpredictable 'negative number' errors. The denominator must always be a power of 10, this way we can prevent unlimited grow of denominators.

newtype Time Source

Constructors

Time 

Fields

deconsTime :: Rational
 

nano :: Num a => aSource

events

type Bundle a = [(Time, a)]Source

The times are relative to the start time of the bundle and do not need to be ordered.

effects

transpose :: Int -> Data -> Maybe DataSource

Transpose a note event by the given number of semitones. Non-note events are returned without modification. If by transposition a note leaves the range of representable MIDI notes, then we return Nothing.

reverse :: Data -> Maybe DataSource

Swap order of keys. Non-note events are returned without modification. If by reversing a note leaves the range of representable MIDI notes, then we return Nothing.

replaceProgram :: [Int32] -> Int32 -> [Int32] -> (Bool, [Int32])Source

 > replaceProgram [1,2,3,4] 5 [10,11,12,13]
 (True,[10,11,2,13])

programsAsBanks :: [Int32] -> Data -> State [Int32] DataSource

Interpret program changes as a kind of bank switches in order to increase the range of instruments that can be selected via a block of patch select buttons.

programAsBanks ns divides the first sum ns instruments into sections of sizes ns!!0, ns!!1, .... Each program in those sections is interpreted as a bank in a hierarchy, where the lower program numbers are the least significant banks. Programs from sum ns on are passed through as they are. product ns is the number of instruments that you can address using this trick. In order to avoid overflow it should be less than 128.

E.g. programAsBanks [n,m] interprets subsequent program changes to a (0<=a<n) and n+b (0<=b<m) as a program change to b*n+a. programAsBanks [8,8] allows to select 64 instruments by 16 program change buttons, whereas programAsBanks [8,4,4] allows to address the full range of MIDI 128 instruments with the same number of buttons.

traversePrograms :: Data -> State [Program] [Data]Source

Before every note switch to another instrument according to a list of programs given as state of the State monad. I do not know how to handle multiple channels in a reasonable way. Currently I just switch the instrument independent from the channel, and send the program switch to the same channel as the beginning note.

traverseProgramsSeek :: Int -> Data -> State [Program] [Data]Source

This function extends traversePrograms. It reacts on external program changes by seeking an according program in the list. This way we can reset the pointer into the instrument list. However the search must be limited in order to prevent an infinite loop if we receive a program that is not contained in the list.

controllerFromNote :: (Int -> Int) -> Controller -> Data -> Maybe DataSource

Map NoteOn events to a controller value. This way you may play notes via the resonance frequency of a filter.

selectFromOctaveChord :: Int -> Time -> KeyQueue -> EventDataBundleSource

Generate notes according to the key set, where notes for negative and too large indices are padded with keys that are transposed by octaves.

powerRationalFromFloat :: (Floating a, RealFrac a) => Int -> Int -> a -> a -> RationalSource

Compute base ** expo approximately to result type Rational such that the result has a denominator which is a power of digitBase and a relative precision of numerator of precision digits with respect to digitBase-ary numbers.

data PatternMono i Source

Constructors

PatternMono (Selector i) [i] 

data IndexNote i Source

Constructors

IndexNote Int i 

Instances

Eq i => Eq (IndexNote i) 
Ord i => Ord (IndexNote i) 
Show i => Show (IndexNote i) 

item :: i -> Int -> IndexNote iSource

data PatternPoly i Source

Constructors

PatternPoly (Selector i) (T Int [IndexNote i]) 

fraction :: RealFrac a => a -> aSource

patterns

flipSeq :: Int -> [Int]Source

See Haskore/FlipSong

flipSeq m !! n = cross sum of the m-ary representation of n modulo m.

For m=2 this yields http:www.research.att.comcgi-binaccess.cgiasnjassequenceseisA.cgi?Anum=A010060

bruijn :: Int -> Int -> [Int]Source

bruijn n k is a sequence with length n^k where cycle (bruijn n k) contains all n-ary numbers with k digits as infixes. The function computes the lexicographically smallest of such sequences.

bruijnAll :: Int -> Int -> [[Int]]Source

All Bruijn sequences with a certain

data Trie a b Source

Constructors

Leaf b 
Branch [(a, Trie a b)] 

Instances

(Show a, Show b) => Show (Trie a b) 

fullTrie :: b -> [a] -> Int -> Trie a bSource

deleteWord :: (Eq a, Eq b) => b -> [a] -> Trie a [b] -> Trie a [b]Source

lookupWord :: Eq a => [a] -> Trie a b -> Maybe bSource

predicates

event list support

mergeStable :: C time => T time body -> T time body -> T time bodySource

mergeEither :: C time => T time a -> T time b -> T time (Either a b)Source