-- Copyright 2013 Evan Laforge
-- This program is distributed under the terms of the GNU General Public
-- License 3.0, see COPYING or http://www.gnu.org/licenses/gpl-3.0.txt

-- | MMC is a MIDI standard for synchronizing with recording devices and DAWs
-- and whatever else chooses to support it.  Ultimately MMC is just a bunch of
-- specially formatted SystemExclusive msgs.
module Midi.Mmc where
import qualified Data.ByteString as B
import Data.Word (Word8)

import qualified Midi.Midi as Midi


-- | There are more, but I only support the ones I use.
data Mmc = Stop | Play | FastForward | Rewind | Pause
    | Goto !Midi.Smpte !SubFrames -- aka Locate
    deriving (Mmc -> Mmc -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mmc -> Mmc -> Bool
$c/= :: Mmc -> Mmc -> Bool
== :: Mmc -> Mmc -> Bool
$c== :: Mmc -> Mmc -> Bool
Eq, Int -> Mmc -> ShowS
[Mmc] -> ShowS
Mmc -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mmc] -> ShowS
$cshowList :: [Mmc] -> ShowS
show :: Mmc -> String
$cshow :: Mmc -> String
showsPrec :: Int -> Mmc -> ShowS
$cshowsPrec :: Int -> Mmc -> ShowS
Show)

-- TODO how many subframes per frame?
goto_seconds :: Midi.FrameRate -> Double -> Mmc
goto_seconds :: FrameRate -> Double -> Mmc
goto_seconds FrameRate
rate Double
secs = Smpte -> Word8 -> Mmc
Goto (FrameRate -> Double -> Smpte
Midi.seconds_to_smpte FrameRate
rate Double
secs) Word8
0

-- | This is just an arbitrary number that evidentally selects which device
-- should pay attention to the msg.  0x7f sometimes means all devices.
type DeviceId = Word8
type SubFrames = Word8

-- | Encode an Mmc msg into a SystemExclusive.
encode :: DeviceId -> Mmc -> Midi.Message
encode :: Word8 -> Mmc -> Message
encode Word8
device_id Mmc
msg =
    CommonMessage -> Message
Midi.CommonMessage forall a b. (a -> b) -> a -> b
$ Word8 -> ByteString -> CommonMessage
Midi.SystemExclusive Word8
0x7f forall a b. (a -> b) -> a -> b
$
        [Word8] -> ByteString
B.pack [Word8
device_id, Word8
0x06] forall a. Semigroup a => a -> a -> a
<> Mmc -> ByteString
encode_msg Mmc
msg

encode_msg :: Mmc -> B.ByteString
encode_msg :: Mmc -> ByteString
encode_msg Mmc
mmc = [Word8] -> ByteString
B.pack forall a b. (a -> b) -> a -> b
$ case Mmc
mmc of
    Mmc
Stop -> [Word8
0x1]
    Mmc
Play -> [Word8
0x2]
    Mmc
FastForward -> [Word8
0x4]
    Mmc
Rewind -> [Word8
0x5]
    Mmc
Pause -> [Word8
0x9]
    Goto (Midi.Smpte Word8
hours Word8
mins Word8
secs Word8
frames) Word8
subframes ->
        [Word8
0x44, Word8
0x06, Word8
0x01, Word8
hours, Word8
mins, Word8
secs, Word8
frames, Word8
subframes]