summaryrefslogtreecommitdiff
path: root/midi-dump.hs
diff options
context:
space:
mode:
Diffstat (limited to 'midi-dump.hs')
-rw-r--r--midi-dump.hs76
1 files changed, 31 insertions, 45 deletions
diff --git a/midi-dump.hs b/midi-dump.hs
index 9407fae..d2b6c15 100644
--- a/midi-dump.hs
+++ b/midi-dump.hs
@@ -30,6 +30,7 @@ import qualified Sound.ALSA.Sequencer.RealTime as RealTime
30 30
31import Midi 31import Midi
32import RealTimeQueue as Q hiding (null) 32import RealTimeQueue as Q hiding (null)
33import qualified Codec.Midi
33 34
34verbose :: Bool 35verbose :: Bool
35verbose = False 36verbose = False
@@ -39,7 +40,8 @@ main = main' `AlsaExc.catch` handler
39 where 40 where
40 handler e = when verbose $ putStrLn $ "alsa_exception: " ++ AlsaExc.show e 41 handler e = when verbose $ putStrLn $ "alsa_exception: " ++ AlsaExc.show e
41 42
42data Triad = Major Event.Pitch | Minor Event.Pitch deriving (Show, Eq) 43data TriadType = Major | Minor deriving (Show, Eq)
44data Triad = Triad TriadType Event.Pitch Event.Velocity deriving (Show, Eq)
43 45
44data LoopState = LoopState { 46data LoopState = LoopState {
45 _wantExit :: Bool, 47 _wantExit :: Bool,
@@ -216,10 +218,10 @@ type MidiController = MidiControllerT IO
216playRecording :: Playable p => p -> MidiController () 218playRecording :: Playable p => p -> MidiController ()
217playRecording = playEvents . playableEvents 219playRecording = playEvents . playableEvents
218 220
219-- fixedOutputChannel :: Maybe _ 221fixedOutputChannel :: Maybe Codec.Midi.Channel
220fixedOutputChannel = Just 0 222fixedOutputChannel = Just 0
221 223
222-- setOutputChannel :: Codec.Midi.Message -> Codec.Midi.Message 224setOutputChannel :: Codec.Midi.Message -> Codec.Midi.Message
223setOutputChannel = case fixedOutputChannel of Just n -> setChannel n 225setOutputChannel = case fixedOutputChannel of Just n -> setChannel n
224 Nothing -> id 226 Nothing -> id
225 227
@@ -278,62 +280,46 @@ processMidi = do
278 280
279filterTriads :: MidiPitchMap -> MidiController () 281filterTriads :: MidiPitchMap -> MidiController ()
280filterTriads newKeys = do 282filterTriads newKeys = do
281 let newTriad = detectTriad newKeys 283 let newTriad = fmap snd $ listToMaybe $ detectTriads newKeys -- TODO: handle each channel
282 (Just (vel, _)) = detectTriad' newKeys
283 -- vel = Event.Velocity 127
284 oldTriad <- gets _triad 284 oldTriad <- gets _triad
285 when (newTriad /= oldTriad) $ do 285 when (newTriad /= oldTriad) $ do
286 forM_ oldTriad (sendTriadEvents Nothing) 286 forM_ oldTriad $ triadOff >>> sendTriadEvents
287 forM_ newTriad (sendTriadEvents $ Just vel) 287 forM_ newTriad sendTriadEvents
288 modify $ \s -> s { _triad = newTriad } 288 modify $ \s -> s { _triad = newTriad }
289 289
290triadBase :: Triad -> Event.Pitch 290triadOff :: Triad -> Triad
291triadBase (Major n) = n 291triadOff (Triad t p _) = Triad t p (Event.Velocity 0)
292triadBase (Minor n) = n
293 292
294-- TODO: set velocity based on average from triad (this requires storing that 293sendTriadEvents :: Triad -> MidiController ()
295-- information, changing the MidiPitchMap type for one more complex than a mere 294sendTriadEvents (Triad _ (Event.Pitch base) vel) = do
296-- Set)
297sendTriadEvents :: Maybe Event.Velocity -> Triad -> MidiController ()
298sendTriadEvents vel triad = do
299 liftIO $ print vel
300 forM_ notes (delayNoteEv (TimeSpec 0 0)) 295 forM_ notes (delayNoteEv (TimeSpec 0 0))
301 return () 296 return ()
302 297
303 where 298 where
304 base = Event.unPitch $ triadBase triad
305 notes = fromVel vel <$> fill base 299 notes = fromVel vel <$> fill base
306 fill n = [ x + y | x <- [n, n + 7], y <- [12, -12]] 300 fill n = [ x + y | x <- [n, n + 7], y <- [12, -12]]
307 fromVel (Just v) pitch = Event.NoteEv Event.NoteOn $ Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) v 301 fromVel (Event.Velocity 0) pitch = Event.NoteEv Event.NoteOff $ Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) (Event.Velocity 0)
308 fromVel Nothing pitch = Event.NoteEv Event.NoteOff $ Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) (Event.Velocity 0) 302 fromVel v pitch = Event.NoteEv Event.NoteOn $ Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) v
309 303
310detectTriad' :: MidiPitchMap -> Maybe (Event.Velocity, Triad) 304detectTriads :: MidiPitchMap -> [(Event.Channel, Triad)]
311detectTriad' pitches = listToMaybe $ concatMap f (Map.keys pitches) 305detectTriads pitches = concatMap f (Map.keys pitches)
312 where 306 where
313 f pitch = do 307 f pitch = do
314 let first_ = Map.lookup pitch pitches 308 let [first_, minor3, major3, fifth_] = map (getVelocity . getNote) [0, 3, 4, 7]
315 major3 = Map.lookup (addPitch 4 pitch) pitches 309 major = sumM [first_, major3, fifth_]
316 minor3 = Map.lookup (addPitch 3 pitch) pitches 310 minor = sumM [first_, minor3, fifth_]
317 fifth_ = Map.lookup (addPitch 7 pitch) pitches 311 getNote n = Map.lookup (addPitch n pitch) pitches
318 let major = foldM (fmap . (+)) (0::Int) $ (fmap . fmap) (fromIntegral . Event.unVelocity) [first_, major3, fifth_] 312 case (major, minor) of
319 let minor = foldM (fmap . (+)) (0::Int) $ (fmap . fmap) (fromIntegral . Event.unVelocity) [first_, minor3, fifth_] 313 (Just n, _) -> [(fst pitch, Triad Major (snd pitch) (Event.Velocity $ fromIntegral $ n `div` 3))]
320 case major of 314 (_, Just n) -> [(fst pitch, Triad Minor (snd pitch) (Event.Velocity $ fromIntegral $ n `div` 3))]
321 Just n -> [(Event.Velocity $ fromIntegral $ n `div` 3, Major $ snd pitch)] 315 _ -> []
322 Nothing -> 316 addPitch :: Word8 -> (t, Event.Pitch) -> (t, Event.Pitch)
323 case minor of 317 addPitch n = fmap (Event.Pitch . (+ n) . Event.unPitch)
324 Just n -> [(Event.Velocity $ fromIntegral $ n `div` 3, Minor $ snd pitch)] 318 getVelocity :: Maybe Event.Velocity -> Maybe Int
325 Nothing -> [] 319 getVelocity = fmap (fromIntegral . Event.unVelocity)
326 addPitch n (c, Event.Pitch p) = (c, Event.Pitch $ p + n) 320
327 321sumM :: (Monad m, Num a, Foldable t) => t (m a) -> m a
328detectTriad :: MidiPitchMap -> Maybe Triad 322sumM = foldM (fmap . (+)) 0
329detectTriad pitches = listToMaybe $ concatMap f (Map.keys pitches)
330 where
331 f pitch
332 | not $ Map.member (addPitch 7 pitch) pitches = []
333 | Map.member (addPitch 4 pitch) pitches = [Major $ snd pitch] -- TODO: do not just drop the channel!!
334 | Map.member (addPitch 3 pitch) pitches = [Minor $ snd pitch]
335 | otherwise = []
336 addPitch n (c, Event.Pitch p) = (c, Event.Pitch $ p+n)
337 323
338latestEvent :: Recording -> TimeSpec 324latestEvent :: Recording -> TimeSpec
339latestEvent (StartRecording x) = x 325latestEvent (StartRecording x) = x