{-# LANGUAGE OverloadedStrings #-} -------------------------------------------------------------------------------- -- Bluetooth plugin -- -- Use the bluez interface on DBus to check status -- -- org.bluez dynamically updates its DBus interfaces using the standard Object -- Manager. The adapter is located at path "/org/bluez/hci" where X is -- usually 0, and each device is "/org/bluez/hci/". -- -- This plugin will reflect if the adapter is powered and if any device is -- connected to it. The rough outline for this procedure: -- 1) get the adapter from the object manager -- 2) get all devices associated with the adapter using the object interface -- 3) determine if the adapter is powered -- 4) determine if any devices are connected -- 5) format the icon; powered vs not powered controls the color and connected -- vs not connected controls the icon (connected bluetooth symbol has two -- dots flanking it) -- -- Step 3 can be accomplished using the "org.bluez.Adapter1" interface and -- querying the "Powered" property. Step 4 can be done using the -- "org.bluez.Device1" interface and the "Connected" property for each device -- path. Since these are properties, we can asynchronously read changes to them -- via the "PropertiesChanged" signal. -- -- If any devices are added/removed, steps 2-4 will need to be redone and any -- listeners will need to be updated. (TODO not sure which signals to use in -- determining if a device is added) -- -- TODO also not sure if I need to care about multiple adapters and/or the -- adapter changing. module Xmobar.Plugins.Bluetooth ( Bluetooth (..) , btAlias , btDep ) where import DBus import DBus.Client import Data.Internal.DBus import Data.Internal.XIO import RIO import RIO.FilePath import RIO.List import qualified RIO.Map as M import qualified RIO.Text as T import XMonad.Internal.DBus.Common import Xmobar import Xmobar.Plugins.Common btAlias :: T.Text btAlias = "bluetooth" btDep :: DBusDependency_ SysClient btDep = Endpoint [Package Official "bluez"] btBus btOMPath omInterface $ Method_ getManagedObjects data Bluetooth = Bluetooth Icons Colors deriving (Read, Show) instance Exec Bluetooth where alias (Bluetooth _ _) = T.unpack btAlias start (Bluetooth icons colors) cb = withDBusClientConnection cb "bluetooth" $ startAdapter icons colors cb startAdapter :: Icons -> Colors -> Callback -> SysClient -> RIO SimpleApp () startAdapter is cs cb cl = do state <- newMVar emptyState let dpy = displayIcon cb (iconFormatter is cs) mapRIO (wrap state) $ do ot <- getBtObjectTree cl -- TODO if this fails it won't be logged forM_ (findAdapter ot) $ \adapter -> do -- set up adapter initAdapter adapter cl void $ addAdaptorListener dpy adapter cl -- set up devices on the adapter (and listeners for adding/removing devices) let devices = findDevices adapter ot addDeviceAddedListener dpy adapter cl addDeviceRemovedListener dpy adapter cl forM_ devices $ \d -> addAndInitDevice dpy d cl -- after setting things up, show the icon based on the initialized state dpy where wrap s env = BTEnv {btEnv = env, btState = s} -------------------------------------------------------------------------------- -- Icon Display -- -- Color corresponds to the adaptor powered state, and the icon corresponds to -- if it is paired or not. If the adaptor state is undefined, display "N/A" type IconFormatter = (Maybe Bool -> Bool -> T.Text) type Icons = (T.Text, T.Text) displayIcon :: Callback -> IconFormatter -> BTIO () displayIcon callback formatter = liftIO . callback . T.unpack . uncurry formatter =<< readState -- TODO maybe I want this to fail when any of the device statuses are Nothing iconFormatter :: Icons -> Colors -> IconFormatter iconFormatter (iconConn, iconDisc) cs powered connected = maybe na (\p -> colorText cs p icon) powered where icon = if connected then iconConn else iconDisc -------------------------------------------------------------------------------- -- Connection State -- -- The signal handlers all run on separate threads, yet the icon depends on -- the state reflected by all these signals. The best (only?) way to do this is -- is to track the shared state of the bluetooth adaptor and its devices using -- an MVar. data BTEnv = BTEnv { btEnv :: !SimpleApp , btState :: !(MVar BtState) } instance HasLogFunc BTEnv where logFuncL = lens btEnv (\x y -> x {btEnv = y}) . logFuncL type BTIO = RIO BTEnv data BTDevice = BTDevice { btDevConnected :: Maybe Bool , btDevSigHandler :: SignalHandler } type ConnectedDevices = M.Map ObjectPath BTDevice data BtState = BtState { btDevices :: ConnectedDevices , btPowered :: Maybe Bool } emptyState :: BtState emptyState = BtState { btDevices = M.empty , btPowered = Nothing } readState :: BTIO (Maybe Bool, Bool) readState = do p <- readPowered c <- readDevices return (p, anyDevicesConnected c) -------------------------------------------------------------------------------- -- Object manager findAdapter :: ObjectTree -> Maybe ObjectPath findAdapter = find (("/org/bluez/hci" `isPrefixOf`) . formatObjectPath) . M.keys findDevices :: ObjectPath -> ObjectTree -> [ObjectPath] findDevices adapter = filter (adaptorHasDevice adapter) . M.keys adaptorHasDevice :: ObjectPath -> ObjectPath -> Bool adaptorHasDevice adaptor device = case splitPathNoRoot device of [org, bluez, hciX, _] -> splitPathNoRoot adaptor == [org, bluez, hciX] _ -> False splitPathNoRoot :: ObjectPath -> [FilePath] splitPathNoRoot = dropWhile (== "/") . splitDirectories . formatObjectPath getBtObjectTree :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) => SysClient -> m ObjectTree getBtObjectTree sys = callGetManagedObjects sys btBus btOMPath btOMPath :: ObjectPath btOMPath = objectPath_ "/" addBtOMListener :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) => SignalCallback m -> SysClient -> m () addBtOMListener sc = void . addInterfaceAddedListener btBus btOMPath sc addDeviceAddedListener :: BTIO () -> ObjectPath -> SysClient -> BTIO () addDeviceAddedListener dpy adapter client = addBtOMListener addDevice client where addDevice = pathCallback adapter dpy $ \d -> addAndInitDevice dpy d client addDeviceRemovedListener :: BTIO () -> ObjectPath -> SysClient -> BTIO () addDeviceRemovedListener dpy adapter sys = addBtOMListener remDevice sys where remDevice = pathCallback adapter dpy $ \d -> do old <- removeDevice d forM_ old $ liftIO . removeMatch (toClient sys) . btDevSigHandler pathCallback :: MonadUnliftIO m => ObjectPath -> m () -> (ObjectPath -> m ()) -> SignalCallback m pathCallback adapter dpy f [device, _] = forM_ (fromVariant device) $ \d -> when (adaptorHasDevice adapter d) $ f d >> dpy pathCallback _ _ _ _ = return () -------------------------------------------------------------------------------- -- Adapter initAdapter :: ObjectPath -> SysClient -> BTIO () initAdapter adapter client = do reply <- callGetPowered adapter client logInfo $ "initializing adapter at path " <> adapter_ -- TODO this could fail if the variant is something weird; the only -- indication I will get is "NA" putPowered $ fromSingletonVariant reply where adapter_ = displayWrapQuote $ displayObjectPath adapter matchBTProperty :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) => SysClient -> ObjectPath -> m (Maybe MatchRule) matchBTProperty sys p = matchPropertyFull sys btBus (Just p) withBTPropertyRule :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m, IsVariant a) => SysClient -> ObjectPath -> (Maybe a -> m ()) -> InterfaceName -> T.Text -> m (Maybe SignalHandler) withBTPropertyRule cl path update iface prop = do res <- matchBTProperty cl path case res of Just rule -> Just <$> addMatchCallback rule (signalToUpdate . matchConnected) cl Nothing -> do logError $ "could not add listener for prop " <> prop_ <> " on path " <> path_ return Nothing where path_ = displayObjectPath path prop_ = Utf8Builder $ encodeUtf8Builder prop signalToUpdate = withSignalMatch update matchConnected = matchPropertyChanged iface prop addAdaptorListener :: BTIO () -> ObjectPath -> SysClient -> BTIO (Maybe SignalHandler) addAdaptorListener dpy adaptor sys = do withBTPropertyRule sys adaptor procMatch adapterInterface adaptorPowered where procMatch b = putPowered b >> dpy callGetPowered :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) => ObjectPath -> SysClient -> m [Variant] callGetPowered adapter = callPropertyGet btBus adapter adapterInterface $ memberName_ $ T.unpack adaptorPowered putPowered :: Maybe Bool -> BTIO () putPowered ds = do m <- asks btState modifyMVar_ m (\s -> return s {btPowered = ds}) readPowered :: BTIO (Maybe Bool) readPowered = fmap btPowered $ readMVar =<< asks btState adapterInterface :: InterfaceName adapterInterface = interfaceName_ "org.bluez.Adapter1" adaptorPowered :: T.Text adaptorPowered = "Powered" -------------------------------------------------------------------------------- -- Devices addAndInitDevice :: BTIO () -> ObjectPath -> SysClient -> BTIO () addAndInitDevice dpy device client = do res <- addDeviceListener dpy device client case res of Just handler -> do logInfo $ "initializing device at path " <> device_ initDevice handler device client Nothing -> logError $ "could not initialize device at path " <> device_ where device_ = displayWrapQuote $ displayObjectPath device initDevice :: SignalHandler -> ObjectPath -> SysClient -> BTIO () initDevice sh device sys = do reply <- callGetConnected device sys void $ insertDevice device $ BTDevice { btDevConnected = fromVariant =<< listToMaybe reply , btDevSigHandler = sh } addDeviceListener :: BTIO () -> ObjectPath -> SysClient -> BTIO (Maybe SignalHandler) addDeviceListener dpy device sys = do withBTPropertyRule sys device procMatch devInterface devConnected where procMatch c = updateDevice device c >> dpy callGetConnected :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) => ObjectPath -> SysClient -> m [Variant] callGetConnected p = callPropertyGet btBus p devInterface $ memberName_ (T.unpack devConnected) insertDevice :: ObjectPath -> BTDevice -> BTIO Bool insertDevice device dev = do m <- asks btState modifyMVar m $ \s -> do let new = M.insert device dev $ btDevices s return (s {btDevices = new}, anyDevicesConnected new) updateDevice :: ObjectPath -> Maybe Bool -> BTIO Bool updateDevice device status = do m <- asks btState modifyMVar m $ \s -> do let new = M.update (\d -> Just d {btDevConnected = status}) device $ btDevices s return (s {btDevices = new}, anyDevicesConnected new) anyDevicesConnected :: ConnectedDevices -> Bool anyDevicesConnected = or . mapMaybe btDevConnected . M.elems removeDevice :: ObjectPath -> BTIO (Maybe BTDevice) removeDevice device = do m <- asks btState modifyMVar m $ \s -> do let devs = btDevices s return (s {btDevices = M.delete device devs}, M.lookup device devs) readDevices :: BTIO ConnectedDevices readDevices = fmap btDevices $ readMVar =<< asks btState devInterface :: InterfaceName devInterface = interfaceName_ "org.bluez.Device1" devConnected :: T.Text devConnected = "Connected"