{-# LANGUAGE OverloadedStrings #-} module Xmobar.Plugins.Common ( colorText , startListener , procSignalMatch , na , fromSingletonVariant , withDBusClientConnection , Callback , Colors (..) , displayMaybe , displayMaybe' , xmobarFGColor ) where import DBus import DBus.Client import Data.Internal.DBus import RIO import qualified RIO.Text as T import XMonad.Hooks.DynamicLog (xmobarColor) -- use string here since all the callbacks in xmobar use strings :( type Callback = String -> IO () data Colors = Colors { colorsOn :: T.Text , colorsOff :: T.Text } deriving (Eq, Show, Read) startListener :: (MonadUnliftIO m, SafeClient c, IsVariant a) => MatchRule -> (c -> m [Variant]) -> ([Variant] -> SignalMatch a) -> (a -> m T.Text) -> Callback -> c -> m () startListener rule getProp fromSignal toColor cb client = do reply <- getProp client displayMaybe cb toColor $ fromSingletonVariant reply void $ addMatchCallback rule (procMatch . fromSignal) client where procMatch = procSignalMatch cb toColor procSignalMatch :: MonadUnliftIO m => Callback -> (a -> m T.Text) -> SignalMatch a -> m () procSignalMatch cb f = withSignalMatch (displayMaybe cb f) colorText :: Colors -> Bool -> T.Text -> T.Text colorText Colors {colorsOn = c} True = xmobarFGColor c colorText Colors {colorsOff = c} False = xmobarFGColor c xmobarFGColor :: T.Text -> T.Text -> T.Text xmobarFGColor c = T.pack . xmobarColor (T.unpack c) "" . T.unpack na :: T.Text na = "N/A" displayMaybe :: MonadUnliftIO m => Callback -> (a -> m T.Text) -> Maybe a -> m () displayMaybe cb f = (liftIO . cb . T.unpack) <=< maybe (return na) f displayMaybe' :: MonadUnliftIO m => Callback -> (a -> m ()) -> Maybe a -> m () displayMaybe' cb = maybe (liftIO $ cb $ T.unpack na) withDBusClientConnection :: (MonadUnliftIO m, SafeClient c) => Callback -> Utf8Builder -> (c -> RIO SimpleApp ()) -> m () withDBusClientConnection cb name f = do logOpts <- setLogVerboseFormat True . setLogUseTime True . setLogFormat pre <$> logOptionsHandle stderr False withLogFunc logOpts $ \lf -> do env <- mkSimpleApp lf Nothing runRIO env $ displayMaybe' cb f =<< getDBusClient where pre rest = "[" <> name <> " plugin] " <> rest