module Sound.MIDI.ALSA.Check where
import qualified Sound.MIDI.ALSA as MALSA
import qualified Sound.ALSA.Sequencer.Event as Event
import Sound.MIDI.Message.Channel (Channel, )
import Sound.MIDI.Message.Channel.Voice (Controller, )
import Data.Accessor.Basic ((^.), )
import Data.Maybe.HT (toMaybe, )
import Control.Monad (guard, )
anyController ::
Channel -> Event.T -> Maybe (Controller, Int)
anyController chan e = do
Event.CtrlEv Event.Controller c <- Just $ Event.body e
guard (c ^. MALSA.ctrlChannel == chan)
MALSA.Controller cn cv <- Just $ c ^. MALSA.ctrlControllerMode
return (cn, cv)
controller :: Channel -> Controller -> Event.T -> Maybe Int
controller chan ctrl e = do
(c,n) <- anyController chan e
guard (ctrl==c)
return n
pitchBend :: Channel -> Event.T -> Maybe Int
pitchBend chan e =
case Event.body e of
Event.CtrlEv Event.PitchBend c ->
toMaybe
(c ^. MALSA.ctrlChannel == chan)
(c ^. MALSA.ctrlValue)
_ -> Nothing
channelPressure :: Channel -> Event.T -> Maybe Int
channelPressure chan e =
case Event.body e of
Event.CtrlEv Event.ChanPress c ->
toMaybe
(c ^. MALSA.ctrlChannel == chan)
(c ^. MALSA.ctrlValue)
_ -> Nothing