mirror of
https://github.com/ellmau/nixos.git
synced 2025-12-19 09:29:36 +01:00
* XMonad base config
* Polybar
* development environment for emacs
* flake bump
Flake lock file updates:
• Added input 'flake-utils':
'github:numtide/flake-utils/cfacdce06f30d2b68473a46042957675eebb3401' (2023-04-11)
• Added input 'flake-utils/systems':
'github:nix-systems/default/da67096a3b9bf56a91d16901293e51ba5b49a27e' (2023-04-09)
• Added input 'flake-utils-plus':
'github:gytis-ivaskevicius/flake-utils-plus/2bf0f91643c2e5ae38c1b26893ac2927ac9bd82a' (2022-07-07)
• Added input 'flake-utils-plus/flake-utils':
'github:numtide/flake-utils/3cecb5b042f7f209c56ffd8371b2711a290ec797' (2022-02-07)
• Added input 'nixpkgs':
'github:NixOS/nixpkgs/7629f9b0680d87c7775f3261bee746da5dac76d1' (2023-05-08)
• Added input 'nixpkgs-unstable':
'github:NixOS/nixpkgs/897876e4c484f1e8f92009fd11b7d988a121a4e7' (2023-05-06)
81 lines
2.7 KiB
Haskell
81 lines
2.7 KiB
Haskell
module Main where
|
|
|
|
import Data.Ratio
|
|
import XMonad hiding ((|||))
|
|
import XMonad.Hooks.FadeInactive
|
|
import XMonad.Hooks.FadeWindows
|
|
import XMonad.Hooks.EwmhDesktops
|
|
import XMonad.Hooks.ManageDocks
|
|
import XMonad.Hooks.ManageHelpers
|
|
import XMonad.Hooks.StatusBar
|
|
import XMonad.Util.EZConfig
|
|
import Network.HostName (getHostName)
|
|
-- Imports for Polybar --
|
|
import qualified Codec.Binary.UTF8.String as UTF8
|
|
import qualified DBus as D
|
|
import qualified DBus.Client as D
|
|
import XMonad.Hooks.DynamicLog
|
|
|
|
main :: IO ()
|
|
main' :: D.Client -> IO ()
|
|
main = mkDbusClient >>= main'
|
|
|
|
main' dbus = do
|
|
hostname <- io $ getHostName
|
|
xmonad . docks . ewmhFullscreen . ewmh $ def
|
|
{ terminal = "alacritty"
|
|
, logHook = polybarLogHook dbus
|
|
}
|
|
|
|
mkDbusClient :: IO D.Client
|
|
mkDbusClient = do
|
|
dbus <- D.connectSession
|
|
D.requestName dbus (D.busName_ "org.xmonad.log") opts
|
|
return dbus
|
|
where
|
|
opts = [D.nameAllowReplacement, D.nameReplaceExisting, D.nameDoNotQueue]
|
|
|
|
-- Emit a DBus signal on log updates
|
|
dbusOutput :: D.Client -> String -> IO ()
|
|
dbusOutput dbus str =
|
|
let opath = D.objectPath_ "/org/xmonad/Log"
|
|
iname = D.interfaceName_ "org.xmonad.Log"
|
|
mname = D.memberName_ "Update"
|
|
signal = D.signal opath iname mname
|
|
body = [D.toVariant $ UTF8.decodeString str]
|
|
in D.emit dbus $ signal { D.signalBody = body }
|
|
|
|
polybarHook :: D.Client -> PP
|
|
polybarHook dbus =
|
|
let wrapper c s | s /= "NSP" = wrap ("%{F" <> c <> "} ") " %{F-}" s
|
|
| otherwise = mempty
|
|
blue = "#2E9AFE"
|
|
gray = "#7F7F7F"
|
|
orange = "#ea4300"
|
|
purple = "#9058c7"
|
|
red = "#722222"
|
|
in def { ppOutput = dbusOutput dbus
|
|
, ppCurrent = wrapper blue
|
|
, ppVisible = wrapper gray
|
|
, ppUrgent = wrapper orange
|
|
, ppHidden = wrapper gray
|
|
, ppHiddenNoWindows = wrapper red
|
|
, ppTitle = shorten 100 . wrapper purple
|
|
}
|
|
|
|
fadeHook :: Rational -> Rational -> X ()
|
|
fadeHook act inact = fadeOutLogHook $ fadeAllBut exceptions act inact
|
|
where exceptions = isFullscreen
|
|
<||> className =? "firefox"
|
|
<||> className =? "Chromium-browser"
|
|
|
|
fadeAllBut :: Query Bool -> Rational -> Rational -> Query Rational
|
|
fadeAllBut qry amt inact = do isInactive <- isUnfocused
|
|
isQry <- qry
|
|
if isQry
|
|
then return 1
|
|
else if isInactive
|
|
then return inact
|
|
else return amt
|
|
|
|
polybarLogHook dbus = fadeHook 0.95 0.75 <+> dynamicLogWithPP (polybarHook dbus) |