summaryrefslogtreecommitdiff
path: root/midi-dump.hs
blob: 0de26bf35ace39dbdb20217a139b1ee894727607 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}

import           AlsaSeq
import           Control.Monad.RWS.Strict
import           Data.List
import           Data.Maybe
import qualified Data.Map.Strict                as Map
import           Data.Map.Strict                (Map)
import qualified Sound.ALSA.Exception           as AlsaExc
import qualified Sound.ALSA.Sequencer.Event     as Event
import           System.Clock

import           Control.Applicative
import           Database.SQLite.Simple
import           Database.SQLite.Simple.FromRow ()

import           BasePrelude                    hiding (loop)
import           Control.Concurrent.Chan        ()
import           Prelude                        hiding (id, (.))

import qualified Sound.ALSA.Sequencer
import qualified Sound.ALSA.Sequencer.Address
import qualified Sound.ALSA.Sequencer.Port
import qualified Sound.ALSA.Sequencer.Queue
import qualified Sound.ALSA.Sequencer.Time as AlsaTime
import qualified Sound.ALSA.Sequencer.RealTime as AlsaRealTime

import Midi
import RealTimeQueue as Q hiding (null)
import qualified Codec.Midi
import Codec.Midi (Midi(..), FileType(..), TimeDiv(..))

import qualified Control.Concurrent.Thread as Thread
import Data.Time.Format
import Data.Time.LocalTime (utcToLocalZonedTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Data.Time.Clock (picosecondsToDiffTime, UTCTime)

import qualified Data.Set as Set
import Data.Set (Set)

import System.IO
import AlsaShutUp

verbose :: Bool
verbose = False

main :: IO ()
main = main' `AlsaExc.catch` handler
  where
  handler e = when verbose $ putStrLn $ "alsa_exception: " ++ AlsaExc.show e

data TriadType = Major | Minor deriving (Show, Eq, Ord)
data Triad =
       Triad
         { _triadType :: TriadType
         , _triadPitch :: Event.Pitch
         , _triadVelocity :: Event.Velocity
         }
  deriving (Show, Eq, Ord)
toPitchClass :: Event.Pitch -> PitchClass
toPitchClass = Event.unPitch >>> (`mod` 12) >>> fromIntegral
tonic :: Triad -> PitchClass
tonic (Triad _ p _) = toPitchClass p

data TriadRecorder = TriadNotRecording | AwaitingTriad | AwaitingRelease Event.Pitch TriadType | Recording Event.Pitch TriadType

type PitchClass = Int
type ScaleDegree = Int

data LoopState = LoopState {
  _wantExit    :: Bool,
  _waitThreads :: [IO (Thread.Result ())],
  _keysDown    :: MidiPitchMap,
  _triad       :: Set Triad,
  _triadMap    :: Map (PitchClass, TriadType) (Set ScaleDegree),
  _triadRecording :: TriadRecorder,
  _scheduled   :: Q.Queue Event.Data,
  _metronome   :: Maybe Metronome,
  _recording   :: Recording,
  _replay      :: Recording,
  _lastTick    :: TimeSpec
}

data Metronome = Metronome {
  _metronomeStart :: TimeSpec,
  _metronomeInterval :: TimeSpec,
  _metronomeTicked :: TimeSpec
}

initializeState :: TimeSpec -> LoopState
initializeState now = LoopState False [] Map.empty Set.empty Map.empty TriadNotRecording createQueue Nothing (StartRecording now) (StartRecording now) now

data LoopEnv = LoopEnv {
  _saver         :: Chan CompleteRecording,
  _sqlite        :: Connection,
  _startTime     :: TimeSpec,
  _startTimeReal :: TimeSpec,
  _h             :: Sound.ALSA.Sequencer.T Sound.ALSA.Sequencer.DuplexMode,
  _public        :: Sound.ALSA.Sequencer.Port.T,
  _private       :: Sound.ALSA.Sequencer.Port.T,
  _q             :: Sound.ALSA.Sequencer.Queue.T,
  _publicAddr    :: Sound.ALSA.Sequencer.Address.T,
  _privateAddr   :: Sound.ALSA.Sequencer.Address.T,
  _doSave        :: Bool,
  _printChordKeys :: Bool,
  _lineReader    :: MVar String
}

getAbsTime :: MidiController TimeSpec
getAbsTime = do
  startTime <- asks _startTime
  startTimeReal <- asks _startTimeReal
  now <- liftIO $ getTime Monotonic
  return $ now - startTime + startTimeReal

createTable :: Query
createTable = fromString . concat $
  [ "CREATE TABLE IF NOT EXISTS axis_input"
  , " (id INTEGER PRIMARY KEY,"
  , " start_sec INTEGER,"
  , " start_nsec INTEGER,"
  , " end_sec INTEGER,"
  , " end_nsec INTEGER,"
  , " first_sec INTEGER,"
  , " first_nsec INTEGER,"
  , " last_sec INTEGER,"
  , " last_nsec INTEGER,"
  , " midi BLOB)"
  ]

sqlInsert :: Query
sqlInsert = fromString . concat $
  [ "INSERT INTO axis_input "
  , "(start_sec,"
  , " start_nsec,"
  , " end_sec,"
  , " end_nsec,"
  , " first_sec,"
  , " first_nsec,"
  , " last_sec,"
  , " last_nsec,"
  , " midi)"
  , "VALUES (?,?,?,?, ?,?,?,?, ?)"
  ]

_sqlSelectRECENT :: MidiController [CompleteRecording]
_sqlSelectRECENT = do
  conn <- asks _sqlite
  fmap reverse $ liftIO $ query_ conn $ fromString . concat $
    [ "SELECT "
    , "start_sec,"
    , "start_nsec,"
    , "end_sec,"
    , "end_nsec,"
    , "first_sec,"
    , "first_nsec,"
    , "last_sec,"
    , "last_nsec,"
    , "midi"
    , " FROM axis_input"
    , " ORDER BY start_sec DESC, start_nsec DESC "
    , " LIMIT 10"
    ]

sqlSelectEVERYTHING :: MidiController [CompleteRecording]
sqlSelectEVERYTHING = do
  conn <- asks _sqlite
  liftIO $ query_ conn $ fromString . concat $
    [ "SELECT "
    , "start_sec,"
    , "start_nsec,"
    , "end_sec,"
    , "end_nsec,"
    , "first_sec,"
    , "first_nsec,"
    , "last_sec,"
    , "last_nsec,"
    , "midi"
    , " FROM axis_input ORDER BY start_sec, start_nsec;"
    ]

main' :: IO ()
main' = withAlsaInit $ \h public private q publicAddr privateAddr -> do
  cmdlineAlsaConnect h public

  startTime <- getTime Monotonic
  startTimeReal <- getTime Realtime

  sqlite <- open "test.db"
  execute_ sqlite createTable
  saver <- startSaver sqlite
  lineReader <- startLineReader

  doSave <- isNothing <$> lookupEnv "NO_SAVE_MIDI"

  let env = LoopEnv saver sqlite startTime startTimeReal h public private q publicAddr privateAddr doSave False lineReader

  void shutUp
  putStrLn "Rock on!"
  (_, ()) <- execRWST mainLoop env $ initializeState startTimeReal
  return ()

mainLoop :: MidiController ()
mainLoop = do
  tick <- getAbsTime
  modify $ \s -> s { _lastTick = tick }

  maybeReadLine >>= maybe processMidi processCommand
  wantExit <- gets _wantExit
  metronome
  playScheduled

  if wantExit
    then waitThreads
    else delay >> mainLoop

  where
    tickDurationMilliseconds = 4

    tickDuration = TimeSpec 0 (tickDurationMilliseconds * 10^(6::Int64))
    delay = do
      before <- gets _lastTick
      liftIO performMinorGC
      after <- getAbsTime
      let duration = tickDuration - (after - before)
      if duration > 0 then
        liftIO $ threadDelay $ fromIntegral (nsec duration) `div` 1000
      else
        liftIO $ putStrLn "Uh oh!  Dropped frame!"
      mainLoop

waitThreads :: MidiController ()
waitThreads = gets _waitThreads >>= mapM_ liftIO

metronome :: MidiController ()
metronome = gets _metronome >>= mapM_ f
  where
    f (Metronome start interval ticked) = do
      now <- getAbsTime
      let next = ticked + interval
          prequeue = 10::Int64
          intervals :: Int64 -> TimeSpec
          intervals n = interval * TimeSpec n 0 -- NB. very strange "*" for TimeSpec
      when (now > next - intervals prequeue) $ do
        let delay = next - now
        forM_ [0..prequeue] $ \n -> alsaDelayNoteEv (delay + intervals n) (metronote 127)
        modify $ \s -> s { _metronome = Just $ Metronome start interval (next + intervals prequeue) }

    metronote vel = Event.NoteEv Event.NoteOn $ Event.simpleNote (Event.Channel 9) (Event.Pitch 37) (Event.Velocity vel)

tsMod :: forall a. Num a => TimeSpec -> TimeSpec -> a
tsMod x y = fromInteger (timeSpecAsNanoSecs x `mod` timeSpecAsNanoSecs y)

tsDiv :: forall a. Num a => TimeSpec -> TimeSpec -> a
tsDiv x y = fromInteger (timeSpecAsNanoSecs x `div` timeSpecAsNanoSecs y)

playScheduled :: MidiController ()
playScheduled = queueAction $ runScheduledIO (TimeSpec 1 0) $ uncurry alsaDelayNoteEv
-- TODO: flush ALSA output here (and remove flush from playNoteEv)

_playNote :: Bool -> Event.Note -> MidiController ()
_playNote noteOn note =
  playNoteEv $ Event.NoteEv onoff note
  where onoff = if noteOn then Event.NoteOn else Event.NoteOff

delayEvent :: Event.T -> TimeSpec -> Event.T
delayEvent evt ts = evt {Event.time = AlsaTime.consRel $ AlsaTime.Real (AlsaRealTime.fromInteger nanosecs)}
  where nanosecs = timeSpecAsNanoSecs ts

playNoteEv :: Event.Data -> MidiController ()
playNoteEv = alsaDelayNoteEv (TimeSpec 0 0)

alsaDelayNoteEv :: TimeSpec -> Event.Data -> MidiController ()
alsaDelayNoteEv delay nevdata = do
  ms <- getMidiSender
  publicAddr <- asks _publicAddr
  liftIO $ ms $ Event.simple publicAddr nevdata `delayEvent` delay'
  where delay' = max 0 delay


queueAction :: (Queue Event.Data -> MidiController (Queue Event.Data)) -> MidiController ()
queueAction act = do
    q <- gets _scheduled
    act q >>= \q' -> modify $ \s -> s { _scheduled = q' }

delayNoteEv :: TimeSpec -> Event.Data -> MidiController ()
delayNoteEv delay nevdata = queueAction $ scheduleEventIO (delay, nevdata)

whenFlag :: MonadReader r m => (r -> Bool) -> m () -> m ()
whenFlag flag f = asks flag >>= flip when f

mkNote :: Word8 -> Event.Note
mkNote pitch = Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) (Event.Velocity 127)

chooseFileName :: Recording -> MidiController FilePath
chooseFileName r = do
  let startTime = earliestEvent r
  zonedTime <- liftIO $ utcToLocalZonedTime $ timeSpecAsUTCTime startTime
  return $ formatTime defaultTimeLocale "%Y-%m-%d %H:%M:%S%Q %Z%z.mid" zonedTime

timeSpecAsUTCTime :: TimeSpec -> UTCTime
timeSpecAsUTCTime = posixSecondsToUTCTime . fromRational . toRational . picosecondsToDiffTime . (* 1000) . timeSpecAsNanoSecs

processCommand :: String -> MidiController ()
processCommand "exit" = modify $ \s -> s { _wantExit = True }
-- processCommand "" = return ()
processCommand "" = gets _replay >>= playRecording
processCommand "save" = do
  recording <- gets _replay
  filename <- chooseFileName recording
  saveRecording filename recording
processCommand "dump" = sqlSelectEVERYTHING >>= saveRecording "dumped.mid" . mconcat
processCommand "C" = do
  let notes = (Event.NoteEv Event.NoteOn . mkNote) <$> [60, 64, 67]
  forM_ notes (delayNoteEv (TimeSpec 0 0))
processCommand "M-t" = gets _triadRecording >>= \case
  TriadNotRecording -> do
    liftIO $ putStrLn "Recording triad"
    modify $ \s -> s { _triadRecording = AwaitingTriad }
  _ -> do
    liftIO $ putStrLn "Cancelled ecording triad"
    modify $ \s -> s { _triadRecording = TriadNotRecording }
processCommand "M-m" = do
  now <- getAbsTime
  m <- gets _metronome
  times <- takeNoteTimes 8 <$> gets _replay
  let deltas = drop 1 . map negate . toDeltas $ times
      deltas' = dropOutliers deltas
      len = length deltas'
      dropOutliers xs@(x:_) = takeWhile (< TimeSpec 2 0 * x) xs
      dropOutliers [] = []
  if isNothing m && (len >= 3) then do
    let interval = sum deltas' `tsDiv` fromIntegral len
        nextBeat = now - now `tsMod` interval + interval
        lastBeat = nextBeat - interval
    modify $ \s -> s { _metronome = Just $ Metronome lastBeat interval nextBeat }
  else
    modify $ \s -> s { _metronome = Nothing }
processCommand "C'" = do
  let notes = (Event.NoteEv Event.NoteOn . mkNote) <$> [60, 64, 67]
  forM_ notes (delayNoteEv (TimeSpec 2 0))
{-
processCommand "C'" = do
  -- changing the duration seems to do nothing
  let mkNote pitch = Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) (Event.Velocity 127)
      setDuration d note = note { Event.noteDuration = Event.Duration d }
  let notes = (Event.NoteEv Event.NoteOn . setDuration 4290000000 . mkNote) <$> [60, 64, 67]
  forM_ notes (delayNoteEv (TimeSpec 0 0))
-}
processCommand str = liftIO $ putStrLn $ "Unknown command: " ++ str

type MidiControllerT m = RWST LoopEnv () LoopState m
type MidiController = MidiControllerT IO

takeNoteTimes :: Playable p => Int -> p -> [TimeSpec]
takeNoteTimes n p = fst <$> take n (filter (isNoteReallyOn . snd) (playableEvents p))

isNoteReallyOn :: Codec.Midi.Message -> Bool
isNoteReallyOn (Codec.Midi.NoteOn _ _ v) | v > 0 = True
isNoteReallyOn _ = False

playRecording :: Playable p => p -> MidiController ()
playRecording = playEvents . playableEvents

saveRecording :: Playable p => FilePath -> p -> MidiController ()
saveRecording file = saveEvents file . playableEvents

fixedOutputChannel :: Maybe Codec.Midi.Channel
fixedOutputChannel = Just 0

setOutputChannel :: Codec.Midi.Message -> Codec.Midi.Message
setOutputChannel = case fixedOutputChannel of Just n -> setChannel n
                                              Nothing -> id

backgroundWithWait :: IO () -> MidiController ()
backgroundWithWait fn = do
  (_, wait) <- liftIO $ Thread.forkIO fn
  modify $ \s -> s { _waitThreads = wait:_waitThreads s }

saveEvents :: FilePath -> [RecordedEvent] -> MidiController ()
saveEvents file evts@(_:_) = backgroundWithWait $ do
  Codec.Midi.exportFile file (toSingleTrackMidi evts)
  liftIO $ putStrLn $ "Saved to " ++ file
saveEvents _ _ = return ()

-- NOTE: The list must be in ascending order for this to work
-- TODO: Check that it is, and use 'last xs' if not.
dropLeadingSilence :: [RecordedEvent] -> [RecordedEvent]
dropLeadingSilence [] = []
dropLeadingSilence xs@(x:_) = map (first (subtract (fst x))) xs

toSingleTrackMidi :: [RecordedEvent] -> Midi
toSingleTrackMidi evts = midi
  where
    midi = Midi MultiTrack (TicksPerBeat $ fromIntegral ticksPerBeat) [track ++ [(0, Codec.Midi.TrackEnd)]]
    track = zip (toDeltas $ map conv delays) events
    (delays, events) = unzip $ fmap setOutputChannel <$> dropLeadingSilence (reverse evts) -- TODO: do not use fixed channel
    conv :: TimeSpec -> Int
    conv = fromIntegral . (`div` (10^(9::Int) `div` ticksPerSecond)) . timeSpecAsNanoSecs
    ticksPerSecond = ticksPerBeat * beatsPerSecond
    beatsPerSecond = 120 `div` 60
    ticksPerBeat :: Integer
    ticksPerBeat = 500          -- 1ms resolution.  See git blame.

playEvents :: [RecordedEvent] -> MidiController ()
playEvents evts@(_:_) =
  mapM_ (uncurry delayNoteEv) $ unConvertEvents $ fmap setOutputChannel <$> dropLeadingSilence (reverse evts)
    -- TODO: do not use fixed channel
playEvents  _ = return ()

getMidiSender :: MidiController MidiHook
getMidiSender = do
  h          <- asks _h
  q          <- asks _q
  publicAddr <- asks _publicAddr
  return $ forwardNoteEvent h q publicAddr

processMidi :: MidiController ()
processMidi = do
  h <- asks _h
  oldKeys <- gets _keysDown
  forwardNOW <- getMidiSender
  (events, newKeys) <- liftIO $ parseAlsaEvents'' h oldKeys (const $ return ())

  when (oldKeys /= newKeys) $ do
    now <- gets _lastTick
    let newEvents = map ((,) now . Event.body) events

    modify $ \s -> s { _keysDown = newKeys, _recording = recordEvents (_recording s) newEvents }

    whenFlag _printChordKeys $ liftIO $ printChordLn' newKeys

    let sendKeys = liftIO (mapM_ forwardNOW events)

    triadRecording <- gets _triadRecording
    case triadRecording of
      TriadNotRecording -> filterTriads newKeys >>= bool sendKeys (return ())
      AwaitingTriad -> do
        let detected = snd <$> listToMaybe (detectTriads newKeys)
        forM_ detected $ \t@(Triad _ p _) ->
              (modify $ \s -> s { _triadRecording = AwaitingRelease p (_triadType t) })
      AwaitingRelease pitch ttype -> do
        let pc = toPitchClass pitch
        when (Map.null newKeys) $
             modify $ \s -> s { _triadRecording = Recording pitch ttype, _triadMap = Map.delete (pc, ttype) (_triadMap s) }
      Recording pitch ttype -> do
        triadMap <- gets _triadMap
        let f :: Map (Event.Channel, Event.Pitch) Event.Velocity -> Set ScaleDegree
            f = Set.fromList . map (subtract (fromIntegral $ Event.unPitch pitch) . fromIntegral . Event.unPitch . snd) . Map.keys
            pc = toPitchClass pitch
            done = Map.null newKeys && not (Map.null triadMap)
        if done then do
          modify $ \s -> s { _triadRecording = TriadNotRecording }
          liftIO $ putStrLn "Recorded triad"
        else
          modify $ \s -> s { _triadMap = Map.insertWith Set.union (pc, ttype) (f newKeys) (_triadMap s) }

    -- Whenever no keys are pressed, flush any buffered events to the database
    when (Map.null newKeys) $ do
      doSave <- asks _doSave
      when doSave $ gets _recording >>= saveMidi >> return ()
      modify $ \s -> s { _recording = StartRecording now }

    -- When a key is pressed after 3+ seconds of silence, overwrite the replay buffer with the new keys
    when (Map.null oldKeys) $ do
      replay <- gets _replay
      when (latestEvent replay < (now - TimeSpec 3 0)) $ do
        modify $ \s -> s { _replay = StartRecording now }
        return ()

    modify $ \s -> s { _replay = recordEvents (_replay s) newEvents }

filterTriads :: MidiPitchMap -> MidiController Bool
filterTriads newKeys = do
  let newTriad = Set.fromList $ map snd $ detectTriads newKeys -- TODO: handle each channel
  oldTriad <- gets _triad
  when (newTriad /= oldTriad) $ do
    forM_ (Set.difference oldTriad newTriad) $ triadOff >>> sendTriadEvents
    forM_ (Set.difference newTriad oldTriad) sendTriadEvents
    modify $ \s -> s { _triad = newTriad }
  return $ not $ Set.null newTriad

triadOff :: Triad -> Triad
triadOff (Triad t p _) = Triad t p (Event.Velocity 0)

sendTriadEvents :: Triad -> MidiController ()
sendTriadEvents t@(Triad ttype (Event.Pitch base) vel) = do
  mappedNotes <- Map.lookup (tonic t, ttype) <$> gets _triadMap
  notesOn $ notes (map fromIntegral . Set.toList <$> mappedNotes)

  where
    notesOn n = forM_ n (delayNoteEv (TimeSpec 0 0))
    notes :: Maybe [Word8] -> [Event.Data]
    notes mappedNotes = fromVel vel <$> map (base +) (fromMaybe [0, third, 7, 12, -12, 7+12, 7-12] mappedNotes)
    third = if ttype == Major then 4 else 3
    fromVel (Event.Velocity 0) pitch = Event.NoteEv Event.NoteOff $ Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) (Event.Velocity 0)
    fromVel v pitch = Event.NoteEv Event.NoteOn $ Event.simpleNote (Event.Channel 0) (Event.Pitch pitch) v

detectTriads :: MidiPitchMap -> [(Event.Channel, Triad)]
detectTriads pitches = concatMap f (Map.keys pitches)
  where
    f pitch = do
      let [first_, minor3, major3, fifth_] = map (getVelocity . getNote) [0, 3, 4, 7]
          major = sumM [first_, major3, fifth_]
          minor = sumM [first_, minor3, fifth_]
          getNote n = Map.lookup (addPitch n pitch) pitches
      case (major, minor) of
        (Just n, _) -> [(fst pitch, Triad Major (snd pitch) (Event.Velocity $ fromIntegral $ n `div` 3))]
        (_, Just n) -> [(fst pitch, Triad Minor (snd pitch) (Event.Velocity $ fromIntegral $ n `div` 3))]
        _ -> []
    addPitch :: Word8 -> (t, Event.Pitch) -> (t, Event.Pitch)
    addPitch n = fmap (Event.Pitch . (+ n) . Event.unPitch)
    getVelocity :: Maybe Event.Velocity -> Maybe Int
    getVelocity = fmap (fromIntegral . Event.unVelocity)

sumM :: (Monad m, Num a, Foldable t) => t (m a) -> m a
sumM = foldM (fmap . (+)) 0

earliestEvent :: Recording -> TimeSpec
earliestEvent (StartRecording x) = x
earliestEvent (RecordingInProgress _ x _) = x

latestEvent :: Recording -> TimeSpec
latestEvent (StartRecording x) = x
latestEvent (RecordingInProgress _ x []) = x
latestEvent (RecordingInProgress _ _ ((x,_):_)) = x

maybeReadLine :: MidiController (Maybe String)
maybeReadLine = asks _lineReader >>= liftIO . tryTakeMVar

startLineReader :: IO (MVar String)
startLineReader = do
  mv <- liftIO newEmptyMVar
  hSetBuffering stdin NoBuffering
  _thread <- liftIO $ forkIO (forever $ tryIOError getChLine >>= either (const $ putMVar mv "exit") (putMVar mv))
  return mv

getChLine :: IO String
getChLine = getChar >>= f ""
    where
      f acc '\n'          = return $ reverse acc
      f _ '\ESC'          = (("M-" ++) . unControlCheck) <$> getChar
      f "" '\^D'          = return "exit"
      f _ c | isControl c = return $ unControl c
      f acc c             = getChar >>= f (c:acc)
      unControl           = ("C-" ++) . return . chr . (+ (ord 'a' - 1)) . ord
      unControlCheck c | isControl c = unControl c
                       | otherwise = return c

saveMidi :: forall (m :: * -> *). (MonadIO m, MonadState LoopState m, MonadReader LoopEnv m) => Recording -> m ()
saveMidi recording = do
  saver <- asks _saver
  now <- gets _lastTick
  mapM_ (liftIO . writeChan saver) $ stopRecording recording now

startSaver :: forall (m :: * -> *). MonadIO m => Connection -> m (Chan CompleteRecording)
startSaver sqlite = do
  chan <- liftIO newChan
  _thread <- liftIO $ forkIO (saver chan)
  return chan
  where
    saver chan = forever $ do
      reco <- readChan chan
      liftIO $ execute sqlite sqlInsert reco
      return ()