module Reactive.Banana.MIDI.Program (
Reactive.Banana.MIDI.Program.traverse, traverseSeek,
next, seek, maybeNoteOn,
asBanks,
) where
import qualified Sound.MIDI.Message.Class.Query as Query
import qualified Sound.MIDI.Message.Class.Construct as Construct
import Sound.MIDI.Message.Channel (Channel, )
import Sound.MIDI.Message.Channel.Voice (Program, fromProgram, toProgram, )
import qualified Control.Monad.Trans.State as MS
import qualified Data.Traversable as Trav
import Control.Monad (join, mplus, )
import Data.Tuple.HT (mapFst, mapSnd, )
import Data.Maybe.HT (toMaybe, )
next ::
(Construct.C msg) =>
Channel -> MS.State [Program] (Maybe msg)
next chan =
MS.state $ \pgms ->
case pgms of
pgm:rest -> (Just $ Construct.program chan pgm, rest)
[] -> (Nothing, [])
seek :: Int -> Program -> MS.State [Program] (Maybe msg)
seek maxSeek pgm =
fmap (const Nothing) $
MS.modify $
uncurry (++) .
mapFst (dropWhile (pgm/=)) .
splitAt maxSeek
traverse ::
(Query.C msg, Construct.C msg) =>
msg -> MS.State [Program] (Maybe msg)
traverse =
fmap join . Trav.traverse next . maybeNoteOn
traverseSeek ::
(Query.C msg, Construct.C msg) =>
Int ->
msg -> MS.State [Program] (Maybe msg)
traverseSeek maxSeek e =
fmap join $ Trav.sequence $
mplus
(fmap next $ maybeNoteOn e)
(fmap (seek maxSeek . snd) $ Query.program e)
maybeNoteOn :: (Query.C msg) => msg -> Maybe Channel
maybeNoteOn msg =
Query.noteExplicitOff msg >>= \(c, (_p, _v, on)) -> toMaybe on c
replace :: Real i => [i] -> i -> [i] -> (Bool, [i])
replace (n:ns) pgm pt =
let (p,ps) =
case pt of
[] -> (0,[])
(x:xs) -> (x,xs)
in if pgm<n
then (True, pgm:ps)
else mapSnd (p:) $
replace ns (pgmn) ps
replace [] _ ps = (False, ps)
fromBanks :: Real i => [i] -> [i] -> i
fromBanks ns ps =
foldr (\(n,p) s -> p+n*s) 0 $
zip ns ps
asBanks ::
(Query.C msg, Construct.C msg) =>
[Int] ->
msg -> MS.State [Int] msg
asBanks ns e =
maybe
(return e)
(\(chan,pgm) -> do
valid <- MS.state $ replace ns (fromProgram pgm)
fmap (Construct.program chan) $
if valid
then MS.gets (toProgram . fromBanks ns)
else return pgm) $
Query.program e