diff options
author | Andrew Cady <d@jerkface.net> | 2015-12-07 16:18:08 -0500 |
---|---|---|
committer | Andrew Cady <d@jerkface.net> | 2015-12-07 16:18:08 -0500 |
commit | 1bed0c53f8bdd6c3c5fb1346524ab133a45763dd (patch) | |
tree | 4e45c2a986dc119c752847e5c0853ba4b00f2e43 /AlsaSeq.hs | |
parent | c15513cc1fc643dc088e430c0c41e923e29c928d (diff) |
Store note velocities in pitch sets
(actually pitch maps, now)
Diffstat (limited to 'AlsaSeq.hs')
-rw-r--r-- | AlsaSeq.hs | 30 |
1 files changed, 26 insertions, 4 deletions
@@ -1,7 +1,7 @@ | |||
1 | {-# LANGUAGE NondecreasingIndentation #-} | 1 | {-# LANGUAGE NondecreasingIndentation #-} |
2 | module AlsaSeq (withAlsaInit, parseAlsaEvents, parseAlsaEvents', forwardNoteEvent, | 2 | module AlsaSeq (withAlsaInit, parseAlsaEvents, parseAlsaEvents', parseAlsaEvents'', forwardNoteEvent, |
3 | cmdlineAlsaConnect, printChordLn, showChord, pitchList, showPitch, | 3 | cmdlineAlsaConnect, printChordLn, printChordLn', showChord, pitchList, showPitch, |
4 | unPitch, unChannel, MidiHook, MidiPitchSet) where | 4 | unPitch, unChannel, MidiHook, MidiPitchSet, MidiPitchMap) where |
5 | import qualified Sound.ALSA.Exception as AlsaExc | 5 | import qualified Sound.ALSA.Exception as AlsaExc |
6 | import qualified Sound.ALSA.Sequencer.Address as Addr | 6 | import qualified Sound.ALSA.Sequencer.Address as Addr |
7 | import qualified Sound.ALSA.Sequencer as SndSeq | 7 | import qualified Sound.ALSA.Sequencer as SndSeq |
@@ -23,6 +23,7 @@ import Text.Printf | |||
23 | import Control.Monad (when, forM_, forM) | 23 | import Control.Monad (when, forM_, forM) |
24 | 24 | ||
25 | import qualified Data.Set as Set | 25 | import qualified Data.Set as Set |
26 | import qualified Data.Map.Strict as Map | ||
26 | import Data.List (group, sort) | 27 | import Data.List (group, sort) |
27 | import Haskore.Basic.Pitch | 28 | import Haskore.Basic.Pitch |
28 | import Foreign.C.Error (Errno(Errno)) | 29 | import Foreign.C.Error (Errno(Errno)) |
@@ -32,6 +33,7 @@ unPitch = Event.unPitch | |||
32 | unChannel = Event.unChannel | 33 | unChannel = Event.unChannel |
33 | 34 | ||
34 | printChordLn set = printWords $ pitchWords set | 35 | printChordLn set = printWords $ pitchWords set |
36 | printChordLn' = printWords . map (showPitch . Event.unPitch . snd) . Map.keys | ||
35 | 37 | ||
36 | joinWords [] = "" | 38 | joinWords [] = "" |
37 | joinWords ls = foldr1 (\a b -> a ++ " " ++ b) ls | 39 | joinWords ls = foldr1 (\a b -> a ++ " " ++ b) ls |
@@ -41,7 +43,7 @@ printWords ls = putStrLn $ joinWords ls | |||
41 | 43 | ||
42 | showChord ls = joinWords $ pitchWords ls | 44 | showChord ls = joinWords $ pitchWords ls |
43 | 45 | ||
44 | showPitch x = | 46 | showPitch x = |
45 | let (octave, pitch) = Haskore.Basic.Pitch.fromInt $ fromIntegral x | 47 | let (octave, pitch) = Haskore.Basic.Pitch.fromInt $ fromIntegral x |
46 | in Haskore.Basic.Pitch.classFormat pitch (show octave) | 48 | in Haskore.Basic.Pitch.classFormat pitch (show octave) |
47 | 49 | ||
@@ -145,6 +147,7 @@ inputPendingLoop h b = do | |||
145 | (Right result) -> return result | 147 | (Right result) -> return result |
146 | 148 | ||
147 | type MidiPitchSet = Set.Set (Event.Channel, Event.Pitch) | 149 | type MidiPitchSet = Set.Set (Event.Channel, Event.Pitch) |
150 | type MidiPitchMap = Map.Map (Event.Channel, Event.Pitch) Event.Velocity | ||
148 | parseAlsaEvents :: SndSeq.AllowInput mode => | 151 | parseAlsaEvents :: SndSeq.AllowInput mode => |
149 | SndSeq.T mode -> Set.Set (Event.Channel, Event.Pitch) -> (Event.T -> IO a) -> IO MidiPitchSet | 152 | SndSeq.T mode -> Set.Set (Event.Channel, Event.Pitch) -> (Event.T -> IO a) -> IO MidiPitchSet |
150 | parseAlsaEvents h keysDown immediate = loop keysDown | 153 | parseAlsaEvents h keysDown immediate = loop keysDown |
@@ -185,6 +188,25 @@ parseAlsaEvents' h keysDown immediate = loop [] keysDown | |||
185 | loop (ev:events) (Set.delete (Event.noteChannel n, Event.noteNote n) keysDown) | 188 | loop (ev:events) (Set.delete (Event.noteChannel n, Event.noteNote n) keysDown) |
186 | _ -> loop (ev:events) keysDown | 189 | _ -> loop (ev:events) keysDown |
187 | 190 | ||
191 | parseAlsaEvents'' h keysDown immediate = loop [] keysDown | ||
192 | where | ||
193 | loop events keysDown = do | ||
194 | pending <- inputPendingLoop h True | ||
195 | if (pending == 0) then | ||
196 | return (events, keysDown) | ||
197 | else do | ||
198 | ev <- Event.input h | ||
199 | immediate ev | ||
200 | case Event.body ev of | ||
201 | Event.NoteEv Event.NoteOn n -> | ||
202 | if (Event.unVelocity (Event.noteVelocity n) == 0) then | ||
203 | loop (ev:events) (Map.delete (Event.noteChannel n, Event.noteNote n) keysDown) | ||
204 | else | ||
205 | loop (ev:events) (Map.insert (Event.noteChannel n, Event.noteNote n) (Event.noteVelocity n) keysDown) | ||
206 | Event.NoteEv Event.NoteOff n -> | ||
207 | loop (ev:events) (Map.delete (Event.noteChannel n, Event.noteNote n) keysDown) | ||
208 | _ -> loop (ev:events) keysDown | ||
209 | |||
188 | type MidiHook = Event.T -> IO () | 210 | type MidiHook = Event.T -> IO () |
189 | 211 | ||
190 | forwardNoteEvent :: SndSeq.AllowOutput mode => SndSeq.T mode -> Queue.T -> Addr.T -> MidiHook | 212 | forwardNoteEvent :: SndSeq.AllowOutput mode => SndSeq.T mode -> Queue.T -> Addr.T -> MidiHook |