Compare commits

...

30 Commits

Author SHA1 Message Date
Nathan Dwarshuis 51ebf01786 ENH use firefox 2024-07-07 10:28:24 -04:00
Nathan Dwarshuis c35be51dd4 FIX wifi password lookup fail 2024-03-30 17:58:24 -04:00
Nathan Dwarshuis 24430eaeb7 FIX typo 2024-03-17 18:33:15 -04:00
Nathan Dwarshuis 8a1345ae4b FIX make network toggles actually work 2024-03-17 11:15:03 -04:00
Nathan Dwarshuis a65cd669dc ENH replace urxvt with alacritty 2024-02-18 19:41:32 -05:00
Nathan Dwarshuis 3ab6ccf45b ENH don't ignore ethenet interfaces 2024-01-21 17:02:47 -05:00
Nathan Dwarshuis 8064b01c90 ENH move external scripts to this repo 2024-01-07 09:52:44 -05:00
Nathan Dwarshuis 80c3d33010 REF add note 2023-10-28 00:18:33 -04:00
Nathan Dwarshuis d9b1886db6 FIX actually the dbus client disconnect problem 2023-10-28 00:14:40 -04:00
Nathan Dwarshuis 841bf0b5c8 Merge branch 'fix_dbus' 2023-10-27 23:58:06 -04:00
Nathan Dwarshuis 87eee7a2b9 FIX dbus not closing callback connections 2023-10-27 23:57:40 -04:00
Nathan Dwarshuis cc5670f2f1 ENH use names for dbus connections 2023-10-27 23:12:22 -04:00
Nathan Dwarshuis 171fa489ca ENH update stack snapshot 2023-10-25 21:55:59 -04:00
Nathan Dwarshuis 78ba3173c3 WIP name dbus connections 2023-10-25 20:40:15 -04:00
Nathan Dwarshuis 58b68f298c FIX bluetooth being dumb 2023-10-15 21:50:46 -04:00
Nathan Dwarshuis 98e0a2943d ENH rejoice, F5 is dead 2023-10-01 01:06:02 -04:00
Nathan Dwarshuis 13ddeb3ba7 ENH use indiv logs for bluetooth devs 2023-10-01 01:02:06 -04:00
Nathan Dwarshuis 700f42d65c REF merge plugin environ 2023-10-01 00:24:33 -04:00
Nathan Dwarshuis 2f6eeb5cdb ENH use active connection plugin for both networkmanager and vpn connections 2023-09-30 23:52:52 -04:00
Nathan Dwarshuis f814ac9217 ENH show network connection names 2023-09-30 18:51:07 -04:00
Nathan Dwarshuis 0a4edb6bf2 FIX vpn not showing when no NM profiles exist 2023-09-30 12:22:30 -04:00
Nathan Dwarshuis 250d5c5eed ENH show VPN interface names 2023-09-29 23:44:08 -04:00
Nathan Dwarshuis 770f1dc1dd FIX icon fonts 2023-05-08 23:00:58 -04:00
Nathan Dwarshuis 09909ac779 ENH update fonts 2023-05-08 12:15:20 -04:00
Nathan Dwarshuis fe61b0192d ENH remove prelude from xio 2023-02-12 23:17:34 -05:00
Nathan Dwarshuis 96cb9298d7 ENH remove prelude from main bin 2023-02-12 23:13:46 -05:00
Nathan Dwarshuis 71e86f2233 REF update compiler flags 2023-02-12 23:08:05 -05:00
Nathan Dwarshuis 7d5a82bd07 ENH use new screenlocker 2023-01-17 22:46:22 -05:00
Nathan Dwarshuis 2712ebdf37 FIX file flushing errors 2023-01-04 23:47:21 -05:00
Nathan Dwarshuis 3cc7e02416 Merge branch 'fix_rio_run' 2023-01-04 13:55:31 -05:00
49 changed files with 993 additions and 941 deletions

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- | Start a VirtualBox instance with a sentinel wrapper process. -- | Start a VirtualBox instance with a sentinel wrapper process.
-- --
-- The only reason why this is needed is because I want to manage virtualboxes -- The only reason why this is needed is because I want to manage virtualboxes

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-- | Xmobar binary -- | Xmobar binary
-- --
-- Features: -- Features:
@ -13,14 +11,14 @@ module Main (main) where
import Data.Internal.DBus import Data.Internal.DBus
import Data.Internal.XIO import Data.Internal.XIO
import GHC.Enum (enumFrom)
import Options.Applicative import Options.Applicative
import RIO hiding (hFlush) import RIO hiding (hFlush)
import qualified RIO.ByteString.Lazy as BL import RIO.FilePath
import RIO.List import RIO.List
import RIO.Process import qualified RIO.NonEmpty as NE
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Core hiding (config) import XMonad.Core hiding (config)
import XMonad.Internal.Command.Desktop
import XMonad.Internal.Command.Power import XMonad.Internal.Command.Power
import XMonad.Internal.DBus.Brightness.ClevoKeyboard import XMonad.Internal.DBus.Brightness.ClevoKeyboard
import XMonad.Internal.DBus.Brightness.IntelBacklight import XMonad.Internal.DBus.Brightness.IntelBacklight
@ -31,13 +29,12 @@ import Xmobar hiding
( iconOffset ( iconOffset
, run , run
) )
import Xmobar.Plugins.ActiveConnection
import Xmobar.Plugins.Bluetooth import Xmobar.Plugins.Bluetooth
import Xmobar.Plugins.ClevoKeyboard import Xmobar.Plugins.ClevoKeyboard
import Xmobar.Plugins.Common import Xmobar.Plugins.Common
import Xmobar.Plugins.Device
import Xmobar.Plugins.IntelBacklight import Xmobar.Plugins.IntelBacklight
import Xmobar.Plugins.Screensaver import Xmobar.Plugins.Screensaver
import Xmobar.Plugins.VPN
main :: IO () main :: IO ()
main = parse >>= xio main = parse >>= xio
@ -67,7 +64,7 @@ parseTest =
xio :: XOpts -> IO () xio :: XOpts -> IO ()
xio o = case o of xio o = case o of
XDeps -> hRunXIO False stderr printDeps XDeps -> hRunXIO False stderr printDeps
XTest -> hRunXIO False stderr $ withDBus_ evalConfig XTest -> hRunXIO False stderr $ withDBus_ Nothing Nothing evalConfig
XRun -> runXIO "xmobar.log" run XRun -> runXIO "xmobar.log" run
run :: XIO () run :: XIO ()
@ -79,9 +76,9 @@ run = do
-- linebuffering it usually only prints the first few characters (even then -- linebuffering it usually only prints the first few characters (even then
-- it only prints 10-20% of the time) -- it only prints 10-20% of the time)
liftIO $ hSetBuffering stderr LineBuffering liftIO $ hSetBuffering stderr LineBuffering
withDBus_ $ \db -> do -- TODO do these dbus things really need to remain connected?
c <- evalConfig db c <- withDBus Nothing Nothing evalConfig
liftIO $ xmobar c liftIO $ xmobar c
evalConfig :: DBusState -> XIO Config evalConfig :: DBusState -> XIO Config
evalConfig db = do evalConfig db = do
@ -92,7 +89,7 @@ evalConfig db = do
return $ config bf ifs ios cs d return $ config bf ifs ios cs d
printDeps :: XIO () printDeps :: XIO ()
printDeps = withDBus_ $ \db -> printDeps = withDBus_ Nothing Nothing $ \db ->
mapM_ logInfo $ mapM_ logInfo $
fmap showFulfillment $ fmap showFulfillment $
sort $ sort $
@ -121,7 +118,7 @@ iconFont =
fontSometimes fontSometimes
"XMobar Icon Font" "XMobar Icon Font"
"Symbols Nerd Font" "Symbols Nerd Font"
[Package Official "ttf-nerd-fonts-symbols-2048-em"] [Package Official "ttf-nerd-fonts-symbols"]
-- | Offsets for the icons in the bar (relative to the text offset) -- | Offsets for the icons in the bar (relative to the text offset)
iconOffset :: BarFont -> Int iconOffset :: BarFont -> Int
@ -167,7 +164,7 @@ config bf ifs ios br confDir =
, pickBroadest = False , pickBroadest = False
, persistent = True , persistent = True
, -- store the icons with the xmonad/xmobar stack project , -- store the icons with the xmonad/xmobar stack project
iconRoot = confDir ++ "/icons" iconRoot = confDir </> "assets" </> "icons"
, commands = csRunnable <$> concatRegions br , commands = csRunnable <$> concatRegions br
} }
@ -222,11 +219,11 @@ getWireless =
xpfWireless xpfWireless
[Subfeature (IORoot wirelessCmd $ Only readWireless) "sysfs path"] [Subfeature (IORoot wirelessCmd $ Only readWireless) "sysfs path"]
getEthernet :: Maybe SysClient -> BarFeature getEthernet :: Maybe NamedSysConnection -> BarFeature
getEthernet cl = iconDBus "ethernet status indicator" xpfEthernet root tree getEthernet cl = iconDBus_ "ethernet status indicator" xpfEthernet root (Only_ devDep)
where where
root useIcon tree' = DBusRoot (const . ethernetCmd useIcon) tree' cl root useIcon tree' =
tree = And1 (Only readEthernet) (Only_ devDep) DBusRoot_ (const $ ethernetCmd useIcon) tree' cl
getBattery :: BarFeature getBattery :: BarFeature
getBattery = iconIO_ "battery level indicator" xpfBattery root tree getBattery = iconIO_ "battery level indicator" xpfBattery root tree
@ -238,18 +235,12 @@ getBattery = iconIO_ "battery level indicator" xpfBattery root tree
io $ io $
fmap (Msg LevelError) <$> hasBattery fmap (Msg LevelError) <$> hasBattery
getVPN :: Maybe SysClient -> BarFeature getVPN :: Maybe NamedSysConnection -> BarFeature
getVPN cl = iconDBus_ "VPN status indicator" xpfVPN root $ toAnd_ vpnDep test getVPN cl = iconDBus_ "VPN status indicator" xpfVPN root (Only_ devDep)
where where
root useIcon tree = DBusRoot_ (const $ vpnCmd useIcon) tree cl root useIcon tree = DBusRoot_ (const $ vpnCmd useIcon) tree cl
test =
DBusIO $
IOTest_
"Use nmcli to test if VPN is present"
networkManagerPkgs
vpnPresent
getBt :: Maybe SysClient -> BarFeature getBt :: Maybe NamedSysConnection -> BarFeature
getBt = xmobarDBus "bluetooth status indicator" xpfBluetooth btDep btCmd getBt = xmobarDBus "bluetooth status indicator" xpfBluetooth btDep btCmd
getAlsa :: BarFeature getAlsa :: BarFeature
@ -260,7 +251,7 @@ getAlsa =
where where
root useIcon = IORoot_ (alsaCmd useIcon) root useIcon = IORoot_ (alsaCmd useIcon)
getBl :: Maybe SesClient -> BarFeature getBl :: Maybe NamedSesConnection -> BarFeature
getBl = getBl =
xmobarDBus xmobarDBus
"Intel backlight indicator" "Intel backlight indicator"
@ -268,7 +259,7 @@ getBl =
intelBacklightSignalDep intelBacklightSignalDep
blCmd blCmd
getCk :: Maybe SesClient -> BarFeature getCk :: Maybe NamedSesConnection -> BarFeature
getCk = getCk =
xmobarDBus xmobarDBus
"Clevo keyboard indicator" "Clevo keyboard indicator"
@ -276,7 +267,7 @@ getCk =
clevoKeyboardSignalDep clevoKeyboardSignalDep
ckCmd ckCmd
getSs :: Maybe SesClient -> BarFeature getSs :: Maybe NamedSesConnection -> BarFeature
getSs = xmobarDBus "screensaver indicator" (const True) ssSignalDep ssCmd getSs = xmobarDBus "screensaver indicator" (const True) ssSignalDep ssCmd
getLock :: Always CmdSpec getLock :: Always CmdSpec
@ -293,7 +284,7 @@ xmobarDBus
-> XPQuery -> XPQuery
-> DBusDependency_ c -> DBusDependency_ c
-> (Fontifier -> CmdSpec) -> (Fontifier -> CmdSpec)
-> Maybe c -> Maybe (NamedConnection c)
-> BarFeature -> BarFeature
xmobarDBus n q dep cmd cl = iconDBus_ n q root (Only_ dep) xmobarDBus n q dep cmd cl = iconDBus_ n q root (Only_ dep)
where where
@ -307,18 +298,16 @@ iconIO_
-> BarFeature -> BarFeature
iconIO_ = iconSometimes' And_ Only_ iconIO_ = iconSometimes' And_ Only_
iconDBus -- iconDBus
:: SafeClient c -- :: T.Text
=> T.Text -- -> XPQuery
-> XPQuery -- -> (Fontifier -> DBusTree c p -> Root CmdSpec)
-> (Fontifier -> DBusTree c p -> Root CmdSpec) -- -> DBusTree c p
-> DBusTree c p -- -> BarFeature
-> BarFeature -- iconDBus = iconSometimes' And1 $ Only_ . DBusIO
iconDBus = iconSometimes' And1 $ Only_ . DBusIO
iconDBus_ iconDBus_
:: SafeClient c :: T.Text
=> T.Text
-> XPQuery -> XPQuery
-> (Fontifier -> DBusTree_ c -> Root CmdSpec) -> (Fontifier -> DBusTree_ c -> Root CmdSpec)
-> DBusTree_ c -> DBusTree_ c
@ -380,13 +369,19 @@ wirelessCmd iface =
, "<icon=wifi_%%.xpm/>" , "<icon=wifi_%%.xpm/>"
] ]
ethernetCmd :: Fontifier -> T.Text -> CmdSpec ethernetCmd :: Fontifier -> CmdSpec
ethernetCmd fontify iface = ethernetCmd = connCmd "\xf0e8" "ETH" ("vlan" :| ["802-3-ethernet"])
vpnCmd :: Fontifier -> CmdSpec
vpnCmd = connCmd "\xf023" "VPN" ("tun" :| [])
connCmd :: T.Text -> T.Text -> NE.NonEmpty T.Text -> Fontifier -> CmdSpec
connCmd icon abbr contypes fontify =
CmdSpec CmdSpec
{ csAlias = iface { csAlias = connAlias contypes
, csRunnable = , csRunnable =
Run $ Run $
Device (iface, fontify IconMedium "\xf0e8" "ETH", colors) ActiveConnection (contypes, fontify IconMedium icon abbr, colors)
} }
batteryCmd :: Fontifier -> CmdSpec batteryCmd :: Fontifier -> CmdSpec
@ -422,20 +417,13 @@ batteryCmd fontify =
, fontify' "\xf1e6" "AC" , fontify' "\xf1e6" "AC"
] ]
vpnCmd :: Fontifier -> CmdSpec
vpnCmd fontify =
CmdSpec
{ csAlias = vpnAlias
, csRunnable = Run $ VPN (fontify IconMedium "\xf023" "VPN", colors)
}
btCmd :: Fontifier -> CmdSpec btCmd :: Fontifier -> CmdSpec
btCmd fontify = btCmd fontify =
CmdSpec CmdSpec
{ csAlias = btAlias { csAlias = btAlias
, csRunnable = , csRunnable =
Run $ Run $
Bluetooth (fontify' "\xf5b0" "+", fontify' "\xf5ae" "-") colors Bluetooth (fontify' "\x0f00b1" "+", fontify' "\x0f00af" "-") colors
} }
where where
fontify' i = fontify IconLarge i . T.append "BT" fontify' i = fontify IconLarge i . T.append "BT"
@ -476,7 +464,7 @@ ckCmd :: Fontifier -> CmdSpec
ckCmd fontify = ckCmd fontify =
CmdSpec CmdSpec
{ csAlias = ckAlias { csAlias = ckAlias
, csRunnable = Run $ ClevoKeyboard $ fontify IconSmall "\xf40b" "KB: " , csRunnable = Run $ ClevoKeyboard $ fontify IconSmall "\xf11c" "KB: "
} }
ssCmd :: Fontifier -> CmdSpec ssCmd :: Fontifier -> CmdSpec
@ -512,8 +500,8 @@ lockCmd fontify =
] ]
} }
where where
numIcon = fontify' "\xf8a5" "N" numIcon = fontify' "\x0f03a6" "N"
capIcon = fontify' "\xf657" "C" capIcon = fontify' "\x0f0bf1" "C"
fontify' = fontify IconXLarge fontify' = fontify IconXLarge
disabledColor = xmobarFGColor XT.backdropFgColor disabledColor = xmobarFGColor XT.backdropFgColor
@ -524,29 +512,6 @@ dateCmd =
, csRunnable = Run $ Date "%Y-%m-%d %H:%M:%S " "date" 10 , csRunnable = Run $ Date "%Y-%m-%d %H:%M:%S " "date" 10
} }
--------------------------------------------------------------------------------
-- low-level testing functions
vpnPresent :: XIO (Maybe Msg)
vpnPresent = do
res <- proc "nmcli" args readProcess
return $ case res of
(ExitSuccess, out, _)
| "vpn" `elem` BL.split 10 out -> Nothing
| otherwise -> Just $ Msg LevelError "vpn not found"
(ExitFailure c, _, err) ->
Just $
Msg LevelError $
T.concat
[ "vpn search exited with code "
, T.pack $ show c
, ": "
, T.decodeUtf8With T.lenientDecode $
BL.toStrict err
]
where
args = ["-c", "no", "-t", "-f", "TYPE", "c", "show"]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- text font -- text font
-- --

View File

@ -1,9 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- XMonad binary -- XMonad binary
@ -27,7 +21,7 @@ import System.Process
( getPid ( getPid
, getProcessExitCode , getProcessExitCode
) )
import XMonad import XMonad hiding (display)
import XMonad.Actions.CopyWindow import XMonad.Actions.CopyWindow
import XMonad.Actions.CycleWS import XMonad.Actions.CycleWS
import XMonad.Actions.PhysicalScreens import XMonad.Actions.PhysicalScreens
@ -51,6 +45,7 @@ import XMonad.Internal.DBus.Removable
import XMonad.Internal.DBus.Screensaver import XMonad.Internal.DBus.Screensaver
import XMonad.Internal.Shell hiding (proc) import XMonad.Internal.Shell hiding (proc)
import qualified XMonad.Internal.Theme as XT import qualified XMonad.Internal.Theme as XT
import XMonad.Layout.Decoration
import XMonad.Layout.MultiToggle import XMonad.Layout.MultiToggle
import XMonad.Layout.NoBorders import XMonad.Layout.NoBorders
import XMonad.Layout.NoFrillsDecoration import XMonad.Layout.NoFrillsDecoration
@ -144,21 +139,21 @@ run = do
, normalBorderColor = T.unpack XT.bordersColor , normalBorderColor = T.unpack XT.bordersColor
, focusedBorderColor = T.unpack XT.selectedBordersColor , focusedBorderColor = T.unpack XT.selectedBordersColor
} }
io $ runXMonad conf runXMonad conf
where where
startDynWorkspaces fs = do startDynWorkspaces fs = do
dws <- catMaybes <$> mapM evalSometimes (fsDynWorkspaces fs) dws <- catMaybes <$> mapM evalSometimes (fsDynWorkspaces fs)
void $ async $ runWorkspaceMon dws void $ async $ runWorkspaceMon dws
return dws return dws
runXMonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO () runXMonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> XIO ()
runXMonad conf = do runXMonad conf = do
dirs <- getCreateDirectories dirs <- getCreateDirectories
launch conf dirs liftIO $ launch conf dirs
getCreateDirectories :: IO Directories getCreateDirectories :: XIO Directories
getCreateDirectories = do getCreateDirectories = do
ds <- getDirectories ds <- liftIO getDirectories
mapM_ (createIfMissing ds) [dataDir, cfgDir, cacheDir] mapM_ (createIfMissing ds) [dataDir, cfgDir, cacheDir]
return ds return ds
where where
@ -166,14 +161,14 @@ getCreateDirectories = do
let d = f ds let d = f ds
r <- tryIO $ createDirectoryIfMissing True d r <- tryIO $ createDirectoryIfMissing True d
case r of case r of
(Left e) -> print e (Left e) -> logError $ display e
_ -> return () _ -> return ()
data FeatureSet = FeatureSet data FeatureSet = FeatureSet
{ fsKeys :: (XIO () -> IO ()) -> X () -> DBusState -> [KeyGroup FeatureX] { fsKeys :: (XIO () -> IO ()) -> X () -> DBusState -> [KeyGroup FeatureX]
, fsDBusExporters :: [Maybe SesClient -> Sometimes (XIO (), XIO ())] , fsDBusExporters :: [Maybe NamedSesConnection -> Sometimes (XIO (), XIO ())]
, fsPowerMon :: SometimesIO , fsPowerMon :: SometimesIO
, fsRemovableMon :: Maybe SysClient -> SometimesIO , fsRemovableMon :: Maybe NamedSysConnection -> SometimesIO
, fsDaemons :: [Sometimes (XIO (Process () () ()))] , fsDaemons :: [Sometimes (XIO (Process () () ()))]
, fsACPIHandler :: Always (String -> X ()) , fsACPIHandler :: Always (String -> X ())
, fsTabbedTheme :: Always Theme , fsTabbedTheme :: Always Theme
@ -188,7 +183,7 @@ tabbedFeature = Always "theme for tabbed windows" $ Option sf fallback
niceTheme = IORoot XT.tabbedTheme $ fontTree XT.defFontFamily defFontPkgs niceTheme = IORoot XT.tabbedTheme $ fontTree XT.defFontFamily defFontPkgs
fallback = Always_ $ FallbackAlone $ XT.tabbedTheme XT.fallbackFont fallback = Always_ $ FallbackAlone $ XT.tabbedTheme XT.fallbackFont
features :: Maybe SysClient -> FeatureSet features :: Maybe NamedSysConnection -> FeatureSet
features cl = features cl =
FeatureSet FeatureSet
{ fsKeys = externalBindings { fsKeys = externalBindings
@ -256,7 +251,7 @@ stopChildDaemons = mapM_ stop
liftIO $ killNoWait p liftIO $ killNoWait p
printDeps :: XIO () printDeps :: XIO ()
printDeps = withDBus_ $ \db -> do printDeps = withDBus_ Nothing Nothing $ \db -> do
runIO <- askRunInIO runIO <- askRunInIO
let mockCleanup = runCleanup runIO mockClean db let mockCleanup = runCleanup runIO mockClean db
let bfs = let bfs =
@ -297,7 +292,7 @@ runCleanup runIO ts db = liftIO $ runIO $ do
mapM_ stopXmobar $ clXmobar ts mapM_ stopXmobar $ clXmobar ts
stopChildDaemons $ clChildren ts stopChildDaemons $ clChildren ts
sequence_ $ clDBusUnexporters ts sequence_ $ clDBusUnexporters ts
disconnectDBusX db disconnectDBus db
-- | Kill a process (group) after xmonad has already started -- | Kill a process (group) after xmonad has already started
-- This is necessary (as opposed to 'stopProcess' from rio) because a) xmonad -- This is necessary (as opposed to 'stopProcess' from rio) because a) xmonad
@ -350,9 +345,6 @@ vmTag = "VM"
xsaneTag :: String xsaneTag :: String
xsaneTag = "XSANE" xsaneTag = "XSANE"
f5Tag :: String
f5Tag = "F5VPN"
gimpDynamicWorkspace :: Sometimes DynWorkspace gimpDynamicWorkspace :: Sometimes DynWorkspace
gimpDynamicWorkspace = sometimesIO_ "gimp workspace" "gimp" tree dw gimpDynamicWorkspace = sometimesIO_ "gimp workspace" "gimp" tree dw
where where
@ -425,31 +417,11 @@ xsaneDynamicWorkspace =
} }
c = "Xsane" c = "Xsane"
f5vpnDynamicWorkspace :: Sometimes DynWorkspace
f5vpnDynamicWorkspace =
Sometimes
"F5 VPN workspace"
xpfF5VPN
[Subfeature (IORoot_ dw tree) "f5vpn"]
where
tree = Only_ $ sysExe [Package AUR "f5vpn"] "f5vpn"
dw =
DynWorkspace
{ dwName = "F5Vpn"
, dwTag = f5Tag
, dwClass = c
, dwHook = [className =? c -?> appendShift f5Tag]
, dwKey = 'i'
, dwCmd = Just skip
}
c = "F5 VPN"
allDWs' :: [Sometimes DynWorkspace] allDWs' :: [Sometimes DynWorkspace]
allDWs' = allDWs' =
[ xsaneDynamicWorkspace [ xsaneDynamicWorkspace
, vmDynamicWorkspace , vmDynamicWorkspace
, gimpDynamicWorkspace , gimpDynamicWorkspace
, f5vpnDynamicWorkspace
] ]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -464,6 +436,10 @@ myLayouts tt =
mkToggle (single HIDE) $ mkToggle (single HIDE) $
tall ||| fulltab ||| full tall ||| fulltab ||| full
where where
addTopBar
:: (Eq a)
=> l a
-> ModifiedLayout (Decoration NoFrillsDecoration DefaultShrinker) l a
addTopBar = noFrillsDeco shrinkText tt addTopBar = noFrillsDeco shrinkText tt
tall = tall =
renamed [Replace "Tall"] $ renamed [Replace "Tall"] $
@ -856,8 +832,9 @@ externalBindings runIO cleanup db =
, -- M-<F1> reserved for showing the keymap , -- M-<F1> reserved for showing the keymap
KeyBinding "M-<F2>" "restart xmonad" restartf KeyBinding "M-<F2>" "restart xmonad" restartf
, KeyBinding "M-<F3>" "recompile xmonad" recompilef , KeyBinding "M-<F3>" "recompile xmonad" recompilef
, KeyBinding "M-<F8>" "select autorandr profile" $ Left $ toX runAutorandrMenu , KeyBinding "M-<F7>" "select autorandr profile" $ Left $ toX runAutorandrMenu
, KeyBinding "M-<F9>" "toggle ethernet" $ Left $ toX runToggleEthernet , KeyBinding "M-<F8>" "toggle wifi" $ Left $ toX runToggleWifi
, KeyBinding "M-<F9>" "toggle network" $ Left $ toX runToggleNetworking
, KeyBinding "M-<F10>" "toggle bluetooth" $ Left $ toX $ runToggleBluetooth sys , KeyBinding "M-<F10>" "toggle bluetooth" $ Left $ toX $ runToggleBluetooth sys
, KeyBinding "M-<F11>" "toggle screensaver" $ Left $ toX $ callToggle ses , KeyBinding "M-<F11>" "toggle screensaver" $ Left $ toX $ callToggle ses
, KeyBinding "M-<F12>" "switch gpu" $ Left runOptimusPrompt , KeyBinding "M-<F12>" "switch gpu" $ Left runOptimusPrompt

View File

@ -1,7 +1,3 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Common internal DBus functions -- Common internal DBus functions
@ -9,11 +5,17 @@ module Data.Internal.DBus
( SafeClient (..) ( SafeClient (..)
, SysClient (..) , SysClient (..)
, SesClient (..) , SesClient (..)
, NamedConnection (..)
, NamedSesConnection
, NamedSysConnection
, DBusEnv (..) , DBusEnv (..)
, DIO , DIO
, HasClient (..) , HasClient (..)
, releaseBusName
, withDIO , withDIO
, addMatchCallback , addMatchCallback
, addMatchCallbackSignal
, matchSignalFull
, matchProperty , matchProperty
, matchPropertyFull , matchPropertyFull
, matchPropertyChanged , matchPropertyChanged
@ -39,6 +41,10 @@ module Data.Internal.DBus
, displayMemberName , displayMemberName
, displayInterfaceName , displayInterfaceName
, displayWrapQuote , displayWrapQuote
, busNameT
, interfaceNameT
, memberNameT
, objectPathT
) )
where where
@ -53,48 +59,129 @@ import qualified RIO.Text as T
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Type-safe client -- Type-safe client
class SafeClient c where data NamedConnection c = NamedConnection
toClient :: c -> Client { ncClient :: !Client
, ncHumanName :: !(Maybe BusName)
--, ncUniqueName :: !BusName
, ncType :: !c
}
type NamedSesConnection = NamedConnection SesClient
type NamedSysConnection = NamedConnection SysClient
class SafeClient c where
getDBusClient getDBusClient
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> m (Maybe c) => Maybe BusName
-> m (Maybe (NamedConnection c))
disconnectDBusClient :: MonadUnliftIO m => c -> m () disconnectDBusClient
disconnectDBusClient = liftIO . disconnect . toClient :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> NamedConnection c
-> m ()
disconnectDBusClient c = do
releaseBusName c
liftIO $ disconnect $ ncClient c
withDBusClient withDBusClient
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> (c -> m a) => Maybe BusName
-> (NamedConnection c -> m a)
-> m (Maybe a) -> m (Maybe a)
withDBusClient f = withDBusClient n f =
bracket getDBusClient (mapM (liftIO . disconnect . toClient)) $ mapM f bracket (getDBusClient n) (mapM (liftIO . disconnect . ncClient)) $ mapM f
withDBusClient_ withDBusClient_
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> (c -> m ()) => Maybe BusName
-> (NamedConnection c -> m ())
-> m () -> m ()
withDBusClient_ = void . withDBusClient withDBusClient_ n = void . withDBusClient n
fromDBusClient fromDBusClient
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> (c -> a) => Maybe BusName
-> (NamedConnection c -> a)
-> m (Maybe a) -> m (Maybe a)
fromDBusClient f = withDBusClient (return . f) fromDBusClient n f = withDBusClient n (return . f)
newtype SysClient = SysClient Client data SysClient = SysClient
instance SafeClient SysClient where instance SafeClient SysClient where
toClient (SysClient cl) = cl getDBusClient = connectToDBusWithName True SysClient
getDBusClient = fmap SysClient <$> getDBusClient' True data SesClient = SesClient
newtype SesClient = SesClient Client
instance SafeClient SesClient where instance SafeClient SesClient where
toClient (SesClient cl) = cl -- TODO wet
getDBusClient = connectToDBusWithName False SesClient
getDBusClient = fmap SesClient <$> getDBusClient' False connectToDBusWithName
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> Bool
-> c
-> Maybe BusName
-> m (Maybe (NamedConnection c))
connectToDBusWithName sys t n = do
clRes <- getDBusClient' sys
case clRes of
Nothing -> do
logError "could not get client"
return Nothing
Just cl -> do
--helloRes <- liftIO $ callHello cl
--case helloRes of
-- Nothing -> do
-- logError "count not get unique name"
-- return Nothing
-- Just unique -> do
n' <- maybe (return Nothing) (`requestBusName` cl) n
return $
Just $
NamedConnection
{ ncClient = cl
, ncHumanName = n'
-- , ncUniqueName = unique
, ncType = t
}
releaseBusName
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> NamedConnection c
-> m ()
releaseBusName NamedConnection {ncClient, ncHumanName} = do
-- TODO this might error?
case ncHumanName of
Just n -> do
liftIO $ void $ releaseName ncClient n
logInfo $ "released bus name: " <> displayBusName n
Nothing -> return ()
requestBusName
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> BusName
-> Client
-> m (Maybe BusName)
requestBusName n cl = do
res <- try $ liftIO $ requestName cl n []
case res of
Left e -> do
logError $ displayBytesUtf8 $ BC.pack $ clientErrorMessage e
return Nothing
Right r -> do
let msg
| r == NamePrimaryOwner = "registering name"
| r == NameAlreadyOwner = "this process already owns name"
| r == NameInQueue
|| r == NameExists =
"another process owns name"
-- this should never happen
| otherwise = "unknown error when requesting name"
logInfo $ msg <> ": " <> displayBusName n
case r of
NamePrimaryOwner -> return $ Just n
_ -> return Nothing
getDBusClient' getDBusClient'
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
@ -108,19 +195,28 @@ getDBusClient' sys = do
return Nothing return Nothing
Right c -> return $ Just c Right c -> return $ Just c
data DBusEnv env c = DBusEnv {dClient :: !c, dEnv :: !env} --callHello :: Client -> IO (Maybe BusName)
--callHello cl = do
-- reply <- call_ cl $ methodCallBus dbusName dbusPath dbusInterface "Hello"
-- case methodReturnBody reply of
-- [name] | Just nameStr <- fromVariant name -> do
-- busName <- parseBusName nameStr
-- return $ Just busName
-- _ -> return Nothing
--
data DBusEnv env c = DBusEnv {dClient :: !(NamedConnection c), dEnv :: !env}
type DIO env c = RIO (DBusEnv env c) type DIO env c = RIO (DBusEnv env c)
instance HasClient (DBusEnv SimpleApp) where instance HasClient (DBusEnv SimpleApp) where
clientL = lens dClient (\x y -> x {dClient = y}) clientL = lens dClient (\x y -> x {dClient = y})
instance SafeClient c => HasLogFunc (DBusEnv SimpleApp c) where instance HasLogFunc (DBusEnv SimpleApp c) where
logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL
withDIO withDIO
:: (MonadUnliftIO m, MonadReader env m, SafeClient c) :: (MonadUnliftIO m, MonadReader env m)
=> c => NamedConnection c
-> DIO env c a -> DIO env c a
-> m a -> m a
withDIO cl x = do withDIO cl x = do
@ -128,7 +224,7 @@ withDIO cl x = do
runRIO (DBusEnv cl env) x runRIO (DBusEnv cl env) x
class HasClient env where class HasClient env where
clientL :: SafeClient c => Lens' (env c) c clientL :: SafeClient c => Lens' (env c) (NamedConnection c)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Methods -- Methods
@ -140,7 +236,7 @@ callMethod'
=> MethodCall => MethodCall
-> m MethodBody -> m MethodBody
callMethod' mc = do callMethod' mc = do
cl <- toClient <$> view clientL cl <- ncClient <$> view clientL
liftIO $ bimap (T.pack . methodErrorMessage) methodReturnBody <$> call cl mc liftIO $ bimap (T.pack . methodErrorMessage) methodReturnBody <$> call cl mc
callMethod callMethod
@ -202,9 +298,21 @@ bodyToMaybe = either (const Nothing) fromSingletonVariant
type SignalCallback m = [Variant] -> m () type SignalCallback m = [Variant] -> m ()
addMatchCallbackSignal
:: ( MonadReader (env c) m
, MonadUnliftIO m
, SafeClient c
, HasClient env
)
=> MatchRule
-> (Signal -> m ())
-> m SignalHandler
addMatchCallbackSignal rule cb = do
cl <- ncClient <$> view clientL
withRunInIO $ \run -> addMatch cl rule $ run . cb
addMatchCallback addMatchCallback
:: ( MonadReader (env c) m :: ( MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m , MonadUnliftIO m
, SafeClient c , SafeClient c
, HasClient env , HasClient env
@ -212,10 +320,7 @@ addMatchCallback
=> MatchRule => MatchRule
-> SignalCallback m -> SignalCallback m
-> m SignalHandler -> m SignalHandler
addMatchCallback rule cb = do addMatchCallback rule cb = addMatchCallbackSignal rule (cb . signalBody)
cl <- toClient <$> view clientL
withRunInIO $ \run -> do
addMatch cl rule $ run . cb . signalBody
matchSignal matchSignal
:: Maybe BusName :: Maybe BusName
@ -284,7 +389,7 @@ callPropertyGet
-> MemberName -> MemberName
-> m [Variant] -> m [Variant]
callPropertyGet bus path iface property = do callPropertyGet bus path iface property = do
cl <- toClient <$> view clientL cl <- ncClient <$> view clientL
res <- liftIO $ getProperty cl $ methodCallBus bus path iface property res <- liftIO $ getProperty cl $ methodCallBus bus path iface property
case res of case res of
Left err -> do Left err -> do
@ -319,26 +424,26 @@ withSignalMatch _ NoMatch = return ()
matchPropertyChanged matchPropertyChanged
:: IsVariant a :: IsVariant a
=> InterfaceName => InterfaceName
-> T.Text -> MemberName
-> [Variant] -> [Variant]
-> SignalMatch a -> SignalMatch a
matchPropertyChanged iface property [i, body, _] = matchPropertyChanged iface property [sigIface, sigValues, _] =
let i' = (fromVariant i :: Maybe T.Text) let i = fromVariant sigIface :: Maybe T.Text
b = toMap body v = fromVariant sigValues :: Maybe (M.Map T.Text Variant)
in case (i', b) of in case (i, v) of
(Just i'', Just b') -> (Just i', Just v') ->
if i'' == T.pack (formatInterfaceName iface) if i' == interfaceNameT iface
then maybe NoMatch Match $ fromVariant =<< M.lookup property b' then
maybe NoMatch Match $
fromVariant =<< M.lookup (memberNameT property) v'
else NoMatch else NoMatch
_ -> Failure _ -> Failure
where
toMap v = fromVariant v :: Maybe (M.Map T.Text Variant)
matchPropertyChanged _ _ _ = Failure matchPropertyChanged _ _ _ = Failure
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Object Manager -- Object Manager
type ObjectTree = M.Map ObjectPath (M.Map T.Text (M.Map T.Text Variant)) type ObjectTree = M.Map ObjectPath (M.Map InterfaceName (M.Map T.Text Variant))
omInterface :: InterfaceName omInterface :: InterfaceName
omInterface = interfaceName_ "org.freedesktop.DBus.ObjectManager" omInterface = interfaceName_ "org.freedesktop.DBus.ObjectManager"
@ -368,7 +473,11 @@ callGetManagedObjects bus path = do
Left err -> do Left err -> do
logError $ Utf8Builder $ encodeUtf8Builder err logError $ Utf8Builder $ encodeUtf8Builder err
return M.empty return M.empty
Right v -> return $ fromMaybe M.empty $ fromSingletonVariant v Right v ->
return $
fmap (M.mapKeys interfaceName_) $
fromMaybe M.empty $
fromSingletonVariant v
addInterfaceChangedListener addInterfaceChangedListener
:: ( MonadReader (env c) m :: ( MonadReader (env c) m
@ -432,14 +541,14 @@ addInterfaceRemovedListener bus =
-- Interface export/unexport -- Interface export/unexport
exportPair exportPair
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m, SafeClient c) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> ObjectPath => ObjectPath
-> (Client -> m Interface) -> (Client -> m Interface)
-> c -> NamedConnection c
-> (m (), m ()) -> (m (), m ())
exportPair path toIface cl = (up, down) exportPair path toIface cl = (up, down)
where where
cl_ = toClient cl cl_ = ncClient cl
up = do up = do
logInfo $ "adding interface: " <> path_ logInfo $ "adding interface: " <> path_
i <- toIface cl_ i <- toIface cl_
@ -452,6 +561,18 @@ exportPair path toIface cl = (up, down)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- logging helpers -- logging helpers
busNameT :: BusName -> T.Text
busNameT = T.pack . formatBusName
objectPathT :: ObjectPath -> T.Text
objectPathT = T.pack . formatObjectPath
interfaceNameT :: InterfaceName -> T.Text
interfaceNameT = T.pack . formatInterfaceName
memberNameT :: MemberName -> T.Text
memberNameT = T.pack . formatMemberName
displayBusName :: BusName -> Utf8Builder displayBusName :: BusName -> Utf8Builder
displayBusName = displayBytesUtf8 . BC.pack . formatBusName displayBusName = displayBytesUtf8 . BC.pack . formatBusName

View File

@ -1,12 +1,3 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Functions for handling dependencies -- Functions for handling dependencies
@ -109,6 +100,7 @@ import qualified DBus.Introspection as I
import Data.Aeson hiding (Error, Result) import Data.Aeson hiding (Error, Result)
import Data.Aeson.Key import Data.Aeson.Key
import Data.Internal.DBus import Data.Internal.DBus
import qualified Data.Text.IO as TI
import Data.Yaml import Data.Yaml
import GHC.IO.Exception (ioe_description) import GHC.IO.Exception (ioe_description)
import RIO hiding (bracket, fromString) import RIO hiding (bracket, fromString)
@ -140,9 +132,9 @@ runXIO logfile x = withLogFile logfile $ \h -> hRunXIO True h x
withLogFile :: MonadUnliftIO m => FilePath -> (Handle -> m a) -> m a withLogFile :: MonadUnliftIO m => FilePath -> (Handle -> m a) -> m a
withLogFile logfile f = do withLogFile logfile f = do
p <- (</> logfile) . dataDir <$> liftIO getDirectories p <- (</> logfile) . dataDir <$> liftIO getDirectories
catchIO (withFile p AppendMode f) $ \e -> do catchIO (withBinaryFile p AppendMode f) $ \e -> do
liftIO $ print e liftIO $ TI.putStrLn $ T.pack $ show e
liftIO $ putStrLn "could not open log file, falling back to stderr" liftIO $ TI.putStrLn "could not open log file, falling back to stderr"
f stderr f stderr
hRunXIO :: Bool -> Handle -> XIO a -> IO a hRunXIO :: Bool -> Handle -> XIO a -> IO a
@ -296,8 +288,18 @@ type SubfeatureRoot a = Subfeature (Root a)
data Root a data Root a
= forall p. IORoot (p -> a) (IOTree p) = forall p. IORoot (p -> a) (IOTree p)
| IORoot_ a IOTree_ | IORoot_ a IOTree_
| forall c p. SafeClient c => DBusRoot (p -> c -> a) (DBusTree c p) (Maybe c) | forall c p.
| forall c. SafeClient c => DBusRoot_ (c -> a) (DBusTree_ c) (Maybe c) SafeClient c =>
DBusRoot
(p -> NamedConnection c -> a)
(DBusTree c p)
(Maybe (NamedConnection c))
| forall c.
SafeClient c =>
DBusRoot_
(NamedConnection c -> a)
(DBusTree_ c)
(Maybe (NamedConnection c))
instance Functor Root where instance Functor Root where
fmap f (IORoot a t) = IORoot (f . a) t fmap f (IORoot a t) = IORoot (f . a) t
@ -425,7 +427,7 @@ data XEnv = XEnv
instance HasLogFunc XEnv where instance HasLogFunc XEnv where
logFuncL = lens xLogFun (\x y -> x {xLogFun = y}) logFuncL = lens xLogFun (\x y -> x {xLogFun = y})
instance SafeClient c => HasLogFunc (DBusEnv XEnv c) where instance HasLogFunc (DBusEnv XEnv c) where
logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL logFuncL = lens dEnv (\x y -> x {dEnv = y}) . logFuncL
instance HasProcessContext XEnv where instance HasProcessContext XEnv where
@ -466,7 +468,8 @@ data XPFeatures = XPFeatures
, xpfIntelBacklight :: Bool , xpfIntelBacklight :: Bool
, xpfClevoBacklight :: Bool , xpfClevoBacklight :: Bool
, xpfBattery :: Bool , xpfBattery :: Bool
, xpfF5VPN :: Bool , xpfEthPrefix :: Maybe Text
, xpfWifiPrefix :: Maybe Text
} }
instance FromJSON XPFeatures where instance FromJSON XPFeatures where
@ -493,7 +496,9 @@ instance FromJSON XPFeatures where
<*> o <*> o
.:+ "battery" .:+ "battery"
<*> o <*> o
.:+ "f5vpn" .:? "ethPrefix"
<*> o
.:? "wifiPrefix"
defParams :: XParams defParams :: XParams
defParams = defParams =
@ -516,7 +521,8 @@ defXPFeatures =
, xpfIntelBacklight = False , xpfIntelBacklight = False
, xpfClevoBacklight = False , xpfClevoBacklight = False
, xpfBattery = False , xpfBattery = False
, xpfF5VPN = False , xpfEthPrefix = Nothing
, xpfWifiPrefix = Nothing
} }
type XPQuery = XPFeatures -> Bool type XPQuery = XPFeatures -> Bool
@ -527,7 +533,7 @@ getParams = do
maybe (return defParams) (liftIO . decodeYaml) p maybe (return defParams) (liftIO . decodeYaml) p
where where
decodeYaml p = decodeYaml p =
either (\e -> print e >> return defParams) return either (\e -> TI.putStrLn (T.pack $ show e) >> return defParams) return
=<< decodeFileEither p =<< decodeFileEither p
getParamFile :: MonadIO m => m (Maybe FilePath) getParamFile :: MonadIO m => m (Maybe FilePath)
@ -827,16 +833,16 @@ testFont fam = maybe pass (Left . (: [])) <$> shellTest "fc-list" args msg
-- start with "en" and wireless interfaces always start with "wl" -- start with "en" and wireless interfaces always start with "wl"
readEthernet :: IODependency T.Text readEthernet :: IODependency T.Text
readEthernet = readInterface "get ethernet interface" isEthernet readEthernet = readInterface "get ethernet interface" (fromMaybe "en" . xpfEthPrefix)
readWireless :: IODependency T.Text readWireless :: IODependency T.Text
readWireless = readInterface "get wireless interface" isWireless readWireless = readInterface "get wireless interface" (fromMaybe "wl" . xpfWifiPrefix)
isWireless :: T.Text -> Bool -- isWireless :: T.Text -> Bool
isWireless = T.isPrefixOf "wl" -- isWireless = T.isPrefixOf "wl"
isEthernet :: T.Text -> Bool -- isEthernet :: T.Text -> Bool
isEthernet = T.isPrefixOf "en" -- isEthernet = T.isPrefixOf "en"
listInterfaces :: MonadUnliftIO m => m [T.Text] listInterfaces :: MonadUnliftIO m => m [T.Text]
listInterfaces = listInterfaces =
@ -848,11 +854,12 @@ sysfsNet = "/sys/class/net"
-- ASSUME there are no (non-base) packages required to make these interfaces -- ASSUME there are no (non-base) packages required to make these interfaces
-- work (all at the kernel level) -- work (all at the kernel level)
readInterface :: T.Text -> (T.Text -> Bool) -> IODependency T.Text readInterface :: T.Text -> (XPFeatures -> Text) -> IODependency T.Text
readInterface n f = IORead n [] go readInterface n f = IORead n [] go
where where
go = io $ do go = do
ns <- filter f <$> listInterfaces p <- asks (f . xpFeatures . xParams)
ns <- filter (T.isPrefixOf p) <$> listInterfaces
case ns of case ns of
[] -> return $ Left [Msg LevelError "no interfaces found"] [] -> return $ Left [Msg LevelError "no interfaces found"]
(x : xs) -> do (x : xs) -> do
@ -888,10 +895,10 @@ introspectInterface = interfaceName_ "org.freedesktop.DBus.Introspectable"
introspectMethod :: MemberName introspectMethod :: MemberName
introspectMethod = memberName_ "Introspect" introspectMethod = memberName_ "Introspect"
testDBusDep_ :: SafeClient c => c -> DBusDependency_ c -> XIO MResult_ testDBusDep_ :: SafeClient c => NamedConnection c -> DBusDependency_ c -> XIO MResult_
testDBusDep_ c d = memoizeMVar $ testDBusDepNoCache_ c d testDBusDep_ c d = memoizeMVar $ testDBusDepNoCache_ c d
testDBusDepNoCache_ :: SafeClient c => c -> DBusDependency_ c -> XIO Result_ testDBusDepNoCache_ :: SafeClient c => NamedConnection c -> DBusDependency_ c -> XIO Result_
testDBusDepNoCache_ cl (Bus _ bus) = do testDBusDepNoCache_ cl (Bus _ bus) = do
ret <- withDIO cl $ callMethod queryBus queryPath queryIface queryMem ret <- withDIO cl $ callMethod queryBus queryPath queryIface queryMem
return $ case ret of return $ case ret of
@ -1022,11 +1029,11 @@ sometimesExeArgs fn n ful sys path args =
sometimesDBus sometimesDBus
:: SafeClient c :: SafeClient c
=> Maybe c => Maybe (NamedConnection c)
-> T.Text -> T.Text
-> T.Text -> T.Text
-> Tree_ (DBusDependency_ c) -> Tree_ (DBusDependency_ c)
-> (c -> a) -> (NamedConnection c -> a)
-> Sometimes a -> Sometimes a
sometimesDBus c fn n t x = sometimes1 fn n $ DBusRoot_ x t c sometimesDBus c fn n t x = sometimes1 fn n $ DBusRoot_ x t c
@ -1040,7 +1047,7 @@ sometimesEndpoint
-> ObjectPath -> ObjectPath
-> InterfaceName -> InterfaceName
-> MemberName -> MemberName
-> Maybe c -> Maybe (NamedConnection c)
-> Sometimes (m ()) -> Sometimes (m ())
sometimesEndpoint fn name ful busname path iface mem cl = sometimesEndpoint fn name ful busname path iface mem cl =
sometimesDBus cl fn name deps cmd sometimesDBus cl fn name deps cmd

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Dmenu (Rofi) Commands -- Dmenu (Rofi) Commands
@ -148,7 +146,7 @@ runAppMenu = spawnDmenuCmd "app launcher" ["-show", "drun"]
runWinMenu :: MonadUnliftIO m => Sometimes (m ()) runWinMenu :: MonadUnliftIO m => Sometimes (m ())
runWinMenu = spawnDmenuCmd "window switcher" ["-show", "window"] runWinMenu = spawnDmenuCmd "window switcher" ["-show", "window"]
runNetMenu :: MonadUnliftIO m => Maybe SysClient -> Sometimes (m ()) runNetMenu :: MonadUnliftIO m => Maybe NamedSysConnection -> Sometimes (m ())
runNetMenu cl = runNetMenu cl =
Sometimes Sometimes
"network control menu" "network control menu"
@ -173,7 +171,7 @@ runAutorandrMenu = sometimesIO_ "autorandr menu" "rofi autorandr" tree cmd
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Password manager -- Password manager
runBwMenu :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runBwMenu :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runBwMenu cl = sometimesDBus cl "password manager" "rofi bitwarden" tree cmd runBwMenu cl = sometimesDBus cl "password manager" "rofi bitwarden" tree cmd
where where
cmd _ = cmd _ =
@ -210,7 +208,7 @@ runClipMenu = sometimesIO_ "clipboard manager" "rofi greenclip" tree act
-- Shortcut menu -- Shortcut menu
runShowKeys runShowKeys
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, MonadUnliftIO m)
=> Always ([((KeyMask, KeySym), NamedAction)] -> m ()) => Always ([((KeyMask, KeySym), NamedAction)] -> m ())
runShowKeys = runShowKeys =
Always "keyboard menu" $ Always "keyboard menu" $
@ -225,7 +223,7 @@ runShowKeys =
defNoteError {body = Just $ Text "could not display keymap"} defNoteError {body = Just $ Text "could not display keymap"}
showKeysDMenu showKeysDMenu
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, MonadUnliftIO m)
=> SubfeatureRoot ([((KeyMask, KeySym), NamedAction)] -> m ()) => SubfeatureRoot ([((KeyMask, KeySym), NamedAction)] -> m ())
showKeysDMenu = showKeysDMenu =
Subfeature Subfeature
@ -234,7 +232,7 @@ showKeysDMenu =
} }
showKeys showKeys
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, MonadUnliftIO m)
=> [((KeyMask, KeySym), NamedAction)] => [((KeyMask, KeySym), NamedAction)]
-> m () -> m ()
showKeys kbs = do showKeys kbs = do

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- General commands -- General commands
@ -21,7 +19,8 @@ module XMonad.Internal.Command.Desktop
, runVolumeUp , runVolumeUp
, runVolumeMute , runVolumeMute
, runToggleBluetooth , runToggleBluetooth
, runToggleEthernet , runToggleNetworking
, runToggleWifi
, runRestart , runRestart
, runRecompile , runRecompile
, runAreaCapture , runAreaCapture
@ -60,13 +59,13 @@ import XMonad.Operations
-- My Executables -- My Executables
myTerm :: FilePath myTerm :: FilePath
myTerm = "urxvt" myTerm = "alacritty"
myCalc :: FilePath myCalc :: FilePath
myCalc = "bc" myCalc = "bc"
myBrowser :: FilePath myBrowser :: FilePath
myBrowser = "brave" myBrowser = "firefox"
myEditor :: FilePath myEditor :: FilePath
myEditor = "emacsclient" myEditor = "emacsclient"
@ -94,8 +93,7 @@ myNotificationCtrl = "dunstctl"
myTermPkgs :: [Fulfillment] myTermPkgs :: [Fulfillment]
myTermPkgs = myTermPkgs =
[ Package Official "rxvt-unicode" [ Package Official "alacritty"
, Package Official "urxvt-perls"
] ]
myEditorPkgs :: [Fulfillment] myEditorPkgs :: [Fulfillment]
@ -110,6 +108,9 @@ bluetoothPkgs = [Package Official "bluez-utils"]
networkManagerPkgs :: [Fulfillment] networkManagerPkgs :: [Fulfillment]
networkManagerPkgs = [Package Official "networkmanager"] networkManagerPkgs = [Package Official "networkmanager"]
nmcli :: IODependency_
nmcli = sysExe networkManagerPkgs "nmcli"
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Misc constants -- Misc constants
@ -120,7 +121,7 @@ volumeChangeSound = "smb_fireball.wav"
-- Some nice apps -- Some nice apps
runTerm :: MonadUnliftIO m => Sometimes (m ()) runTerm :: MonadUnliftIO m => Sometimes (m ())
runTerm = sometimesExe "terminal" "urxvt" myTermPkgs True myTerm runTerm = sometimesExe "terminal" "alacritty" myTermPkgs True myTerm
runTMux :: MonadUnliftIO m => Sometimes (m ()) runTMux :: MonadUnliftIO m => Sometimes (m ())
runTMux = sometimesIO_ "terminal multiplexer" "tmux" deps act runTMux = sometimesIO_ "terminal multiplexer" "tmux" deps act
@ -208,7 +209,7 @@ runStopPlay = runMultimediaIfInstalled "stop playback" "stop"
-- Volume Commands -- Volume Commands
soundDir :: FilePath soundDir :: FilePath
soundDir = "sound" soundDir = "assets" </> "sound"
playSound :: MonadIO m => FilePath -> m () playSound :: MonadIO m => FilePath -> m ()
playSound file = do playSound file = do
@ -248,7 +249,7 @@ runNotificationCmd
:: MonadUnliftIO m :: MonadUnliftIO m
=> T.Text => T.Text
-> T.Text -> T.Text
-> Maybe SesClient -> Maybe NamedSesConnection
-> Sometimes (m ()) -> Sometimes (m ())
runNotificationCmd n arg cl = runNotificationCmd n arg cl =
sometimesDBus cl (T.unwords [n, "control"]) "dunstctl" tree cmd sometimesDBus cl (T.unwords [n, "control"]) "dunstctl" tree cmd
@ -260,37 +261,37 @@ runNotificationCmd n arg cl =
Method_ $ Method_ $
memberName_ "NotificationAction" memberName_ "NotificationAction"
runNotificationClose :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runNotificationClose :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runNotificationClose = runNotificationCmd "close notification" "close" runNotificationClose = runNotificationCmd "close notification" "close"
runNotificationCloseAll :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runNotificationCloseAll :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runNotificationCloseAll = runNotificationCloseAll =
runNotificationCmd "close all notifications" "close-all" runNotificationCmd "close all notifications" "close-all"
runNotificationHistory :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runNotificationHistory :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runNotificationHistory = runNotificationHistory =
runNotificationCmd "see notification history" "history-pop" runNotificationCmd "see notification history" "history-pop"
runNotificationContext :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runNotificationContext :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runNotificationContext = runNotificationContext =
runNotificationCmd "open notification context" "context" runNotificationCmd "open notification context" "context"
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- System commands -- System commands
-- this is required for some vpn's to work properly with network-manager -- needed to lookup/prompt for passwords/keys for wifi connections and some VPNs
runNetAppDaemon :: Maybe SysClient -> Sometimes (XIO (P.Process () () ())) runNetAppDaemon :: Maybe NamedSysConnection -> Sometimes (XIO (P.Process () () ()))
runNetAppDaemon cl = runNetAppDaemon cl =
Sometimes Sometimes
"network applet" "network applet"
xpfVPN (\x -> xpfVPN x || xpfWireless x)
[Subfeature (DBusRoot_ cmd tree cl) "NM-applet"] [Subfeature (DBusRoot_ cmd tree cl) "NM-applet"]
where where
tree = toAnd_ app $ Bus networkManagerPkgs networkManagerBus tree = toAnd_ app $ Bus networkManagerPkgs networkManagerBus
app = DBusIO $ sysExe [Package Official "network-manager-applet"] "nm-applet" app = DBusIO $ sysExe [Package Official "network-manager-applet"] "nm-applet"
cmd _ = P.proc "nm-applet" [] (P.startProcess . P.setCreateGroup True) cmd _ = P.proc "nm-applet" [] (P.startProcess . P.setCreateGroup True)
runToggleBluetooth :: MonadUnliftIO m => Maybe SysClient -> Sometimes (m ()) runToggleBluetooth :: MonadUnliftIO m => Maybe NamedSysConnection -> Sometimes (m ())
runToggleBluetooth cl = runToggleBluetooth cl =
Sometimes Sometimes
"bluetooth toggle" "bluetooth toggle"
@ -307,27 +308,35 @@ runToggleBluetooth cl =
#!>> fmtCmd myBluetooth ["power", "$a", ">", "/dev/null"] #!>> fmtCmd myBluetooth ["power", "$a", ">", "/dev/null"]
#!&& fmtNotifyCmd defNoteInfo {body = Just $ Text "bluetooth powered $a"} #!&& fmtNotifyCmd defNoteInfo {body = Just $ Text "bluetooth powered $a"}
runToggleEthernet :: MonadUnliftIO m => Sometimes (m ()) runToggleNetworking :: MonadUnliftIO m => Sometimes (m ())
runToggleEthernet = runToggleNetworking =
Sometimes Sometimes
"ethernet toggle" "network toggle"
xpfEthernet (\x -> xpfEthernet x || xpfWireless x)
[Subfeature root "nmcli"] [Subfeature root "nmcli"]
where where
root = root = IORoot_ cmd $ Only_ nmcli
IORoot cmd $ cmd =
And1 (Only readEthernet) $
Only_ $
sysExe networkManagerPkgs "nmcli"
-- TODO make this less noisy
cmd iface =
S.spawn $ S.spawn $
fmtCmd "nmcli" ["-g", "GENERAL.STATE", "device", "show", iface] fmtCmd "nmcli" ["networking"]
#!| "grep -q disconnected" #!| "grep -q enabled"
#!&& "a=connect" #!&& "a=off"
#!|| "a=disconnect" #!|| "a=on"
#!>> fmtCmd "nmcli" ["device", "$a", iface] #!>> fmtCmd "nmcli" ["networking", "$a"]
#!&& fmtNotifyCmd defNoteInfo {body = Just $ Text "ethernet \"$a\"ed"} #!&& fmtNotifyCmd defNoteInfo {body = Just $ Text "networking switched $a"}
runToggleWifi :: MonadUnliftIO m => Sometimes (m ())
runToggleWifi = Sometimes "wifi toggle" xpfWireless [Subfeature root "nmcli"]
where
root = IORoot_ cmd $ Only_ nmcli
cmd =
S.spawn $
fmtCmd "nmcli" ["radio", "wifi"]
#!| "grep -q enabled"
#!&& "a=off"
#!|| "a=on"
#!>> fmtCmd "nmcli" ["radio", "wifi", "$a"]
#!&& fmtNotifyCmd defNoteInfo {body = Just $ Text "wifi switched $a"}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Configuration commands -- Configuration commands
@ -368,7 +377,7 @@ runFlameshot
:: MonadUnliftIO m :: MonadUnliftIO m
=> T.Text => T.Text
-> T.Text -> T.Text
-> Maybe SesClient -> Maybe NamedSesConnection
-> Sometimes (m ()) -> Sometimes (m ())
runFlameshot n mode cl = sometimesDBus cl n (T.pack myCapture) tree cmd runFlameshot n mode cl = sometimesDBus cl n (T.pack myCapture) tree cmd
where where
@ -380,15 +389,15 @@ runFlameshot n mode cl = sometimesDBus cl n (T.pack myCapture) tree cmd
-- TODO this will steal focus from the current window (and puts it -- TODO this will steal focus from the current window (and puts it
-- in the root window?) ...need to fix -- in the root window?) ...need to fix
runAreaCapture :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runAreaCapture :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runAreaCapture = runFlameshot "screen area capture" "gui" runAreaCapture = runFlameshot "screen area capture" "gui"
-- myWindowCap = "screencap -w" --external script -- myWindowCap = "screencap -w" --external script
runDesktopCapture :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runDesktopCapture :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runDesktopCapture = runFlameshot "fullscreen capture" "full" runDesktopCapture = runFlameshot "fullscreen capture" "full"
runScreenCapture :: MonadUnliftIO m => Maybe SesClient -> Sometimes (m ()) runScreenCapture :: MonadUnliftIO m => Maybe NamedSesConnection -> Sometimes (m ())
runScreenCapture = runFlameshot "screen capture" "screen" runScreenCapture = runFlameshot "screen capture" "screen"
runCaptureBrowser :: MonadUnliftIO m => Sometimes (m ()) runCaptureBrowser :: MonadUnliftIO m => Sometimes (m ())

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Commands for controlling power -- Commands for controlling power
@ -91,7 +89,8 @@ runAutolock = sometimesIO_ "automatic screen lock" "xss-lock" tree cmd
And_ (Only_ $ sysExe [Package Official "xss-lock"] "xss-lock") $ And_ (Only_ $ sysExe [Package Official "xss-lock"] "xss-lock") $
Only_ $ Only_ $
IOSometimes_ runScreenLock IOSometimes_ runScreenLock
cmd = P.proc "xss-lock" ["--ignore-sleep", "screenlock"] (P.startProcess . P.setCreateGroup True) cmd = P.proc "xss-lock" args (P.startProcess . P.setCreateGroup True)
args = ["--ignore-sleep", "--", "screenlock", "true"]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Confirmation prompts -- Confirmation prompts
@ -180,17 +179,20 @@ data PowerMaybeAction
| Reboot | Reboot
deriving (Eq) deriving (Eq)
instance Enum PowerMaybeAction where fromPMA :: PowerMaybeAction -> Int
toEnum 0 = Poweroff fromPMA a = case a of
toEnum 1 = Shutdown Poweroff -> 0
toEnum 2 = Hibernate Shutdown -> 1
toEnum 3 = Reboot Hibernate -> 2
toEnum _ = errorWithoutStackTrace "Main.Enum.PowerMaybeAction.toEnum: bad argument" Reboot -> 3
fromEnum Poweroff = 0 toPMA :: Int -> Maybe PowerMaybeAction
fromEnum Shutdown = 1 toPMA x = case x of
fromEnum Hibernate = 2 0 -> Just Poweroff
fromEnum Reboot = 3 1 -> Just Shutdown
2 -> Just Hibernate
3 -> Just Reboot
_ -> Nothing
data PowerPrompt = PowerPrompt data PowerPrompt = PowerPrompt
@ -222,9 +224,11 @@ powerPrompt lock fb = mkXPrompt PowerPrompt theme comp executeMaybeAction
, (xK_Return, quit) , (xK_Return, quit)
, (xK_Escape, quit) , (xK_Escape, quit)
] ]
sendMaybeAction a = setInput (show $ fromEnum a) >> setSuccess True >> setDone True sendMaybeAction a = setInput (show $ fromPMA a) >> setSuccess True >> setDone True
executeMaybeAction a = case toEnum $ read a of executeMaybeAction a = case toPMA =<< readMaybe a of
Poweroff -> liftIO runPowerOff Just Poweroff -> liftIO runPowerOff
Shutdown -> lock >> liftIO runSuspend Just Shutdown -> lock >> liftIO runSuspend
Hibernate -> lock >> liftIO runHibernate Just Hibernate -> lock >> liftIO runHibernate
Reboot -> liftIO runReboot Just Reboot -> liftIO runReboot
-- TODO log an error here since this should never happen
Nothing -> skip

View File

@ -1,6 +1,3 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Concurrent module to handle events from acpid -- Concurrent module to handle events from acpid
@ -33,15 +30,18 @@ data ACPIEvent
| LidClose | LidClose
deriving (Eq) deriving (Eq)
instance Enum ACPIEvent where fromACPIEvent :: ACPIEvent -> Int
toEnum 0 = Power fromACPIEvent x = case x of
toEnum 1 = Sleep Power -> 0
toEnum 2 = LidClose Sleep -> 1
toEnum _ = errorWithoutStackTrace "ACPI.Enum.ACPIEvent.toEnum: bad argument" LidClose -> 2
fromEnum Power = 0 toACPIEvent :: Int -> Maybe ACPIEvent
fromEnum Sleep = 1 toACPIEvent x = case x of
fromEnum LidClose = 2 0 -> Just Power
1 -> Just Sleep
2 -> Just LidClose
_ -> Nothing
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Internal functions -- Internal functions
@ -64,7 +64,7 @@ parseLine line =
-- | Send an ACPIEvent to the X server as a ClientMessage -- | Send an ACPIEvent to the X server as a ClientMessage
sendACPIEvent :: ACPIEvent -> IO () sendACPIEvent :: ACPIEvent -> IO ()
sendACPIEvent = sendXMsg ACPI . show . fromEnum sendACPIEvent = sendXMsg ACPI . show . fromACPIEvent
isDischarging :: IO (Maybe Bool) isDischarging :: IO (Maybe Bool)
isDischarging = do isDischarging = do
@ -91,7 +91,7 @@ socketDep = Only_ $ pathR acpiPath [Package Official "acpid"]
-- Xmonad's event hook) -- Xmonad's event hook)
handleACPI :: FontBuilder -> X () -> String -> X () handleACPI :: FontBuilder -> X () -> String -> X ()
handleACPI fb lock tag = do handleACPI fb lock tag = do
let acpiTag = toEnum <$> readMaybe tag :: Maybe ACPIEvent let acpiTag = toACPIEvent =<< readMaybe tag :: Maybe ACPIEvent
forM_ acpiTag $ \case forM_ acpiTag $ \case
Power -> powerPrompt lock fb Power -> powerPrompt lock fb
Sleep -> suspendPrompt fb Sleep -> suspendPrompt fb

View File

@ -28,6 +28,7 @@ import Graphics.X11.Xlib.Atom
import Graphics.X11.Xlib.Display import Graphics.X11.Xlib.Display
import Graphics.X11.Xlib.Event import Graphics.X11.Xlib.Event
import Graphics.X11.Xlib.Extras import Graphics.X11.Xlib.Extras
import RIO
import XMonad.Internal.IO import XMonad.Internal.IO
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -42,14 +43,18 @@ data XMsgType
| Unknown | Unknown
deriving (Eq, Show) deriving (Eq, Show)
instance Enum XMsgType where fromXMsgType :: XMsgType -> Int
toEnum 0 = ACPI fromXMsgType x = case x of
toEnum 1 = Workspace ACPI -> 0
toEnum _ = errorWithoutStackTrace "ACPI.Enum.ACPIEvent.toEnum: bad argument" Workspace -> 1
Unknown -> 2
fromEnum ACPI = 0 toXMsgType :: Int -> Maybe XMsgType
fromEnum Workspace = 1 toXMsgType x = case x of
fromEnum Unknown = 2 0 -> Just ACPI
1 -> Just Workspace
2 -> Just Unknown
_ -> Nothing
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Exported API -- Exported API
@ -58,9 +63,9 @@ instance Enum XMsgType where
-- type and payload -- type and payload
splitXMsg :: (Integral a) => [a] -> (XMsgType, String) splitXMsg :: (Integral a) => [a] -> (XMsgType, String)
splitXMsg [] = (Unknown, "") splitXMsg [] = (Unknown, "")
splitXMsg (x : xs) = (xtype, tag) splitXMsg (x : xs) = (fromMaybe Unknown xtype, tag)
where where
xtype = toEnum $ fromIntegral x xtype = toXMsgType $ fromIntegral x
tag = chr . fromIntegral <$> takeWhile (/= 0) xs tag = chr . fromIntegral <$> takeWhile (/= 0) xs
-- | Emit a ClientMessage event to the X server with the given type and payloud -- | Emit a ClientMessage event to the X server with the given type and payloud
@ -86,5 +91,5 @@ sendXMsg xtype tag = withOpenDisplay $ \dpy -> do
setClientMessageEvent' e root bITMAP 8 (x : t) setClientMessageEvent' e root bITMAP 8 (x : t)
sendEvent dpy root False substructureNotifyMask e sendEvent dpy root False substructureNotifyMask e
where where
x = fromIntegral $ fromEnum xtype x = fromIntegral $ fromXMsgType xtype
t = fmap (fromIntegral . fromEnum) tag t = fmap (fromIntegral . fromEnum) tag

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Automatically Manage Dynamic Workspaces -- Automatically Manage Dynamic Workspaces
-- This is a somewhat convoluted wrapper for the Dymamic Workspaces module -- This is a somewhat convoluted wrapper for the Dymamic Workspaces module

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- VirtualBox-specific functions -- VirtualBox-specific functions
@ -36,7 +33,7 @@ vmInstanceConfig vmName = do
vmDirectory :: IO (Either String String) vmDirectory :: IO (Either String String)
vmDirectory = do vmDirectory = do
p <- vmConfig p <- vmConfig
s <- tryIO $ readFile p s <- tryIO $ readFileUtf8 p
return $ case s of return $ case s of
(Left _) -> Left "could not read VirtualBox config file" (Left _) -> Left "could not read VirtualBox config file"
(Right x) -> (Right x) ->

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for Clevo Keyboard control -- DBus module for Clevo Keyboard control
@ -120,7 +117,7 @@ clevoKeyboardSignalDep =
exportClevoKeyboard exportClevoKeyboard
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> Maybe SesClient => Maybe NamedSesConnection
-> Sometimes (m (), m ()) -> Sometimes (m (), m ())
exportClevoKeyboard = exportClevoKeyboard =
brightnessExporter brightnessExporter
@ -131,7 +128,7 @@ exportClevoKeyboard =
clevoKeyboardControls clevoKeyboardControls
:: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m) :: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m)
=> Maybe SesClient => Maybe NamedSesConnection
-> BrightnessControls m -> BrightnessControls m
clevoKeyboardControls = brightnessControls xpfClevoBacklight clevoKeyboardConfig clevoKeyboardControls = brightnessControls xpfClevoBacklight clevoKeyboardConfig
@ -142,7 +139,6 @@ callGetBrightnessCK = callGetBrightness clevoKeyboardConfig
matchSignalCK matchSignalCK
:: ( SafeClient c :: ( SafeClient c
, HasLogFunc (env c)
, HasClient env , HasClient env
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m

View File

@ -1,7 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for DBus brightness controls -- DBus module for DBus brightness controls
@ -57,7 +53,7 @@ brightnessControls
:: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m) :: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m)
=> XPQuery => XPQuery
-> BrightnessConfig m a b -> BrightnessConfig m a b
-> Maybe SesClient -> Maybe NamedSesConnection
-> BrightnessControls m -> BrightnessControls m
brightnessControls q bc cl = brightnessControls q bc cl =
BrightnessControls BrightnessControls
@ -80,15 +76,14 @@ callGetBrightness
-> m (Maybe n) -> m (Maybe n)
callGetBrightness BrightnessConfig {bcPath = p, bcInterface = i} = callGetBrightness BrightnessConfig {bcPath = p, bcInterface = i} =
either (const Nothing) bodyGetBrightness either (const Nothing) bodyGetBrightness
<$> callMethod xmonadBusName p i memGet <$> callMethod xmonadSesBusName p i memGet
signalDep :: BrightnessConfig m a b -> DBusDependency_ SesClient signalDep :: BrightnessConfig m a b -> DBusDependency_ c
signalDep BrightnessConfig {bcPath = p, bcInterface = i} = signalDep BrightnessConfig {bcPath = p, bcInterface = i} =
Endpoint [] xmonadBusName p i $ Signal_ memCur Endpoint [] xmonadSesBusName p i $ Signal_ memCur
matchSignal matchSignal
:: ( HasClient env :: ( HasClient env
, HasLogFunc (env c)
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m
, SafeClient c , SafeClient c
@ -117,18 +112,18 @@ brightnessExporter
-> [Fulfillment] -> [Fulfillment]
-> [IODependency_] -> [IODependency_]
-> BrightnessConfig m a b -> BrightnessConfig m a b
-> Maybe SesClient -> Maybe NamedSesConnection
-> Sometimes (m (), m ()) -> Sometimes (m (), m ())
brightnessExporter q ful deps bc@BrightnessConfig {bcName = n} cl = brightnessExporter q ful deps bc@BrightnessConfig {bcName = n} cl =
Sometimes (T.append n " DBus Interface") q [Subfeature root "exporter"] Sometimes (T.append n " DBus Interface") q [Subfeature root "exporter"]
where where
root = DBusRoot_ (exportBrightnessControlsInner bc) tree cl root = DBusRoot_ (exportBrightnessControlsInner bc) tree cl
tree = listToAnds (Bus ful xmonadBusName) $ fmap DBusIO deps tree = listToAnds (Bus ful xmonadSesBusName) $ fmap DBusIO deps
exportBrightnessControlsInner exportBrightnessControlsInner
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m, RealFrac b) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m, RealFrac b)
=> BrightnessConfig m a b => BrightnessConfig m a b
-> SesClient -> NamedSesConnection
-> (m (), m ()) -> (m (), m ())
exportBrightnessControlsInner bc = cmd exportBrightnessControlsInner bc = cmd
where where
@ -177,7 +172,7 @@ emitBrightness BrightnessConfig {bcPath = p, bcInterface = i} client cur =
callBacklight callBacklight
:: (MonadReader env m, HasClient (DBusEnv env), MonadUnliftIO m) :: (MonadReader env m, HasClient (DBusEnv env), MonadUnliftIO m)
=> XPQuery => XPQuery
-> Maybe SesClient -> Maybe NamedSesConnection
-> BrightnessConfig m a b -> BrightnessConfig m a b
-> T.Text -> T.Text
-> MemberName -> MemberName
@ -185,8 +180,8 @@ callBacklight
callBacklight q cl BrightnessConfig {bcPath = p, bcInterface = i, bcName = n} controlName m = callBacklight q cl BrightnessConfig {bcPath = p, bcInterface = i, bcName = n} controlName m =
Sometimes (T.unwords [n, controlName]) q [Subfeature root "method call"] Sometimes (T.unwords [n, controlName]) q [Subfeature root "method call"]
where where
root = DBusRoot_ cmd (Only_ $ Endpoint [] xmonadBusName p i $ Method_ m) cl root = DBusRoot_ cmd (Only_ $ Endpoint [] xmonadSesBusName p i $ Method_ m) cl
cmd c = void $ withDIO c $ callMethod xmonadBusName p i m cmd c = void $ withDIO c $ callMethod xmonadSesBusName p i m
bodyGetBrightness :: Num a => [Variant] -> Maybe a bodyGetBrightness :: Num a => [Variant] -> Maybe a
bodyGetBrightness [b] = fromIntegral <$> (fromVariant b :: Maybe Int32) bodyGetBrightness [b] = fromIntegral <$> (fromVariant b :: Maybe Int32)

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for Intel Backlight control -- DBus module for Intel Backlight control
@ -106,7 +103,7 @@ intelBacklightSignalDep =
exportIntelBacklight exportIntelBacklight
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> Maybe SesClient => Maybe NamedSesConnection
-> Sometimes (m (), m ()) -> Sometimes (m (), m ())
exportIntelBacklight = exportIntelBacklight =
brightnessExporter brightnessExporter
@ -117,7 +114,7 @@ exportIntelBacklight =
intelBacklightControls intelBacklightControls
:: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m) :: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m)
=> Maybe SesClient => Maybe NamedSesConnection
-> BrightnessControls m -> BrightnessControls m
intelBacklightControls = brightnessControls xpfIntelBacklight intelBacklightConfig intelBacklightControls = brightnessControls xpfIntelBacklight intelBacklightConfig
@ -128,7 +125,6 @@ callGetBrightnessIB = callGetBrightness intelBacklightConfig
matchSignalIB matchSignalIB
:: ( SafeClient c :: ( SafeClient c
, HasLogFunc (env c)
, HasClient env , HasClient env
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m

View File

@ -2,7 +2,8 @@
-- High-level interface for managing XMonad's DBus -- High-level interface for managing XMonad's DBus
module XMonad.Internal.DBus.Common module XMonad.Internal.DBus.Common
( xmonadBusName ( xmonadSesBusName
, xmonadSysBusName
, btBus , btBus
, notifyBus , notifyBus
, notifyPath , notifyPath
@ -12,8 +13,11 @@ where
import DBus import DBus
xmonadBusName :: BusName xmonadSesBusName :: BusName
xmonadBusName = busName_ "org.xmonad" xmonadSesBusName = busName_ "org.xmonad.session"
xmonadSysBusName :: BusName
xmonadSysBusName = busName_ "org.xmonad.system"
btBus :: BusName btBus :: BusName
btBus = busName_ "org.bluez" btBus = busName_ "org.bluez"

View File

@ -1,6 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- High-level interface for managing XMonad's DBus -- High-level interface for managing XMonad's DBus
@ -13,9 +10,8 @@ module XMonad.Internal.DBus.Control
, withDBus , withDBus
, withDBus_ , withDBus_
, connectDBus , connectDBus
, connectDBusX
, disconnectDBus , disconnectDBus
, disconnectDBusX -- , disconnectDBusX
, getDBusClient , getDBusClient
, withDBusClient , withDBusClient
, withDBusClient_ , withDBusClient_
@ -29,7 +25,6 @@ import DBus.Client
import Data.Internal.DBus import Data.Internal.DBus
import Data.Internal.XIO import Data.Internal.XIO
import RIO import RIO
import qualified RIO.Text as T
import XMonad.Internal.DBus.Brightness.ClevoKeyboard import XMonad.Internal.DBus.Brightness.ClevoKeyboard
import XMonad.Internal.DBus.Brightness.IntelBacklight import XMonad.Internal.DBus.Brightness.IntelBacklight
import XMonad.Internal.DBus.Common import XMonad.Internal.DBus.Common
@ -37,8 +32,8 @@ import XMonad.Internal.DBus.Screensaver
-- | Current connections to the DBus (session and system buses) -- | Current connections to the DBus (session and system buses)
data DBusState = DBusState data DBusState = DBusState
{ dbSesClient :: Maybe SesClient { dbSesClient :: Maybe NamedSesConnection
, dbSysClient :: Maybe SysClient , dbSysClient :: Maybe NamedSysConnection
} }
withDBusX_ withDBusX_
@ -50,59 +45,79 @@ withDBusX_ = void . withDBusX
withDBusX withDBusX
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> (DBusState -> m a) => (DBusState -> m a)
-> m (Maybe a) -> m a
withDBusX f = withDBus $ \db -> do withDBusX = withDBus (Just xmonadSesBusName) Nothing
forM (dbSesClient db) $ \ses -> do
bracket_ (requestXMonadName ses) (releaseXMonadName ses) $ f db
withDBus_ withDBus_
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> (DBusState -> m a) => Maybe BusName
-> Maybe BusName
-> (DBusState -> m a)
-> m () -> m ()
withDBus_ = void . withDBus withDBus_ sesname sysname = void . withDBus sesname sysname
withDBus withDBus
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> (DBusState -> m a) => Maybe BusName
-> Maybe BusName
-> (DBusState -> m a)
-> m a -> m a
withDBus = bracket connectDBus disconnectDBus withDBus sesname sysname = bracket (connectDBus sesname sysname) disconnectDBus
-- | Connect to the DBus -- | Connect to the DBus
connectDBus connectDBus
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> m DBusState => Maybe BusName
connectDBus = do -> Maybe BusName
ses <- getDBusClient -> m DBusState
sys <- getDBusClient connectDBus sesname sysname = do
ses <- getDBusClient sesname
sys <- getDBusClient sysname
return DBusState {dbSesClient = ses, dbSysClient = sys} return DBusState {dbSesClient = ses, dbSysClient = sys}
-- | Disconnect from the DBus -- | Disconnect from the DBus
disconnectDBus :: MonadUnliftIO m => DBusState -> m () disconnectDBus
disconnectDBus db = disc dbSesClient >> disc dbSysClient
where
disc f = maybe (return ()) disconnectDBusClient $ f db
-- | Connect to the DBus and request the XMonad name
connectDBusX
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> m DBusState
connectDBusX = do
db <- connectDBus
forM_ (dbSesClient db) requestXMonadName
return db
-- | Disconnect from DBus and release the XMonad name
disconnectDBusX
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> DBusState => DBusState
-> m () -> m ()
disconnectDBusX db = do disconnectDBus db = disc dbSesClient >> disc dbSysClient
forM_ (dbSesClient db) releaseXMonadName where
disconnectDBus db disc
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m, SafeClient c)
=> (DBusState -> Maybe (NamedConnection c))
-> m ()
disc f = maybe (return ()) disconnectDBusClient $ f db
-- -- | Connect to the DBus and request the XMonad name
-- connectDBusX
-- :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
-- => m DBusState
-- connectDBusX = do
-- db <- connectDBus
-- requestXMonadName2 db
-- return db
-- -- | Disconnect from DBus and release the XMonad name
-- disconnectDBusX
-- :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
-- => DBusState
-- -> m ()
-- disconnectDBusX db = do
-- forM_ (dbSesClient db) releaseBusName
-- forM_ (dbSysClient db) releaseBusName
-- disconnectDBus db
-- requestXMonadName2
-- :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
-- => DBusState
-- -> m ()
-- requestXMonadName2 db = do
-- forM_ (dbSesClient db) requestXMonadName
-- forM_ (dbSysClient db) requestXMonadName
withDBusInterfaces withDBusInterfaces
:: DBusState :: DBusState
-> [Maybe SesClient -> Sometimes (XIO (), XIO ())] -> [Maybe NamedSesConnection -> Sometimes (XIO (), XIO ())]
-> ([XIO ()] -> XIO a) -> ([XIO ()] -> XIO a)
-> XIO a -> XIO a
withDBusInterfaces db interfaces = bracket up sequence withDBusInterfaces db interfaces = bracket up sequence
@ -115,35 +130,59 @@ withDBusInterfaces db interfaces = bracket up sequence
-- | All exporter features to be assigned to the DBus -- | All exporter features to be assigned to the DBus
dbusExporters dbusExporters
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> [Maybe SesClient -> Sometimes (m (), m ())] => [Maybe NamedSesConnection -> Sometimes (m (), m ())]
dbusExporters = [exportScreensaver, exportIntelBacklight, exportClevoKeyboard] dbusExporters = [exportScreensaver, exportIntelBacklight, exportClevoKeyboard]
releaseXMonadName -- releaseXMonadName
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) -- :: (SafeClient c, MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> SesClient -- => c
-> m () -- -> m ()
releaseXMonadName ses = do -- releaseXMonadName cl = do
-- TODO this might error? -- -- TODO this might error?
liftIO $ void $ releaseName (toClient ses) xmonadBusName -- liftIO $ void $ releaseName (toClient cl) xmonadBusName
logInfo "released xmonad name" -- logInfo "released xmonad name"
requestXMonadName -- releaseBusName
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) -- :: (SafeClient c, MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> SesClient -- => BusName
-> m () -- -> c
requestXMonadName ses = do -- -> m ()
res <- liftIO $ requestName (toClient ses) xmonadBusName [] -- releaseBusName n cl = do
let msg -- -- TODO this might error?
| res == NamePrimaryOwner = "registering name" -- liftIO $ void $ releaseName (toClient cl) n
| res == NameAlreadyOwner = "this process already owns name" -- logInfo $ "released bus name: " <> displayBusName n
| res == NameInQueue
|| res == NameExists = -- requestBusName
"another process owns name" -- :: (SafeClient c, MonadReader env m, HasLogFunc env, MonadUnliftIO m)
| otherwise = "unknown error when requesting name" -- => BusName
logInfo $ msg <> ": " <> xn -- -> c
where -- -> m ()
xn = -- requestBusName n cl = do
Utf8Builder $ -- res <- try $ liftIO $ requestName (toClient cl) n []
encodeUtf8Builder $ -- case res of
T.pack $ -- Left e -> logError $ displayBytesUtf8 $ BC.pack $ clientErrorMessage e
formatBusName xmonadBusName -- Right r -> do
-- let msg
-- | r == NamePrimaryOwner = "registering name"
-- | r == NameAlreadyOwner = "this process already owns name"
-- | r == NameInQueue
-- || r == NameExists =
-- "another process owns name"
-- -- this should never happen
-- | otherwise = "unknown error when requesting name"
-- logInfo $ msg <> ": " <> displayBusName n
-- requestXMonadName
-- :: (SafeClient c, MonadReader env m, HasLogFunc env, MonadUnliftIO m)
-- => c
-- -> m ()
-- requestXMonadName cl = do
-- res <- liftIO $ requestName (toClient cl) xmonadBusName []
-- let msg
-- | res == NamePrimaryOwner = "registering name"
-- | res == NameAlreadyOwner = "this process already owns name"
-- | res == NameInQueue
-- || res == NameExists =
-- "another process owns name"
-- | otherwise = "unknown error when requesting name"
-- logInfo $ msg <> ": " <> displayBusName xmonadBusName

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Module for monitoring removable drive events -- Module for monitoring removable drive events
-- --
@ -83,11 +80,10 @@ playSoundMaybe p b = when b $ io $ playSound p
-- enable the udisks2 service at boot; however this is not default behavior. -- enable the udisks2 service at boot; however this is not default behavior.
listenDevices listenDevices
:: ( HasClient (DBusEnv env) :: ( HasClient (DBusEnv env)
, HasLogFunc (DBusEnv env SysClient)
, MonadReader env m , MonadReader env m
, MonadUnliftIO m , MonadUnliftIO m
) )
=> SysClient => NamedSysConnection
-> m () -> m ()
listenDevices cl = do listenDevices cl = do
addMatch' memAdded driveInsertedSound addedHasDrive addMatch' memAdded driveInsertedSound addedHasDrive
@ -99,11 +95,10 @@ listenDevices cl = do
runRemovableMon runRemovableMon
:: ( HasClient (DBusEnv env) :: ( HasClient (DBusEnv env)
, HasLogFunc (DBusEnv env SysClient)
, MonadReader env m , MonadReader env m
, MonadUnliftIO m , MonadUnliftIO m
) )
=> Maybe SysClient => Maybe NamedSysConnection
-> Sometimes (m ()) -> Sometimes (m ())
runRemovableMon cl = runRemovableMon cl =
sometimesDBus cl "removeable device monitor" "dbus monitor" deps listenDevices sometimesDBus cl "removeable device monitor" "dbus monitor" deps listenDevices

View File

@ -1,6 +1,3 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- DBus module for X11 screensave/DPMS control -- DBus module for X11 screensave/DPMS control
@ -96,7 +93,7 @@ bodyGetCurrentState _ = Nothing
exportScreensaver exportScreensaver
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m) :: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> Maybe SesClient => Maybe NamedSesConnection
-> Sometimes (m (), m ()) -> Sometimes (m (), m ())
exportScreensaver ses = exportScreensaver ses =
sometimesDBus ses "screensaver toggle" "xset" (toAnd_ bus ssx) cmd sometimesDBus ses "screensaver toggle" "xset" (toAnd_ bus ssx) cmd
@ -122,19 +119,19 @@ exportScreensaver ses =
} }
] ]
} }
bus = Bus [] xmonadBusName bus = Bus [] xmonadSesBusName
ssx = DBusIO $ sysExe [Package Official "xorg-xset"] ssExecutable ssx = DBusIO $ sysExe [Package Official "xorg-xset"] ssExecutable
callToggle callToggle
:: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m) :: (HasClient (DBusEnv env), MonadReader env m, MonadUnliftIO m)
=> Maybe SesClient => Maybe NamedSesConnection
-> Sometimes (m ()) -> Sometimes (m ())
callToggle = callToggle =
sometimesEndpoint sometimesEndpoint
"screensaver toggle" "screensaver toggle"
"dbus switch" "dbus switch"
[] []
xmonadBusName xmonadSesBusName
ssPath ssPath
interface interface
memToggle memToggle
@ -143,12 +140,11 @@ callQuery
:: (HasClient env, MonadReader (env SesClient) m, MonadUnliftIO m) :: (HasClient env, MonadReader (env SesClient) m, MonadUnliftIO m)
=> m (Maybe SSState) => m (Maybe SSState)
callQuery = do callQuery = do
reply <- callMethod xmonadBusName ssPath interface memQuery reply <- callMethod xmonadSesBusName ssPath interface memQuery
return $ either (const Nothing) bodyGetCurrentState reply return $ either (const Nothing) bodyGetCurrentState reply
matchSignal matchSignal
:: ( HasLogFunc (env SesClient) :: ( HasClient env
, HasClient env
, MonadReader (env SesClient) m , MonadReader (env SesClient) m
, MonadUnliftIO m , MonadUnliftIO m
) )
@ -161,4 +157,4 @@ matchSignal cb =
(cb . bodyGetCurrentState) (cb . bodyGetCurrentState)
ssSignalDep :: DBusDependency_ SesClient ssSignalDep :: DBusDependency_ SesClient
ssSignalDep = Endpoint [] xmonadBusName ssPath interface $ Signal_ memState ssSignalDep = Endpoint [] xmonadSesBusName ssPath interface $ Signal_ memState

View File

@ -1,5 +1,3 @@
{-# LANGUAGE ViewPatterns #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Random IO-ish functions used throughtout xmonad -- Random IO-ish functions used throughtout xmonad
-- --
@ -41,7 +39,7 @@ import System.Process
-- read -- read
readInt :: MonadIO m => (Read a, Integral a) => FilePath -> m a readInt :: MonadIO m => (Read a, Integral a) => FilePath -> m a
readInt = fmap (read . takeWhile isDigit . T.unpack) . readFileUtf8 readInt = fmap (fromMaybe 0 . readMaybe . takeWhile isDigit . T.unpack) . readFileUtf8
readBool :: MonadIO m => FilePath -> m Bool readBool :: MonadIO m => FilePath -> m Bool
readBool = fmap (== (1 :: Int)) . readInt readBool = fmap (== (1 :: Int)) . readInt
@ -49,7 +47,7 @@ readBool = fmap (== (1 :: Int)) . readInt
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- write -- write
writeInt :: MonadIO m => (Show a, Integral a) => FilePath -> a -> m () writeInt :: (MonadIO m, Show a) => FilePath -> a -> m ()
writeInt f = writeFileUtf8 f . T.pack . show writeInt f = writeFileUtf8 f . T.pack . show
writeBool :: MonadIO m => FilePath -> Bool -> m () writeBool :: MonadIO m => FilePath -> Bool -> m ()
@ -62,7 +60,7 @@ writeBool f b = writeInt f ((if b then 1 else 0) :: Int)
-- value. Assume that the file being read has a min of 0 and an unchanging max -- value. Assume that the file being read has a min of 0 and an unchanging max
-- given by a runtime argument, which is scaled linearly to the range 0-100 -- given by a runtime argument, which is scaled linearly to the range 0-100
-- (percent). -- (percent).
rawToPercent :: (Integral a, Integral b, Read b, RealFrac c) => (a, a) -> b -> c rawToPercent :: (Integral a, Integral b, RealFrac c) => (a, a) -> b -> c
rawToPercent (lower, upper) raw = rawToPercent (lower, upper) raw =
100 * (fromIntegral raw - fromIntegral lower) / fromIntegral (upper - lower) 100 * (fromIntegral raw - fromIntegral lower) / fromIntegral (upper - lower)

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Functions for formatting and sending notifications -- Functions for formatting and sending notifications
-- --

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-- Functions for formatting and spawning shell commands -- Functions for formatting and spawning shell commands
module XMonad.Internal.Shell module XMonad.Internal.Shell
@ -85,10 +83,7 @@ spawn :: MonadIO m => T.Text -> m ()
spawn = X.spawn . T.unpack spawn = X.spawn . T.unpack
-- | Run 'XMonad.Run.Utils.spawnPipe' with 'Text' input. -- | Run 'XMonad.Run.Utils.spawnPipe' with 'Text' input.
spawnPipe spawnPipe :: MonadUnliftIO m => T.Text -> m Handle
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m)
=> T.Text
-> m Handle
spawnPipe = liftIO . XR.spawnPipe . T.unpack spawnPipe = liftIO . XR.spawnPipe . T.unpack
-- spawnPipeRW -- spawnPipeRW

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Theme for XMonad and Xmobar -- Theme for XMonad and Xmobar
@ -33,6 +31,7 @@ where
import Data.Colour import Data.Colour
import Data.Colour.SRGB import Data.Colour.SRGB
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import qualified XMonad.Layout.Decoration as D import qualified XMonad.Layout.Decoration as D
import qualified XMonad.Prompt as P import qualified XMonad.Prompt as P

View File

@ -0,0 +1,155 @@
--------------------------------------------------------------------------------
-- NetworkManager Connection plugin
--
-- Show active connections of varying types.
--
-- This plugin exclusively monitors the */ActiveConnection/* paths in the
-- NetworkManager DBus path for state changes. It does not pin these to any
-- particular interface but instead looks at all connections equally and filters
-- based on their Type (ethernet, wifi, VPN, etc). For many use cases this will
-- track well enough with either one or a collection of similar interfaces (ie
-- all ethernet or all wifi).
module Xmobar.Plugins.ActiveConnection
( ActiveConnection (..)
, devDep
, connAlias
)
where
import DBus
import Data.Internal.DBus
import Data.Internal.XIO
import RIO
import qualified RIO.Map as M
import qualified RIO.NonEmpty as NE
import qualified RIO.Text as T
import XMonad.Internal.Command.Desktop
import XMonad.Internal.DBus.Common
import Xmobar
import Xmobar.Plugins.Common
newtype ActiveConnection
= ActiveConnection (NE.NonEmpty T.Text, T.Text, Colors)
deriving (Read, Show)
connAlias :: NE.NonEmpty T.Text -> T.Text
connAlias = T.intercalate "_" . NE.toList
instance Exec ActiveConnection where
alias (ActiveConnection (contypes, _, _)) = T.unpack $ connAlias contypes
start (ActiveConnection (contypes, text, colors)) cb =
withDBusClientConnection cb Nothing (Just "ethernet.log") $ \c -> do
let dpy cb' = displayMaybe cb' formatter . Just =<< readState
i <- withDIO c $ initialState contypes
s <- newMVar i
let mapEnv c' = mapRIO (PluginEnv c' s dpy cb)
mapEnv c $ addListener mapEnv >> pluginDisplay
where
formatter names = return $ case names of
[] -> colorText colors False text
xs -> T.unwords [colorText colors True text, T.intercalate "|" xs]
addListener mapEnv = do
res <- matchSignalFull nmBus Nothing (Just nmActiveInterface) (Just stateChanged)
case res of
Nothing -> logError "could not start listener"
Just rule ->
-- Start a new connection and RIO process since the parent thread
-- will have died before these callbacks fire, therefore the logging
-- file descriptor will be closed. This makes a new one
-- TODO can I recycle the client?
void $
addMatchCallbackSignal rule $ \sig ->
withDBusClientConnection cb Nothing (Just "ethernet-cb.log") $ \c' ->
mapEnv c' $
testActiveType contypes sig
nmBus :: BusName
nmBus = "org.freedesktop.NetworkManager"
nmPath :: ObjectPath
nmPath = "/org/freedesktop/NetworkManager"
nmInterface :: InterfaceName
nmInterface = "org.freedesktop.NetworkManager"
nmObjectTreePath :: ObjectPath
nmObjectTreePath = "/org/freedesktop"
nmActiveInterface :: InterfaceName
nmActiveInterface = "org.freedesktop.NetworkManager.Connection.Active"
stateChanged :: MemberName
stateChanged = "StateChanged"
-- semi-random method to test to ensure that NetworkManager is up and on DBus
devDep :: DBusDependency_ SysClient
devDep =
Endpoint networkManagerPkgs networkManagerBus nmPath nmInterface $
Method_ "GetDeviceByIpIface"
type EthIO = PluginIO EthState SysClient
type EthState = M.Map ObjectPath T.Text
getConnectionProp :: MemberName -> ObjectPath -> EthIO [Variant]
getConnectionProp prop path = callPropertyGet nmBus path nmActiveInterface prop
getConnectionId :: ObjectPath -> EthIO (Maybe T.Text)
getConnectionId = fmap fromSingletonVariant . getConnectionProp "Id"
getConnectionType :: ObjectPath -> EthIO (Maybe T.Text)
getConnectionType = fmap fromSingletonVariant . getConnectionProp "Type"
updateConnected :: NE.NonEmpty T.Text -> ObjectPath -> EthIO ()
updateConnected contypes path = do
typeRes <- getConnectionType path
logMaybe "type" getId typeRes
where
path' = displayBytesUtf8 $ T.encodeUtf8 $ T.pack $ formatObjectPath path
logMaybe what = maybe (logError ("could not get " <> what <> " for " <> path'))
getId contype = do
when (contype `elem` contypes) $ do
idRes <- getConnectionId path
logMaybe "ID" insertId idRes
insertId i = do
s <- asks plugState
modifyMVar_ s $ return . M.insert path i
updateDisconnected :: ObjectPath -> EthIO ()
updateDisconnected path = do
s <- asks plugState
modifyMVar_ s $ return . M.delete path
testActiveType :: NE.NonEmpty T.Text -> Signal -> EthIO ()
testActiveType contypes sig = do
case signalBody sig of
[state, _] -> case fromVariant state of
Just (2 :: Word32) -> updateConnected contypes path >> pluginDisplay
Just 4 -> updateDisconnected path >> pluginDisplay
_ -> return ()
_ -> return ()
where
path = signalPath sig
initialState
:: ( SafeClient c
, MonadUnliftIO m
, MonadReader (env c) m
, HasClient env
, HasLogFunc (env c)
)
=> NE.NonEmpty T.Text
-> m EthState
initialState contypes =
M.mapMaybe go <$> callGetManagedObjects nmBus nmObjectTreePath
where
go = getId <=< M.lookup nmActiveInterface
getId m =
fromVariant
=<< (\t -> if t `elem` contypes then M.lookup "Id" m else Nothing)
=<< fromVariant
=<< M.lookup "Type" m
readState :: EthIO [T.Text]
readState = M.elems <$> (readMVar =<< asks plugState)

View File

@ -1,11 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
-- Common backlight plugin bits -- Common backlight plugin bits
-- --
-- Use the custom DBus interface exported by the XMonad process so I can react -- Use the custom DBus interface exported by the XMonad process so I can react
-- to signals spawned by commands -- to signals spawned by commands
module Xmobar.Plugins.BacklightCommon (startBacklight) where module Xmobar.Plugins.BacklightCommon (startBacklight) where
import DBus
import Data.Internal.DBus import Data.Internal.DBus
import RIO import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
@ -13,14 +12,15 @@ import Xmobar.Plugins.Common
startBacklight startBacklight
:: (MonadUnliftIO m, RealFrac a) :: (MonadUnliftIO m, RealFrac a)
=> Maybe FilePath => Maybe BusName
-> Maybe FilePath
-> ((Maybe a -> DIO SimpleApp SesClient ()) -> DIO SimpleApp SesClient ()) -> ((Maybe a -> DIO SimpleApp SesClient ()) -> DIO SimpleApp SesClient ())
-> DIO SimpleApp SesClient (Maybe a) -> DIO SimpleApp SesClient (Maybe a)
-> T.Text -> T.Text
-> Callback -> Callback
-> m () -> m ()
startBacklight name matchSignal callGetBrightness icon cb = do startBacklight n name matchSignal callGetBrightness icon cb = do
withDBusClientConnection cb name $ \c -> withDIO c $ do withDBusClientConnection cb n name $ \c -> withDIO c $ do
matchSignal dpy matchSignal dpy
dpy =<< callGetBrightness dpy =<< callGetBrightness
where where

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Bluetooth plugin -- Bluetooth plugin
-- --
@ -9,28 +7,18 @@
-- Manager. The adapter is located at path "/org/bluez/hci<X>" where X is -- Manager. The adapter is located at path "/org/bluez/hci<X>" where X is
-- usually 0, and each device is "/org/bluez/hci<X>/<MAC_ADDRESS>". -- usually 0, and each device is "/org/bluez/hci<X>/<MAC_ADDRESS>".
-- --
-- This plugin will reflect if the adapter is powered and if any device is -- Simple and somewhat crude way to do this is to have two monitors, one
-- connected to it. The rough outline for this procedure: -- watching the powered state of the adaptor and one listening for connection
-- 1) get the adapter from the object manager -- changes. The former is easy since this is just one /org/bluez/hciX. For the
-- 2) get all devices associated with the adapter using the object interface -- latter, each 'Connected' property is embedded in each individual device path
-- 3) determine if the adapter is powered -- on `org.bluez.Device1', so just watch the entire bluez bus for property
-- 4) determine if any devices are connected -- changes and filter those that correspond to the aforementioned
-- 5) format the icon; powered vs not powered controls the color and connected -- interface/property. Track all this in a state which keeps the powered
-- vs not connected controls the icon (connected bluetooth symbol has two -- property and a running list of connected devices.
-- 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 -- TODO also not sure if I need to care about multiple adapters and/or the
-- adapter changing. -- adapter changing. For now it should just get the first adaptor and only pay
-- attention to devices associated with it.
module Xmobar.Plugins.Bluetooth module Xmobar.Plugins.Bluetooth
( Bluetooth (..) ( Bluetooth (..)
@ -47,6 +35,7 @@ import RIO
import RIO.FilePath import RIO.FilePath
import RIO.List import RIO.List
import qualified RIO.Map as M import qualified RIO.Map as M
import qualified RIO.Set as S
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Internal.DBus.Common import XMonad.Internal.DBus.Common
import Xmobar import Xmobar
@ -65,32 +54,28 @@ data Bluetooth = Bluetooth Icons Colors deriving (Read, Show)
instance Exec Bluetooth where instance Exec Bluetooth where
alias (Bluetooth _ _) = T.unpack btAlias alias (Bluetooth _ _) = T.unpack btAlias
start (Bluetooth icons colors) cb = start (Bluetooth icons colors) cb =
withDBusClientConnection cb (Just "bluetooth.log") $ startAdapter icons colors cb withDBusClientConnection cb Nothing (Just "bluetooth.log") $
startAdapter icons colors cb
startAdapter startAdapter
:: Icons :: Icons
-> Colors -> Colors
-> Callback -> Callback
-> SysClient -> NamedSysConnection
-> RIO SimpleApp () -> RIO SimpleApp ()
startAdapter is cs cb cl = do startAdapter is cs cb cl = do
state <- newMVar emptyState state <- newMVar emptyState
let dpy = displayIcon cb (iconFormatter is cs) let dpy cb' = displayIcon cb' (iconFormatter is cs)
mapRIO (BTEnv cl state dpy) $ do mapRIO (PluginEnv cl state dpy cb) $ do
ot <- getBtObjectTree ot <- getBtObjectTree
case findAdapter ot of case findAdaptor ot of
Nothing -> logError "could not find bluetooth adapter" Nothing -> logError "could not find bluetooth adapter"
Just adapter -> do Just adaptor -> do
-- set up adapter initAdapterState adaptor
initAdapter adapter initDevicesState adaptor ot
void $ addAdaptorListener adapter startAdaptorListener adaptor
-- set up devices on the adapter (and listeners for adding/removing devices) startConnectedListener adaptor
let devices = findDevices adapter ot pluginDisplay
addDeviceAddedListener adapter
addDeviceRemovedListener adapter
forM_ devices $ \d -> addAndInitDevice d
-- after setting things up, show the icon based on the initialized state
dpy
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Icon Display -- Icon Display
@ -115,43 +100,18 @@ iconFormatter (iconConn, iconDisc) cs powered connected =
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Connection State -- 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 c = BTEnv type BTIO = PluginIO BtState SysClient
{ btClient :: !c
, btState :: !(MVar BtState)
, btDisplay :: !(BTIO ())
, btEnv :: !SimpleApp
}
instance HasClient BTEnv where
clientL = lens btClient (\x y -> x {btClient = y})
instance HasLogFunc (BTEnv a) where
logFuncL = lens btEnv (\x y -> x {btEnv = y}) . logFuncL
type BTIO = RIO (BTEnv SysClient)
data BTDevice = BTDevice
{ btDevConnected :: Maybe Bool
, btDevSigHandler :: SignalHandler
}
type ConnectedDevices = M.Map ObjectPath BTDevice
data BtState = BtState data BtState = BtState
{ btDevices :: ConnectedDevices { btDevices :: S.Set ObjectPath
, btPowered :: Maybe Bool , btPowered :: Maybe Bool
} }
emptyState :: BtState emptyState :: BtState
emptyState = emptyState =
BtState BtState
{ btDevices = M.empty { btDevices = S.empty
, btPowered = Nothing , btPowered = Nothing
} }
@ -159,24 +119,33 @@ readState :: BTIO (Maybe Bool, Bool)
readState = do readState = do
p <- readPowered p <- readPowered
c <- readDevices c <- readDevices
return (p, anyDevicesConnected c) return (p, not $ null c)
modifyState :: (BtState -> BTIO (BtState, a)) -> BTIO a modifyState :: (BtState -> BTIO (BtState, a)) -> BTIO a
modifyState f = do modifyState f = do
m <- asks btState m <- asks plugState
modifyMVar m f modifyMVar m f
beforeDisplay :: BTIO () -> BTIO () beforeDisplay :: BTIO () -> BTIO ()
beforeDisplay f = f >> join (asks btDisplay) beforeDisplay f = f >> pluginDisplay
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Object manager -- Object manager
findAdapter :: ObjectTree -> Maybe ObjectPath findAdaptor :: ObjectTree -> Maybe ObjectPath
findAdapter = find (("/org/bluez/hci" `isPrefixOf`) . formatObjectPath) . M.keys findAdaptor = find (("/org/bluez/hci" `isPrefixOf`) . formatObjectPath) . M.keys
findDevices :: ObjectPath -> ObjectTree -> [ObjectPath] -- | Search the object tree for devices which are in a connected state.
findDevices adapter = filter (adaptorHasDevice adapter) . M.keys -- Return the object path for said devices.
findConnectedDevices :: ObjectPath -> ObjectTree -> [ObjectPath]
findConnectedDevices adaptor =
filter (adaptorHasDevice adaptor) . M.keys . M.filter isConnectedDev
where
isConnectedDev m = Just True == lookupState m
lookupState =
fromVariant
<=< M.lookup (memberNameT devConnected)
<=< M.lookup devInterface
adaptorHasDevice :: ObjectPath -> ObjectPath -> Bool adaptorHasDevice :: ObjectPath -> ObjectPath -> Bool
adaptorHasDevice adaptor device = case splitPathNoRoot device of adaptorHasDevice adaptor device = case splitPathNoRoot device of
@ -199,49 +168,14 @@ getBtObjectTree = callGetManagedObjects btBus btOMPath
btOMPath :: ObjectPath btOMPath :: ObjectPath
btOMPath = objectPath_ "/" btOMPath = objectPath_ "/"
addBtOMListener
:: ( HasClient env
, SafeClient c
, MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m
)
=> SignalCallback m
-> m ()
addBtOMListener sc = void $ addInterfaceAddedListener btBus btOMPath sc
addDeviceAddedListener :: ObjectPath -> BTIO ()
addDeviceAddedListener adapter = addBtOMListener addDevice
where
addDevice = pathCallback adapter $ \d ->
addAndInitDevice d
addDeviceRemovedListener :: ObjectPath -> BTIO ()
addDeviceRemovedListener adapter =
addBtOMListener remDevice
where
remDevice = pathCallback adapter $ \d -> do
old <- removeDevice d
cl <- asks btClient
forM_ old $ liftIO . removeMatch (toClient cl) . btDevSigHandler
pathCallback :: ObjectPath -> (ObjectPath -> BTIO ()) -> SignalCallback BTIO
pathCallback adapter f [device, _] = forM_ (fromVariant device) $ \d -> do
when (adaptorHasDevice adapter d) $ beforeDisplay $ f d
pathCallback _ _ _ = return ()
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Adapter -- Adapter
initAdapter :: ObjectPath -> BTIO () -- | Get powered state of adaptor and log the result
initAdapter adapter = do initAdapterState :: ObjectPath -> BTIO ()
initAdapterState adapter = do
reply <- callGetPowered adapter reply <- callGetPowered adapter
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 putPowered $ fromSingletonVariant reply
where
adapter_ = displayWrapQuote $ displayObjectPath adapter
matchBTProperty matchBTProperty
:: ( SafeClient c :: ( SafeClient c
@ -254,40 +188,23 @@ matchBTProperty
-> m (Maybe MatchRule) -> m (Maybe MatchRule)
matchBTProperty p = matchPropertyFull btBus (Just p) matchBTProperty p = matchPropertyFull btBus (Just p)
withBTPropertyRule -- | Start a listener that monitors changes to the powered state of an adaptor
:: ( SafeClient c startAdaptorListener :: ObjectPath -> BTIO ()
, MonadReader (env c) m startAdaptorListener adaptor = do
, HasLogFunc (env c) res <- matchBTProperty adaptor
, HasClient env
, MonadUnliftIO m
, IsVariant a
)
=> ObjectPath
-> (Maybe a -> m ())
-> InterfaceName
-> T.Text
-> m (Maybe SignalHandler)
withBTPropertyRule path update iface prop = do
res <- matchBTProperty path
case res of case res of
Just rule -> Just <$> addMatchCallback rule (signalToUpdate . matchConnected) Just rule -> void $ addMatchCallback rule callback
Nothing -> do Nothing -> do
logError $ logError $
"could not add listener for prop " "could not add listener for prop "
<> prop_ <> displayMemberName adaptorPowered
<> " on path " <> " on path "
<> path_ <> displayObjectPath adaptor
return Nothing
where
path_ = displayObjectPath path
prop_ = Utf8Builder $ encodeUtf8Builder prop
signalToUpdate = withSignalMatch update
matchConnected = matchPropertyChanged iface prop
addAdaptorListener :: ObjectPath -> BTIO (Maybe SignalHandler)
addAdaptorListener adaptor =
withBTPropertyRule adaptor procMatch adapterInterface adaptorPowered
where where
callback sig =
withNestedDBusClientConnection Nothing Nothing $
withSignalMatch procMatch $
matchPropertyChanged adaptorInterface adaptorPowered sig
procMatch = beforeDisplay . putPowered procMatch = beforeDisplay . putPowered
callGetPowered callGetPowered
@ -300,88 +217,58 @@ callGetPowered
=> ObjectPath => ObjectPath
-> m [Variant] -> m [Variant]
callGetPowered adapter = callGetPowered adapter =
callPropertyGet btBus adapter adapterInterface $ callPropertyGet btBus adapter adaptorInterface adaptorPowered
memberName_ $
T.unpack adaptorPowered
putPowered :: Maybe Bool -> BTIO () putPowered :: Maybe Bool -> BTIO ()
putPowered ds = modifyState $ \s -> return (s {btPowered = ds}, ()) putPowered ds = modifyState $ \s -> return (s {btPowered = ds}, ())
readPowered :: BTIO (Maybe Bool) readPowered :: BTIO (Maybe Bool)
readPowered = fmap btPowered $ readMVar =<< asks btState readPowered = fmap btPowered $ readMVar =<< asks plugState
adapterInterface :: InterfaceName adaptorInterface :: InterfaceName
adapterInterface = interfaceName_ "org.bluez.Adapter1" adaptorInterface = interfaceName_ "org.bluez.Adapter1"
adaptorPowered :: T.Text adaptorPowered :: MemberName
adaptorPowered = "Powered" adaptorPowered = "Powered"
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Devices -- Devices
addAndInitDevice :: ObjectPath -> BTIO () initDevicesState :: ObjectPath -> ObjectTree -> BTIO ()
addAndInitDevice device = do initDevicesState adaptor ot = do
res <- addDeviceListener device let devices = findConnectedDevices adaptor ot
case res of modifyState $ \s -> return (s {btDevices = S.fromList devices}, ())
Just handler -> do
logInfo $ "initializing device at path " <> device_ startConnectedListener :: ObjectPath -> BTIO ()
initDevice handler device startConnectedListener adaptor = do
Nothing -> logError $ "could not initialize device at path " <> device_ reply <- matchPropertyFull btBus Nothing
case reply of
Just rule -> do
void $ addMatchCallbackSignal rule callback
logInfo $ "Started listening for device connections on " <> adaptor_
Nothing -> logError "Could not listen for connection changes"
where where
device_ = displayWrapQuote $ displayObjectPath device adaptor_ = displayWrapQuote $ displayObjectPath adaptor
callback sig =
withNestedDBusClientConnection Nothing Nothing $ do
let devpath = signalPath sig
when (adaptorHasDevice adaptor devpath) $
withSignalMatch (update devpath) $
matchConnected $
signalBody sig
matchConnected = matchPropertyChanged devInterface devConnected
update _ Nothing = return ()
update devpath (Just x) = do
let f = if x then S.insert else S.delete
beforeDisplay $
modifyState $
\s -> return (s {btDevices = f devpath $ btDevices s}, ())
initDevice :: SignalHandler -> ObjectPath -> BTIO () readDevices :: BTIO (S.Set ObjectPath)
initDevice sh device = do readDevices = fmap btDevices $ readMVar =<< asks plugState
reply <- callGetConnected device
void $
insertDevice device $
BTDevice
{ btDevConnected = fromVariant =<< listToMaybe reply
, btDevSigHandler = sh
}
addDeviceListener :: ObjectPath -> BTIO (Maybe SignalHandler)
addDeviceListener device =
withBTPropertyRule device procMatch devInterface devConnected
where
procMatch = beforeDisplay . void . updateDevice device
callGetConnected
:: ( SafeClient c
, HasClient env
, MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m
)
=> ObjectPath
-> m [Variant]
callGetConnected p =
callPropertyGet btBus p devInterface $
memberName_ (T.unpack devConnected)
insertDevice :: ObjectPath -> BTDevice -> BTIO Bool
insertDevice device dev = modifyState $ \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 = modifyState $ \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 = modifyState $ \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
devInterface = interfaceName_ "org.bluez.Device1" devInterface = interfaceName_ "org.bluez.Device1"
devConnected :: T.Text devConnected :: MemberName
devConnected = "Connected" devConnected = "Connected"

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Clevo Keyboard plugin -- Clevo Keyboard plugin
-- --
@ -12,6 +10,7 @@ module Xmobar.Plugins.ClevoKeyboard
) )
where where
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Internal.DBus.Brightness.ClevoKeyboard import XMonad.Internal.DBus.Brightness.ClevoKeyboard
import Xmobar import Xmobar
@ -25,4 +24,9 @@ ckAlias = "clevokeyboard"
instance Exec ClevoKeyboard where instance Exec ClevoKeyboard where
alias (ClevoKeyboard _) = T.unpack ckAlias alias (ClevoKeyboard _) = T.unpack ckAlias
start (ClevoKeyboard icon) = start (ClevoKeyboard icon) =
startBacklight (Just "clevo_kbd.log") matchSignalCK callGetBrightnessCK icon startBacklight
(Just "org.xmobar.clevo")
(Just "clevo_kbd.log")
matchSignalCK
callGetBrightnessCK
icon

View File

@ -1,17 +1,19 @@
{-# LANGUAGE OverloadedStrings #-}
module Xmobar.Plugins.Common module Xmobar.Plugins.Common
( colorText ( colorText
, startListener , startListener
, procSignalMatch , procSignalMatch
, na , na
, fromSingletonVariant , fromSingletonVariant
, withNestedDBusClientConnection
, withDBusClientConnection , withDBusClientConnection
, Callback , Callback
, Colors (..) , Colors (..)
, displayMaybe , displayMaybe
, displayMaybe' , displayMaybe'
, xmobarFGColor , xmobarFGColor
, PluginEnv (..)
, PluginIO
, pluginDisplay
) )
where where
@ -23,6 +25,28 @@ import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Hooks.DynamicLog (xmobarColor) import XMonad.Hooks.DynamicLog (xmobarColor)
data PluginEnv s c = PluginEnv
{ plugClient :: !(NamedConnection c)
, plugState :: !(MVar s)
, plugDisplay :: !(Callback -> PluginIO s c ())
, plugCallback :: !Callback
, plugEnv :: !SimpleApp
}
pluginDisplay :: PluginIO s c ()
pluginDisplay = do
cb <- asks plugCallback
dpy <- asks plugDisplay
dpy cb
type PluginIO s c = RIO (PluginEnv s c)
instance HasClient (PluginEnv s) where
clientL = lens plugClient (\x y -> x {plugClient = y})
instance HasLogFunc (PluginEnv s c) where
logFuncL = lens plugEnv (\x y -> x {plugEnv = y}) . logFuncL
-- use string here since all the callbacks in xmobar use strings :( -- use string here since all the callbacks in xmobar use strings :(
type Callback = String -> IO () type Callback = String -> IO ()
@ -33,8 +57,7 @@ data Colors = Colors
deriving (Eq, Show, Read) deriving (Eq, Show, Read)
startListener startListener
:: ( HasLogFunc (env c) :: ( HasClient env
, HasClient env
, MonadReader (env c) m , MonadReader (env c) m
, MonadUnliftIO m , MonadUnliftIO m
, SafeClient c , SafeClient c
@ -76,14 +99,42 @@ displayMaybe' cb = maybe (liftIO $ cb $ T.unpack na)
withDBusClientConnection withDBusClientConnection
:: (MonadUnliftIO m, SafeClient c) :: (MonadUnliftIO m, SafeClient c)
=> Callback => Callback
-> Maybe BusName
-> Maybe FilePath -> Maybe FilePath
-> (c -> RIO SimpleApp ()) -> (NamedConnection c -> RIO SimpleApp ())
-> m () -> m ()
withDBusClientConnection cb logfile f = withDBusClientConnection cb n logfile f =
maybe (run stderr) (`withLogFile` run) logfile maybe (run stderr) (`withLogFile` run) logfile
where where
run h = do run h = do
logOpts <- setLogVerboseFormat True . setLogUseTime True <$> logOptionsHandle h False logOpts <- setLogVerboseFormat True . setLogUseTime True <$> logOptionsHandle h False
withLogFunc logOpts $ \lf -> do withLogFunc logOpts $ \lf -> do
env <- mkSimpleApp lf Nothing env <- mkSimpleApp lf Nothing
runRIO env $ displayMaybe' cb f =<< getDBusClient runRIO env $ displayMaybe' cb f =<< getDBusClient n
-- | Run a plugin action with a new DBus client and logfile path. This is
-- necessary for DBus callbacks which run in separate threads, which will
-- usually fire when the parent thread already exited and killed off its DBus
-- connection and closed its logfile. NOTE: unlike 'withDBusClientConnection'
-- this function will open and new logfile and client connection and close both
-- on completion. 'withDBusClientConnection' will only close the log file but
-- keep the client connection active upon termination; this client will only be
-- killed when the entire process is killed. This distinction is important
-- because callbacks only need ephemeral connections, while listeners (started
-- with 'withDBusClientConnection') need long-lasting connections.
withNestedDBusClientConnection
:: (MonadUnliftIO m, SafeClient c, MonadReader (PluginEnv s c) m)
=> Maybe BusName
-> Maybe FilePath
-> PluginIO s c ()
-> m ()
withNestedDBusClientConnection n logfile f = do
dpy <- asks plugDisplay
s <- asks plugState
cb <- asks plugCallback
let run h = do
logOpts <- setLogVerboseFormat True . setLogUseTime True <$> logOptionsHandle h False
withLogFunc logOpts $ \lf -> do
env <- mkSimpleApp lf Nothing
runRIO env $ withDBusClient_ n $ \cl -> mapRIO (PluginEnv cl s dpy cb) f
maybe (run stderr) (`withLogFile` run) logfile

View File

@ -1,89 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
--------------------------------------------------------------------------------
-- Device plugin
--
-- Display different text depending on whether or not the interface has
-- connectivity
module Xmobar.Plugins.Device
( Device (..)
, devDep
)
where
import DBus
import Data.Internal.DBus
import Data.Internal.XIO
import RIO
import qualified RIO.Text as T
import XMonad.Internal.Command.Desktop
import XMonad.Internal.DBus.Common
import Xmobar
import Xmobar.Plugins.Common
newtype Device = Device (T.Text, T.Text, Colors) deriving (Read, Show)
nmPath :: ObjectPath
nmPath = objectPath_ "/org/freedesktop/NetworkManager"
nmInterface :: InterfaceName
nmInterface = interfaceName_ "org.freedesktop.NetworkManager"
nmDeviceInterface :: InterfaceName
nmDeviceInterface = interfaceName_ "org.freedesktop.NetworkManager.Device"
getByIP :: MemberName
getByIP = memberName_ "GetDeviceByIpIface"
devSignal :: T.Text
devSignal = "Ip4Connectivity"
devDep :: DBusDependency_ SysClient
devDep =
Endpoint networkManagerPkgs networkManagerBus nmPath nmInterface $
Method_ getByIP
getDevice
:: (SafeClient c, HasClient env, MonadReader (env c) m, MonadUnliftIO m)
=> T.Text
-> m (Maybe ObjectPath)
getDevice iface = bodyToMaybe <$> callMethod' mc
where
mc =
(methodCallBus networkManagerBus nmPath nmInterface getByIP)
{ methodCallBody = [toVariant iface]
}
getDeviceConnected
:: ( SafeClient c
, HasClient env
, MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m
)
=> ObjectPath
-> m [Variant]
getDeviceConnected path =
callPropertyGet networkManagerBus path nmDeviceInterface $
memberName_ $
T.unpack devSignal
matchStatus :: [Variant] -> SignalMatch Word32
matchStatus = matchPropertyChanged nmDeviceInterface devSignal
instance Exec Device where
alias (Device (iface, _, _)) = T.unpack iface
start (Device (iface, text, colors)) cb =
withDBusClientConnection cb logName $ \(sys :: SysClient) -> withDIO sys $ do
path <- getDevice iface
displayMaybe' cb listener path
where
logName = Just $ T.unpack $ T.concat ["device@", iface, ".log"]
listener path = do
res <- matchPropertyFull networkManagerBus (Just path)
case res of
Just rule -> startListener rule (getDeviceConnected path) matchStatus chooseColor' cb
Nothing -> logError "could not start listener"
chooseColor' = return . (\s -> colorText colors s text) . (> 1)

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Intel backlight plugin -- Intel backlight plugin
-- --
@ -12,6 +10,7 @@ module Xmobar.Plugins.IntelBacklight
) )
where where
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Internal.DBus.Brightness.IntelBacklight import XMonad.Internal.DBus.Brightness.IntelBacklight
import Xmobar import Xmobar
@ -25,4 +24,9 @@ blAlias = "intelbacklight"
instance Exec IntelBacklight where instance Exec IntelBacklight where
alias (IntelBacklight _) = T.unpack blAlias alias (IntelBacklight _) = T.unpack blAlias
start (IntelBacklight icon) = start (IntelBacklight icon) =
startBacklight (Just "intel_backlight.log") matchSignalIB callGetBrightnessIB icon startBacklight
(Just "org.xmobar.intelbacklight")
(Just "intel_backlight.log")
matchSignalIB
callGetBrightnessIB
icon

View File

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Screensaver plugin -- Screensaver plugin
-- --
@ -13,6 +11,7 @@ module Xmobar.Plugins.Screensaver
where where
import Data.Internal.DBus import Data.Internal.DBus
import RIO
import qualified RIO.Text as T import qualified RIO.Text as T
import XMonad.Internal.DBus.Screensaver import XMonad.Internal.DBus.Screensaver
import Xmobar import Xmobar
@ -26,8 +25,12 @@ ssAlias = "screensaver"
instance Exec Screensaver where instance Exec Screensaver where
alias (Screensaver _) = T.unpack ssAlias alias (Screensaver _) = T.unpack ssAlias
start (Screensaver (text, colors)) cb = start (Screensaver (text, colors)) cb =
withDBusClientConnection cb (Just "screensaver.log") $ \cl -> withDIO cl $ do withDBusClientConnection
matchSignal dpy cb
dpy =<< callQuery (Just "org.xmobar.screensaver")
(Just "screensaver.log")
$ \cl -> withDIO cl $ do
matchSignal dpy
dpy =<< callQuery
where where
dpy = displayMaybe cb $ return . (\s -> colorText colors s text) dpy = displayMaybe cb $ return . (\s -> colorText colors s text)

View File

@ -1,173 +0,0 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
--------------------------------------------------------------------------------
-- VPN plugin
--
-- Use the networkmanager to detect when a VPN interface is added or removed.
-- Specifically, monitor the object tree to detect paths with the interface
-- "org.freedesktop.NetworkManager.Device.Tun".
module Xmobar.Plugins.VPN
( VPN (..)
, vpnAlias
, vpnDep
)
where
import DBus
import Data.Internal.DBus
import Data.Internal.XIO
import RIO
import qualified RIO.Map as M
import qualified RIO.Set as S
import qualified RIO.Text as T
import XMonad.Internal.Command.Desktop
import XMonad.Internal.DBus.Common
import Xmobar
import Xmobar.Plugins.Common
newtype VPN = VPN (T.Text, Colors) deriving (Read, Show)
instance Exec VPN where
alias (VPN _) = T.unpack vpnAlias
start (VPN (text, colors)) cb =
withDBusClientConnection cb (Just "vpn.log") $ \c -> do
let dpy = displayMaybe cb iconFormatter . Just =<< readState
s <- newEmptyMVar
mapRIO (VEnv c s dpy) $ do
initState
vpnAddedListener addedCallback
vpnRemovedListener removedCallback
dpy
where
iconFormatter b = return $ colorText colors b text
--------------------------------------------------------------------------------
-- VPN State
--
-- Maintain a set of paths which are the currently active VPNs. Most of the time
-- this will be a null or singleton set, but this setup could handle the edge
-- case of multiple VPNs being active at once without puking.
data VEnv c = VEnv
{ vClient :: !c
, vState :: !(MVar VPNState)
, vDisplay :: !(VIO ())
, vEnv :: !SimpleApp
}
instance SafeClient c => HasLogFunc (VEnv c) where
logFuncL = lens vEnv (\x y -> x {vEnv = y}) . logFuncL
instance HasClient VEnv where
clientL = lens vClient (\x y -> x {vClient = y})
type VIO = RIO (VEnv SysClient)
type VPNState = S.Set ObjectPath
initState :: VIO ()
initState = do
ot <- getVPNObjectTree
s <- asks vState
putMVar s $ findTunnels ot
readState :: VIO Bool
readState = fmap (not . null) . readMVar =<< asks vState
updateState :: (ObjectPath -> VPNState -> VPNState) -> ObjectPath -> VIO ()
updateState f op = do
s <- asks vState
modifyMVar_ s $ return . f op
beforeDisplay :: VIO () -> VIO ()
beforeDisplay f = f >> join (asks vDisplay)
--------------------------------------------------------------------------------
-- Tunnel Device Detection
getVPNObjectTree
:: ( SafeClient c
, HasClient env
, MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m
)
=> m ObjectTree
getVPNObjectTree = callGetManagedObjects vpnBus vpnPath
findTunnels :: ObjectTree -> VPNState
findTunnels = S.fromList . M.keys . M.filter (elem vpnDeviceTun . M.keys)
vpnAddedListener
:: ( SafeClient c
, HasClient env
, MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m
)
=> SignalCallback m
-> m ()
vpnAddedListener cb = void $ addInterfaceAddedListener vpnBus vpnPath cb
vpnRemovedListener
:: ( SafeClient c
, HasClient env
, MonadReader (env c) m
, HasLogFunc (env c)
, MonadUnliftIO m
)
=> SignalCallback m
-> m ()
vpnRemovedListener cb = void $ addInterfaceRemovedListener vpnBus vpnPath cb
addedCallback :: SignalCallback VIO
addedCallback [device, added] =
beforeDisplay $
updateDevice S.insert device $
M.keys $
fromMaybe M.empty added'
where
added' = fromVariant added :: Maybe (M.Map T.Text (M.Map T.Text Variant))
addedCallback _ = return ()
removedCallback :: SignalCallback VIO
removedCallback [device, interfaces] =
beforeDisplay $
updateDevice S.delete device $
fromMaybe [] $
fromVariant interfaces
removedCallback _ = return ()
updateDevice
:: (ObjectPath -> VPNState -> VPNState)
-> Variant
-> [T.Text]
-> VIO ()
updateDevice f device interfaces =
when (vpnDeviceTun `elem` interfaces) $
forM_ d $
updateState f
where
d = fromVariant device :: Maybe ObjectPath
--------------------------------------------------------------------------------
-- DBus Interface
vpnBus :: BusName
vpnBus = busName_ "org.freedesktop.NetworkManager"
vpnPath :: ObjectPath
vpnPath = objectPath_ "/org/freedesktop"
vpnDeviceTun :: T.Text
vpnDeviceTun = "org.freedesktop.NetworkManager.Device.Tun"
vpnAlias :: T.Text
vpnAlias = "vpn"
vpnDep :: DBusDependency_ SysClient
vpnDep =
Endpoint networkManagerPkgs networkManagerBus vpnPath omInterface $
Method_ getManagedObjects

View File

@ -9,9 +9,47 @@ extra-source-files:
- README.md - README.md
- fourmolu.yaml - fourmolu.yaml
- make_pkgs - make_pkgs
- icons/* - runtime_pkgs
- assets/icons/*
- assets/sound/*
- scripts/* - scripts/*
- sound/*
default-extensions:
- OverloadedStrings
- FlexibleContexts
- FlexibleInstances
- InstanceSigs
- MultiParamTypeClasses
- EmptyCase
- LambdaCase
- MultiWayIf
- NamedFieldPuns
- TupleSections
- DeriveFoldable
- DeriveFunctor
- DeriveGeneric
- DeriveLift
- DeriveTraversable
- DerivingStrategies
- DeriveDataTypeable
- EmptyDataDecls
- PartialTypeSignatures
- GeneralizedNewtypeDeriving
- StandaloneDeriving
- BangPatterns
- TypeOperators
- ScopedTypeVariables
- TypeApplications
- ConstraintKinds
- RankNTypes
- GADTs
- DefaultSignatures
- NoImplicitPrelude
- FunctionalDependencies
- DataKinds
- TypeFamilies
- BinaryLiterals
- ViewPatterns
dependencies: dependencies:
- rio >= 0.1.21.0 - rio >= 0.1.21.0
@ -37,13 +75,19 @@ dependencies:
- unliftio >= 0.2.21.0 - unliftio >= 0.2.21.0
- optparse-applicative >= 0.16.1.0 - optparse-applicative >= 0.16.1.0
ghc-options:
- -Wall
- -Wcompat
- -Widentities
- -Wincomplete-record-updates
- -Wincomplete-uni-patterns
- -Wredundant-constraints
- -Wpartial-fields
- -Werror
- -O2
library: library:
source-dirs: lib/ source-dirs: lib/
ghc-options:
- -Wall
- -Werror
- -Wpartial-fields
- -O2
executables: executables:
xmobar: &bin xmobar: &bin
@ -53,21 +97,15 @@ executables:
- xmonad-config - xmonad-config
ghc-options: ghc-options:
- -threaded - -threaded
- -Wall
- -Werror
- -Wpartial-fields
- -O2
xmonad: xmonad:
<<: *bin <<: *bin
main: xmonad.hs main: xmonad.hs
ghc-options: ghc-options:
- -threaded - -threaded
- -Wall
- -Werror
- -Wpartial-fields
- -O2
# this is needed to avoid writing super complex layout types # this is needed to avoid writing super complex layout types
- -fno-warn-missing-signatures - -fno-warn-missing-signatures
vbox-start: vbox-start:
<<: *bin <<: *bin
main: vbox-start.hs main: vbox-start.hs
ghc-options:
- -threaded

22
scripts/screencap Executable file
View File

@ -0,0 +1,22 @@
#! /bin/bash
## capture a screenshot using scrot
SS_DIR="$XDG_CACHE_HOME/screenshots"
while getopts ":sw" opt; do
case ${opt} in
s)
scrot "$SS_DIR/desktop/%Y-%m-%d-%H:%M:%S_desktop.png"
notify-send "Screen captured"
;;
w)
scrot -u "$SS_DIR/window/%Y-%m-%d-%H:%M:%S-\$wx\$h.png"
notify-send "Window captured"
;;
\?)
echo "invalid option, read the code"
;;
esac
done

61
scripts/screenlock Executable file
View File

@ -0,0 +1,61 @@
#! /bin/bash
## lock the screen using i3lock (and maybe suspend)
## usage: screenlock [SUSPEND]
# WORKAROUND make the date show up in the right place on 2+ monitor setups
# I want it to only show up on the primary screen, so use xrandr to get the
# dimensions and position of the primary monitor and calculate the date position
# from that
geometry=$(xrandr | sed -n 's/^.*primary \([0-9]*\)x[0-9]*+\([0-9]\)*+[0-9]* .*/\1 \2/p')
width=$(echo "$geometry" | cut -f1 -d" ")
xpos=$(echo "$geometry" | cut -f2 -d" ")
xoffset=$(("$xpos" + "$width" / 2))
datepos="$xoffset:600"
# lock and fork so we can suspend with the screen locked
i3lock --color=000000 \
--pass-media-keys \
--nofork \
--ignore-empty-password \
--screen=0 \
--indicator \
--inside-color=00000055 \
--insidever-color=00000055 \
--insidewrong-color=00000055 \
--ring-color=555555ff \
--ringwrong-color=ff3333ff \
--ringver-color=99ceffff \
--keyhl-color=99ceffff \
--bshl-color=9523ffff \
--line-color=00000000 \
--separator-color=00000000 \
--clock \
--verif-color=99ceffff \
--wrong-color=ff8282ff \
--time-color=ffffffff \
--time-size=72 \
--time-str="%H:%M" \
--date-color=ffffffff \
--date-size=42 \
--date-str="%b %d, %Y" \
--date-align 0 \
--date-pos="$datepos" \
--wrong-size=72 \
--verif-size=72 \
--radius=300 \
--ring-width=25 &
# suspend if we want, and if this machine is currently using a battery
batpath=/sys/class/power_supply/BAT0/status
if [ -f "$batpath" ] && \
[ "$(cat $batpath)" == "Discharging" ] && \
[ "$1" == "true" ]; then
systemctl suspend
fi
# block until the screen is unlocked (since xss-lock expects the locker to exit
# only when unlocked)
wait

View File

@ -17,8 +17,8 @@
# #
# resolver: ./custom-snapshot.yaml # resolver: ./custom-snapshot.yaml
# resolver: https://example.com/snapshots/2018-01-01.yaml # resolver: https://example.com/snapshots/2018-01-01.yaml
#resolver: lts-17.4 resolver: lts-19.33
resolver: nightly-2022-03-03 #resolver: nightly-2022-03-03
# User packages to be built. # User packages to be built.
# Various formats can be used as shown in the example below. # Various formats can be used as shown in the example below.