{-# LANGUAGE TupleSections #-} -- | Bind media keys for Spotify using @dbus@. module XMonad.Util.Spotify ( -- * default keybindings mediaKeys -- * media control in the 'X' monad , audioPrev , audioNext , audioPlayPause ) where import Control.Arrow (first) import Control.Monad.IO.Class import qualified Data.Map as M import DBus import DBus.Client import Graphics.X11.ExtraTypes.XF86 import Graphics.X11.Types -- | Given your keymaps, add the media keybindings. Currently they are set up -- for Spotify. mediaKeys :: MonadIO m => M.Map (KeyMask, KeySym) (m ()) -> M.Map (KeyMask, KeySym) (m ()) mediaKeys = M.union mediaKeyMap where mediaKeyMap = M.fromList mediaKeyList mediaKeyList :: MonadIO m => [((KeyMask, KeySym), m ())] mediaKeyList = go <$> [ (xF86XK_AudioNext, audioNext) , (xF86XK_AudioPrev, audioPrev) , (xF86XK_AudioPlay, audioPlayPause) ] where go = first (0 ,) spIO :: String -> IO () spIO str = do client <- connectSession _ <- call_ client (methodCall (objectPath_ "/org/mpris/MediaPlayer2") (interfaceName_ "org.mpris.MediaPlayer2.Player") (memberName_ str)) { methodCallDestination = Just (busName_ "org.mpris.MediaPlayer2.spotify") } disconnect client -- | Helper function for use with dbus sp :: MonadIO m => String -> m () sp = liftIO . spIO -- | Action in the 'X' monad to go to next audioNext :: MonadIO m => m () audioNext = sp "Next" -- | Action in the 'X' monad to go the previous audioPrev :: MonadIO m => m () audioPrev = sp "Previous" -- | Action in the 'X' monad to play/pause audioPlayPause :: MonadIO m => m () audioPlayPause = sp "PlayPause"