module System.MIDI.Launchpad.AppFramework
(
red , green , amber , yellow , orange
, PureApp(..)
, runPureApp
, MonadicApp(..) , runMonadicApp
, RenderMonad , ButtonMonad , SyncMonad
, setButtonColor , setButtonColor' , setButtonColors
, getMode , setMode
, CanChangeState , setState , getState , modifyState
, CanSendMessage , sendMessage , sendMessages
, GlobalConfig(..) , defaultGlobalConfig
)
where
import Control.Monad
import System.MIDI
import System.MIDI.Utility
import Control.Concurrent
import Control.Concurrent.MVar ()
import Control.Monad.Trans
import Control.Monad.Identity
import Control.Monad.Writer
import Control.Monad.State
import System.IO.Unsafe as Unsafe
import System.MIDI.Launchpad.Control
import System.MIDI.Launchpad.AppFramework.Internal
data MonadicApp cfg mode state = MonadicApp
{ mAppConfig :: cfg
, mAppIniState :: (mode,state)
, mAppStartStop :: cfg -> Bool -> (state -> state)
, mAppRender :: cfg -> mode -> state -> Maybe Int -> RenderMonad ()
, mAppButton :: cfg -> ButtonPress -> ButtonMonad mode state ()
, mAppSync :: cfg -> mode -> Int -> SyncMonad state ()
}
newtype RenderMonad a
= RM { unRM :: WriterT [(Button,Color)] Identity a }
deriving Monad
newtype ButtonMonad mode state a
= BM { unBM :: StateT (mode,state) (WriterT [ MidiMessage' ] Identity) a }
deriving Monad
newtype SyncMonad state a
= SM { unSM :: StateT state (WriterT [ MidiMessage' ] Identity) a }
deriving Monad
setButtonColor :: (Button,Color) -> RenderMonad ()
setButtonColor bc = RM $ tell [bc]
setButtonColor' :: Button -> Color -> RenderMonad ()
setButtonColor' b c = setButtonColor (b,c)
setButtonColors :: [(Button,Color)] -> RenderMonad ()
setButtonColors bcs = RM $ tell bcs
getMode :: ButtonMonad mode state mode
getMode = BM $ do
(mode,_) <- get
return mode
setMode :: mode -> ButtonMonad mode state ()
setMode newmode = BM $ do
(_,b) <- get
put (newmode,b)
class Monad m => CanSendMessage m where
sendMessages :: [MidiMessage'] -> m ()
sendMessage :: MidiMessage' -> m ()
sendMessage msg = sendMessages [msg]
instance CanSendMessage (ButtonMonad mode state) where
sendMessages ms = BM $ lift $ tell ms
instance CanSendMessage (SyncMonad state) where
sendMessages ms = SM $ lift $ tell ms
class CanChangeState m where
getState :: Monad (m state) => m state state
setState :: Monad (m state) => state -> m state ()
modifyState :: (CanChangeState m, Monad (m state)) => (state -> state) -> m state ()
modifyState f = do
old <- getState
setState $! f old
instance CanChangeState (ButtonMonad mode) where
getState = BM $ do
(_,state) <- get
return state
setState newstate = BM $ do
(a,_) <- get
put (a,newstate)
instance CanChangeState SyncMonad where
getState = SM $ get
setState s = SM $ put $! s
monadicAppToPureApp :: MonadicApp cfg mode state -> PureApp cfg mode state
monadicAppToPureApp mApp@(MonadicApp cfg ini startstop render button sync) = pApp where
pApp = PureApp
{ pAppConfig = cfg
, pAppIniState = ini
, pAppStartStop = startstop
, pAppRender = \c m s i -> runIdentity $ execWriterT (unRM $ render c m s i)
, pAppButton = \c b ms -> runIdentity $ runWriterT (execStateT (unBM $ button c b ) ms)
, pAppSync = \c m s i -> runIdentity $ runWriterT (execStateT (unSM $ sync c m i ) s)
}
defaultGlobalConfig :: GlobalConfig
defaultGlobalConfig = GlobalConfig
{ defaultLaunchpadDevice = "Launchpad"
, defaultMidiOutputDevice = "IAC Bus 1"
, outputChannel = 1
, onlyUserMode2 = True
}
runMonadicApp :: GlobalConfig -> MonadicApp cfg mode state -> IO ()
runMonadicApp globalConfig mApp = runPureApp globalConfig (monadicAppToPureApp mApp)