WIP add networkmanager xmobar plugin
This commit is contained in:
parent
ab73c24f75
commit
89ac1304ab
|
@ -1,5 +1,6 @@
|
||||||
import Xmobar.Plugins.Bluetooth
|
import Xmobar.Plugins.Bluetooth
|
||||||
import Xmobar.Plugins.IntelBacklight
|
import Xmobar.Plugins.IntelBacklight
|
||||||
|
import Xmobar.Plugins.NetworkManager
|
||||||
import Xmobar.Plugins.Screensaver
|
import Xmobar.Plugins.Screensaver
|
||||||
|
|
||||||
import qualified Theme as T
|
import qualified Theme as T
|
||||||
|
@ -29,6 +30,7 @@ myTemplate = formatTemplate left right
|
||||||
, "%intelbacklight%"
|
, "%intelbacklight%"
|
||||||
, "%bluetooth%"
|
, "%bluetooth%"
|
||||||
, "%screensaver%"
|
, "%screensaver%"
|
||||||
|
, "%networkmanager%"
|
||||||
, "%locks%"
|
, "%locks%"
|
||||||
, "%date%"
|
, "%date%"
|
||||||
]
|
]
|
||||||
|
@ -126,6 +128,8 @@ config confDir = defaultConfig
|
||||||
, Run $ Bluetooth ("<fn=1>\xf293</fn>", T.fgColor, T.backdropFgColor)
|
, Run $ Bluetooth ("<fn=1>\xf293</fn>", T.fgColor, T.backdropFgColor)
|
||||||
|
|
||||||
, Run UnsafeStdinReader
|
, Run UnsafeStdinReader
|
||||||
|
|
||||||
|
, Run $ NetworkManager ("VPN", T.fgColor, T.backdropFgColor)
|
||||||
]
|
]
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
|
@ -0,0 +1,43 @@
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
|
module Xmobar.Plugins.NetworkManager where
|
||||||
|
|
||||||
|
import Control.Concurrent
|
||||||
|
import Control.Monad
|
||||||
|
|
||||||
|
import DBus
|
||||||
|
import DBus.Client
|
||||||
|
import DBus.Internal.Types
|
||||||
|
|
||||||
|
import Xmobar
|
||||||
|
|
||||||
|
newtype NetworkManager = NetworkManager (String, String, String)
|
||||||
|
deriving (Read, Show)
|
||||||
|
|
||||||
|
rule :: MatchRule
|
||||||
|
rule = matchAny
|
||||||
|
{ matchInterface = Just "org.freedesktop.NetworkManager.VPN.Connection"
|
||||||
|
, matchMember = Just "VpnStateChanged"
|
||||||
|
}
|
||||||
|
|
||||||
|
-- TODO would polling be better for this? Using events means that we need
|
||||||
|
-- to catch all of them perfectly to stay synchronized...which *might* happen
|
||||||
|
|
||||||
|
instance Exec NetworkManager where
|
||||||
|
alias (NetworkManager _) = "networkmanager"
|
||||||
|
start (NetworkManager (text, colorOn, colorOff)) cb = do
|
||||||
|
-- start (NetworkManager _) cb = do
|
||||||
|
client <- connectSystem
|
||||||
|
-- TODO initialize
|
||||||
|
_ <- addMatch client rule $ cb . fmtState . getVPNState . signalBody
|
||||||
|
forever (threadDelay 5000000)
|
||||||
|
where
|
||||||
|
getVPNState = \case
|
||||||
|
[Variant (ValueAtom (AtomWord32 s)), _] -> Just s
|
||||||
|
_ -> Nothing
|
||||||
|
fmtState = \case
|
||||||
|
-- state = 5 means VPN is connected
|
||||||
|
Just s -> wrapColor text $ if s == 5 then colorOn else colorOff
|
||||||
|
Nothing -> "N/A"
|
||||||
|
wrapColor s c = "<fc=" ++ c ++ ">" ++ s ++ "</fc>"
|
|
@ -16,6 +16,7 @@ library
|
||||||
, DBus.Screensaver
|
, DBus.Screensaver
|
||||||
, Xmobar.Plugins.Bluetooth
|
, Xmobar.Plugins.Bluetooth
|
||||||
, Xmobar.Plugins.IntelBacklight
|
, Xmobar.Plugins.IntelBacklight
|
||||||
|
, Xmobar.Plugins.NetworkManager
|
||||||
, Xmobar.Plugins.Screensaver
|
, Xmobar.Plugins.Screensaver
|
||||||
build-depends: base
|
build-depends: base
|
||||||
, X11 >= 1.9.1
|
, X11 >= 1.9.1
|
||||||
|
|
Loading…
Reference in New Issue