module Sound.MIDI.Message.Class.Check (
C(..),
noteExplicitOff,
noteImplicitOff,
controller,
liftMidi,
liftFile,
) where
import qualified Sound.MIDI.Message.Class.Utility as CU
import Sound.MIDI.Message.Channel (Channel, )
import Sound.MIDI.Message.Channel.Voice (Pitch, Velocity, Program, Controller, )
import qualified Sound.MIDI.File.Event as FileEvent
import qualified Sound.MIDI.Message as MidiMsg
import qualified Sound.MIDI.Message.Channel as ChannelMsg
import qualified Sound.MIDI.Message.Channel.Mode as Mode
import Control.Monad (guard, )
class C event where
note :: Channel -> event -> Maybe (Velocity, Pitch, Bool)
program :: Channel -> event -> Maybe Program
anyController :: Channel -> event -> Maybe (Controller, Int)
pitchBend :: Channel -> event -> Maybe Int
channelPressure :: Channel -> event -> Maybe Int
mode :: Channel -> event -> Maybe Mode.T
note _chan _ev = Nothing
program _chan _ev = Nothing
anyController _chan _ev = Nothing
pitchBend _chan _ev = Nothing
channelPressure _chan _ev = Nothing
mode _chan _ev = Nothing
noteExplicitOff ::
(C event) =>
Channel -> event -> Maybe (Velocity, Pitch, Bool)
noteExplicitOff chan e =
fmap CU.explicitNoteOff $ note chan e
noteImplicitOff ::
(C event) =>
Channel -> event -> Maybe (Velocity, Pitch, Bool)
noteImplicitOff chan e =
fmap CU.implicitNoteOff $ note chan e
controller ::
(C event) =>
Channel -> Controller -> event -> Maybe Int
controller chan ctrl e = do
(c,n) <- anyController chan e
guard (ctrl==c)
return n
lift ::
(Maybe ChannelMsg.Body -> Maybe a) ->
Channel -> ChannelMsg.T -> Maybe a
lift act chan msg = do
guard (ChannelMsg.messageChannel msg == chan)
act $ Just $ ChannelMsg.messageBody msg
instance C ChannelMsg.T where
note = lift CU.note
program = lift CU.program
anyController = lift CU.anyController
pitchBend = lift CU.pitchBend
channelPressure = lift CU.channelPressure
mode = lift CU.mode
liftMidi ::
(Channel -> ChannelMsg.T -> Maybe a) ->
(Channel -> MidiMsg.T -> Maybe a)
liftMidi checkMsg chan msg =
case msg of
MidiMsg.Channel chanMsg -> checkMsg chan chanMsg
_ -> Nothing
instance C MidiMsg.T where
note = liftMidi note
program = liftMidi program
anyController = liftMidi anyController
pitchBend = liftMidi pitchBend
channelPressure = liftMidi channelPressure
mode = liftMidi mode
liftFile ::
(Channel -> ChannelMsg.T -> Maybe a) ->
(Channel -> FileEvent.T -> Maybe a)
liftFile checkMsg chan msg =
case msg of
FileEvent.MIDIEvent midiMsg -> checkMsg chan midiMsg
_ -> Nothing
instance C FileEvent.T where
note = liftFile note
program = liftFile program
anyController = liftFile anyController
pitchBend = liftFile pitchBend
channelPressure = liftFile channelPressure
mode = liftFile mode