mirror of
https://git.sr.ht/~magic_rb/dotfiles
synced 2024-11-26 10:06:13 +01:00
c1684d5203
Signed-off-by: magic_rb <magic_rb@redalder.org>
489 lines
17 KiB
Haskell
489 lines
17 KiB
Haskell
-- SPDX-FileCopyrightText: 2022 Richard Brežák <richard@brezak.sk>
|
|
--
|
|
-- SPDX-License-Identifier: LGPL-3.0-or-later
|
|
|
|
--
|
|
-- xmonad example config file.
|
|
--
|
|
-- A template showing all available configuration hooks,
|
|
-- and how to override the defaults in your own xmonad.hs conf file.
|
|
--
|
|
-- Normally, you'd only override those defaults you care about.
|
|
--
|
|
|
|
{-# LANGUAGE BlockArguments
|
|
#-}
|
|
{-# LANGUAGE LambdaCase #-}
|
|
{-# LANGUAGE TupleSections #-}
|
|
|
|
import XMonad
|
|
import Data.Monoid
|
|
import Data.List (delete)
|
|
import Data.Maybe
|
|
import Data.Function
|
|
import Data.Functor
|
|
import System.Exit
|
|
import System.Environment
|
|
import XMonad.Util.EZConfig
|
|
import XMonad.Util.SpawnOnce
|
|
import XMonad.Util.WindowProperties
|
|
import XMonad.Hooks.ManageDocks
|
|
import XMonad.Hooks.EwmhDesktops
|
|
|
|
import XMonad.Layout.BinarySpacePartition
|
|
import XMonad.Layout.Tabbed
|
|
import XMonad.Layout.NoBorders
|
|
import XMonad.Layout.IndependentScreens
|
|
import XMonad.Util.WorkspaceCompare
|
|
import XMonad.Hooks.DynamicLog
|
|
import XMonad.Hooks.StatusBar
|
|
import XMonad.Actions.UpdatePointer
|
|
import XMonad.Actions.FloatKeys
|
|
import XMonad.Actions.Warp
|
|
import XMonad.Actions.CopyWindow
|
|
import XMonad.StackSet (Workspace, integrate', stack)
|
|
import Foreign.C.String (peekCString)
|
|
|
|
import Control.Monad
|
|
|
|
import qualified XMonad.StackSet as W
|
|
import qualified Data.Map as M
|
|
import XMonad.Actions.Navigation2D
|
|
import XMonad.Layout.Cross (simpleCross)
|
|
import Data.IORef
|
|
import GHC.IO.Unsafe (unsafePerformIO)
|
|
|
|
|
|
myTerminal = "xterm"
|
|
myFocusFollowsMouse = True
|
|
myClickJustFocuses = False
|
|
-- > workspaces = ["web", "irc", "code" ] ++ map show [4..9]
|
|
myWorkspaces = withScreens 2 $ map show ([1..9] ++ [0])
|
|
|
|
toggleFloat :: Window -> X ()
|
|
toggleFloat window = do
|
|
{ floats <- gets (W.floating . windowset);
|
|
if window `M.member` floats
|
|
then withFocused $ windows . W.sink
|
|
else float window }
|
|
|
|
toggleFullscreen :: Display -> Window -> X ()
|
|
toggleFullscreen dpy window = do
|
|
wmstate <- getAtom "_NET_WM_STATE"
|
|
fullsc <- getAtom "_NET_WM_STATE_FULLSCREEN"
|
|
wstate <- fromMaybe [] `fmap` getProp32 wmstate window
|
|
|
|
let
|
|
ptype = 4
|
|
chWstate f = io $ changeProperty32 dpy window wmstate ptype propModeReplace (f wstate)
|
|
isFull = fromIntegral fullsc `elem` wstate
|
|
|
|
unless isFull $ do
|
|
chWstate (fromIntegral fullsc:)
|
|
windows $ W.float window $ W.RationalRect 0 0 1 1
|
|
when isFull $ do
|
|
chWstate $ delete (fromIntegral fullsc)
|
|
windows $ W.sink window
|
|
|
|
centerMouse :: X ()
|
|
centerMouse = warpToWindow 0.5 0.5
|
|
|
|
getCurrentLayout :: X String
|
|
getCurrentLayout =
|
|
gets windowset <&> description . W.layout . W.workspace . W.current
|
|
|
|
workspacesGrouped :: X [(WorkspaceId, Window, String)]
|
|
workspacesGrouped = withDisplay \dpy -> do
|
|
ws <- gets windowset
|
|
let x = map W.workspace (W.current ws : W.visible ws)
|
|
let y = W.hidden ws
|
|
mapM (\v -> do
|
|
let windows = getWorkspaceWindows v
|
|
mapM (\win -> getWindowTitle win dpy <&> \title -> (W.tag v, win, title)) windows) (x ++ y) <&> concat
|
|
|
|
getWorkspaceWindows :: Workspace i l Window -> [Window]
|
|
getWorkspaceWindows w = integrate' $ stack w
|
|
|
|
getWindowTitle :: Window -> Display -> X String
|
|
getWindowTitle w d = liftIO $ getTextProperty d w wM_NAME >>= (peekCString . tp_value)
|
|
|
|
modm :: KeyMask
|
|
modm = mod4Mask
|
|
|
|
skipFloating :: Ord a => W.StackSet i l a s sd -> (W.StackSet i l a s sd -> W.StackSet i l a s sd) -> W.StackSet i l a s sd
|
|
skipFloating stacks f
|
|
| isNothing curr = stacks -- short circuit if there is no currently focused window
|
|
| otherwise = skipFloatingR stacks curr f
|
|
where curr = W.peek stacks
|
|
|
|
skipFloatingR :: Ord a => W.StackSet i l a s sd -> (Maybe a) -> (W.StackSet i l a s sd -> W.StackSet i l a s sd) -> W.StackSet i l a s sd
|
|
skipFloatingR stacks startWindow f
|
|
| isNothing nextWindow = stacks -- next window is nothing return current stack set
|
|
| nextWindow == startWindow = newStacks -- if next window is the starting window then return the new stack set
|
|
| M.notMember (fromJust nextWindow) (W.floating stacks) = newStacks -- if next window is not a floating window return the new stack set
|
|
| otherwise = skipFloatingR newStacks startWindow f -- the next window is a floating window so keep recursing (looking)
|
|
where newStacks = f stacks
|
|
nextWindow = W.peek newStacks
|
|
|
|
------------------------------------------------------------------------
|
|
-- Key bindings. Add, modify or remove key bindings here.
|
|
--
|
|
myKeymap c =
|
|
[
|
|
-- launch dmenu
|
|
("M-e", spawn "dmenu_run")
|
|
|
|
-- close focused window
|
|
, ("M-S-q", io exitSuccess)
|
|
|
|
-- Rotate through the available layout algorithms
|
|
, ("M-<Space>", sendMessage NextLayout)
|
|
|
|
-- Reset the layouts on the current workspace to default
|
|
-- , ("M-S-Space", setLayout $ XMonad.layoutHook c)
|
|
|
|
-- Resize viewed windows to the correct size
|
|
, ("M-b", refresh)
|
|
|
|
-- Push window back into tiling
|
|
, ("M-y", withFocused toggleFloat)
|
|
|
|
-- warp to middle of window
|
|
, ("M-d", centerMouse)
|
|
|
|
-- , ("M-b", spawn ("pkill xmobar && " ++ xmobarCmd))
|
|
, ("<Print>", spawn "sleep 0.1 ; screenshot select")
|
|
, ("S-<Print>", spawn "screenshot screen && sleep 0.1 && notify -t 5000 \"snap\"")
|
|
, ("C-S-<Print>", spawn "screenshot focused && sleep 0.1 && notify -t 5000 \"snap\"")
|
|
|
|
-- Kill focused window
|
|
, ("M-S-k", kill1)
|
|
-- Kill all instances of focused window
|
|
, ("M-S-C-k", kill)
|
|
|
|
-- Restart xmonad
|
|
, ("M-k", spawn "reload")
|
|
|
|
-- float keys
|
|
, ("M-g", sendMessage $ ExpandTowards L)
|
|
, ("M-c", sendMessage $ ExpandTowards U)
|
|
, ("M-l", sendMessage $ ExpandTowards D)
|
|
, ("M-ß", sendMessage $ ExpandTowards R)
|
|
, ("M-S-g", sendMessage $ ShrinkFrom L)
|
|
, ("M-S-c", sendMessage $ ShrinkFrom U)
|
|
, ("M-S-l", sendMessage $ ShrinkFrom D)
|
|
, ("M-S-ẞ", sendMessage $ ShrinkFrom R)
|
|
|
|
, ("M-t", windowGo L False >> centerMouse)
|
|
, ("M-r", getCurrentLayout >>= \case
|
|
"Tabbed Simplest" -> windows (`skipFloating` W.focusUp)
|
|
_ -> windowGo U False >> centerMouse)
|
|
, ("M-n", getCurrentLayout >>= \case
|
|
"Tabbed Simplest" -> windows (`skipFloating` W.focusDown)
|
|
_ -> windowGo D False >> centerMouse)
|
|
, ("M-s", windowGo R False >> centerMouse)
|
|
|
|
, ("M-S-t", windowSwap L False >> centerMouse)
|
|
, ("M-S-r", windowSwap U False >> centerMouse)
|
|
, ("M-S-n", windowSwap D False >> centerMouse)
|
|
, ("M-S-s", windowSwap R False >> centerMouse)
|
|
|
|
, ("M-C-g", sendMessage Rotate)
|
|
, ("M-C-c", sendMessage Swap)
|
|
, ("M-C-l", sendMessage FocusParent)
|
|
, ("M-C-ß", sendMessage SelectNode)
|
|
|
|
, ("M-C-t", sendMessage Balance >> centerMouse >> (liftIO . print . description $ smartBorders simpleTabbed))
|
|
, ("M-C-r", sendMessage Equalize >> centerMouse >> (liftIO . print . description $ smartBorders simpleTabbed))
|
|
, ("M-C-n", sendMessage $ SplitShift Prev)
|
|
, ("M-C-s", sendMessage $ SplitShift Next)
|
|
|
|
, ("M-z", spawn "loginctl lock-session")
|
|
|
|
, ("<XF86AudioMute>" , spawn "wpctl set-mute @DEFAULT_AUDIO_SINK@ toggle")
|
|
, ("<XF86AudioRaiseVolume>" , spawn "wpctl set-volume -l 1.5 @DEFAULT_AUDIO_SINK@ 5%+")
|
|
, ("<XF86AudioLowerVolume>" , spawn "wpctl set-volume @DEFAULT_AUDIO_SINK@ 5%-")
|
|
, ("<XF86MonBrightnessUp>" , spawn "brightnessctl set +5%")
|
|
, ("<XF86MonBrightnessDown>" , spawn "brightnessctl set 5%-")
|
|
|
|
, ("<XF86AudioPlay>" , spawn "notify-send -t 5000 \"Music: Play\"" >> spawn "playerctl play-pause")
|
|
, ("<XF86AudioStop>" , spawn "notify-send -t 5000 \"Music: Stop\"" >> spawn "playerctl stop")
|
|
, ("<XF86AudioPrev>" , spawn "notify-send -t 5000 \"Music: Prev\"" >> spawn "playerctl previous")
|
|
, ("<XF86AudioNext>" , spawn "notify-send -t 5000 \"Music: Next\"" >> spawn "playerctl next")
|
|
|
|
, ("<XF86TouchpadToggle>" , spawn "toggle-touchpad")
|
|
|
|
, ("M-<F1>", spawn "auxmenu")
|
|
, ("M-<F2>", spawn "emacsclient -cn")
|
|
, ("M-<F3>", spawn "emacs-passmenu copy")
|
|
, ("M-S-<F3>", spawn "emacs-passmenu qr")
|
|
, ("M-S-<Return>", spawn "emacs-vterm")
|
|
, ("M-<Return>", spawn "alacritty")
|
|
|
|
, ("M-<F11>", withDisplay $ \dpy -> withFocused $ \window -> toggleFullscreen dpy window)
|
|
, ("M-<F9>", (workspacesGrouped >>= \ws -> (liftIO . print $ ws)))
|
|
]
|
|
++
|
|
--
|
|
--
|
|
--
|
|
--
|
|
-- mod-[1..9], Switch to workspace N
|
|
-- mod-[1..9], Switch to workspace N
|
|
-- mod-[1..9], Switch to workspace N
|
|
-- mod-[1..9], Switch to workspace N
|
|
--
|
|
--
|
|
--
|
|
--
|
|
|
|
--
|
|
|
|
--
|
|
-- mod-[1..9], Switch to workspace N
|
|
-- mod-[1..9], Switch to workspace N
|
|
--
|
|
--
|
|
|
|
--
|
|
--
|
|
-- mod-[1..9], Switch to workspace N
|
|
-- mod-[1..9], Switch to workspace N
|
|
--
|
|
--
|
|
|
|
--
|
|
-- mod-[1..9], Switch to workspace N
|
|
--
|
|
[("M-" ++ m ++ [k], windows $ onCurrentScreen f i)
|
|
| (i, k) <- zip (workspaces' c) "1234567890"
|
|
, (f, m) <- [(W.greedyView, ""), (W.shift, "S-"), (copy, "S-C-")]]
|
|
++
|
|
--
|
|
--
|
|
--
|
|
--
|
|
-- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
|
|
-- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
|
|
-- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
|
|
-- mod-{w,e,r}, Switch to physical/Xinerama screens 1, 2, or 3
|
|
-- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
|
|
-- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
|
|
-- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
|
|
-- mod-shift-{w,e,r}, Move client to screen 1, 2, or 3
|
|
--
|
|
--
|
|
--
|
|
--
|
|
[("M-"++m++[key], screenWorkspace sc >>= flip whenJust (windows . f))
|
|
| (key, sc) <- zip ".o," [0..]
|
|
, (f, m) <- [(W.view, ""), (W.shift, "S-")]]
|
|
where
|
|
xMoveWindow
|
|
:: (Position, Position)
|
|
-> Window
|
|
-> X ()
|
|
xMoveWindow (x, y) w = withDisplay (\d -> do
|
|
(_, ox, oy, _, _, _, _) <- io $ getGeometry d w
|
|
io $ moveWindow d w (ox + x) (oy + y))
|
|
|
|
|
|
------------------------------------------------------------------------
|
|
-- Mouse bindings: default actions bound to mouse events
|
|
--
|
|
myMouseBindings (XConfig {XMonad.modMask = modm}) = M.fromList $
|
|
|
|
-- mod-button1, Set the window to floating mode and move by dragging
|
|
[ ((modm, button2), (\w -> focus w >> windows W.shiftMaster))
|
|
|
|
-- mod-button3, Set the window to floating mode and resize by dragging
|
|
, ((modm, button3), (\w -> focus w >> mouseResizeWindow w
|
|
>> windows W.shiftMaster))
|
|
|
|
-- you may also bind events to the mouse scroll wheel (button4 and button5)
|
|
]
|
|
|
|
------------------------------------------------------------------------
|
|
-- Layouts:
|
|
|
|
-- You can specify and transform your layouts by modifying these values.
|
|
-- If you change layout bindings be sure to use 'mod-shift-space' after
|
|
-- restarting (with 'mod-q') to reset your layout state to the new
|
|
-- defaults, as xmonad preserves your old layout settings by default.
|
|
--
|
|
-- The available layouts. Note that each layout is separated by |||,
|
|
-- which denotes layout choice.
|
|
--
|
|
myLayout = smartBorders simpleTabbed ||| smartBorders emptyBSP
|
|
where
|
|
-- default tiling algorithm partitions the screen into two panes
|
|
tiled = Tall nmaster delta ratio
|
|
|
|
-- The default number of windows in the master pane
|
|
nmaster = 1
|
|
|
|
-- Default proportion of screen occupied by master pane
|
|
ratio = 1/2
|
|
|
|
-- Percent of screen to increment by when resizing panes
|
|
delta = 3/100
|
|
|
|
myPP = def
|
|
{ ppLayout = const "" -- Don't show the layout name
|
|
, ppSort = getSortByXineramaRule -- Sort left/right screens on the left, non-empty workspaces after those
|
|
, ppTitle = const "" -- Don't show the focused window's title
|
|
, ppTitleSanitize = const "" -- Also about window's title
|
|
, ppVisible = wrap "(" ")" -- Non-focused (but still visible) screen
|
|
}
|
|
|
|
spawnBar :: ScreenId -> IO StatusBarConfig
|
|
spawnBar screen = pure $ statusBarPropTo ("_XMONAD_LOG_" <> screenString ) ("polybar-mm " <> screenString) (pure myPP)
|
|
where screenString = show (fromIntegral screen :: Int)
|
|
|
|
------------------------------------------------------------------------
|
|
-- Now run xmonad with all the defaults we set up.
|
|
|
|
-- Run xmonad with the settings you specify. No need to modify this.
|
|
--
|
|
-- main = xmonad $ ewmh $ docks $ defaults
|
|
main = do
|
|
getEnv "PATH" >>= \path -> setEnv "PATH" (path <> ":/home/main/.xmonad/runenv/bin")
|
|
print (description (smartBorders simpleTabbed))
|
|
|
|
let
|
|
nav2dConfig
|
|
= def
|
|
-- doesn't work with tabbed at all
|
|
-- { unmappedWindowRect = [("Tabbed Simplest", fullScreenRect)]}
|
|
|
|
defaults & xmonad . docks . dynamicSBs spawnBar . withNavigation2DConfig nav2dConfig
|
|
|
|
getNetWMState :: Window -> X [Atom]
|
|
getNetWMState w = do
|
|
atom <- getAtom "_NET_WM_STATE"
|
|
map fromIntegral . fromMaybe [] <$> getProp32 atom w
|
|
|
|
|
|
hasNetWMState :: String -> Query Bool
|
|
hasNetWMState state = do
|
|
window <- ask
|
|
wmstate <- liftX $ getNetWMState window
|
|
atom <- liftX $ getAtom state
|
|
return $ elem atom wmstate
|
|
|
|
ewwWindows :: IORef [Window]
|
|
{-# NOINLINE ewwWindows #-}
|
|
ewwWindows = unsafePerformIO $ newIORef []
|
|
|
|
-- A structure containing your configuration settings, overriding
|
|
-- fields in the default config. Any you don't override, will
|
|
-- use the defaults defined in xmonad/XMonad/Config.hs
|
|
--
|
|
-- No need to modify this.
|
|
--
|
|
defaults = let
|
|
c = def {
|
|
-- simple stuff
|
|
terminal = myTerminal,
|
|
focusFollowsMouse = myFocusFollowsMouse,
|
|
clickJustFocuses = myClickJustFocuses,
|
|
modMask = modm,
|
|
workspaces = myWorkspaces,
|
|
|
|
-- key bindings
|
|
-- keys = myKeys,
|
|
mouseBindings = myMouseBindings,
|
|
|
|
-- hooks, layouts
|
|
layoutHook = avoidStruts $ myLayout,
|
|
|
|
-- To find the property name associated with a program, use
|
|
-- > xprop | grep WM_CLASS
|
|
-- and click on the client you're interested in.
|
|
--
|
|
-- To match on the WM_NAME, you can use 'title' in the same way that
|
|
-- 'className' and 'resource' are used below.
|
|
manageHook = manageDocks <+> composeAll
|
|
[ title =? "emacs-completing-read-float" --> doFloat
|
|
, hasNetWMState "_NET_WM_STATE_ABOVE" --> doFloat
|
|
, hasNetWMState "_NET_WM_STATE_STICKY" --> doF copyToAll
|
|
, className =? "Eww" --> (do
|
|
liftIO $ print "eww"
|
|
window <- ask
|
|
oldSet <- liftIO $ readIORef ewwWindows
|
|
liftIO $ writeIORef ewwWindows (window : oldSet)
|
|
doF id)
|
|
, className =? "xmessage" --> doFloat
|
|
-- , resource =? "desktop_window" --> doIgnore
|
|
-- , resource =? "kdesktop" --> doIgnore
|
|
],
|
|
|
|
logHook = do
|
|
updatePointer (0.5, 0.5) (1, 1)
|
|
set <- liftIO $ readIORef ewwWindows
|
|
liftIO $ print set
|
|
pure (),
|
|
|
|
-- XMonad.Layout.PerWorkspace
|
|
-- startupHook = void,
|
|
|
|
-- Looks
|
|
focusedBorderColor = "#5c5c5c",
|
|
normalBorderColor = "#222222",
|
|
borderWidth = 4
|
|
}
|
|
in additionalKeysP c (myKeymap c)
|
|
& flip additionalKeys [ ((mod1Mask, xK_v), return ()) ]
|
|
& ewmh
|
|
|
|
-- | Finally, a copy of the default bindings in simple textual tabular format.
|
|
help :: String
|
|
help = unlines ["The default modifier key is 'alt'. Default keybindings:",
|
|
"",
|
|
"-- launching and killing programs",
|
|
"mod-Shift-Enter Launch xterminal",
|
|
"mod-p Launch dmenu",
|
|
"mod-Shift-p Launch gmrun",
|
|
"mod-Shift-c Close/kill the focused window",
|
|
"mod-Space Rotate through the available layout algorithms",
|
|
"mod-Shift-Space Reset the layouts on the current workSpace to default",
|
|
"mod-n Resize/refresh viewed windows to the correct size",
|
|
"",
|
|
"-- move focus up or down the window stack",
|
|
"mod-Tab Move focus to the next window",
|
|
"mod-Shift-Tab Move focus to the previous window",
|
|
"mod-j Move focus to the next window",
|
|
"mod-k Move focus to the previous window",
|
|
"mod-m Move focus to the master window",
|
|
"",
|
|
"-- modifying the window order",
|
|
"mod-Return Swap the focused window and the master window",
|
|
"mod-Shift-j Swap the focused window with the next window",
|
|
"mod-Shift-k Swap the focused window with the previous window",
|
|
"",
|
|
"-- resizing the master/slave ratio",
|
|
"mod-h Shrink the master area",
|
|
"mod-l Expand the master area",
|
|
"",
|
|
"-- floating layer support",
|
|
"mod-t Push window back into tiling; unfloat and re-tile it",
|
|
"",
|
|
"-- increase or decrease number of windows in the master area",
|
|
"mod-comma (mod-,) Increment the number of windows in the master area",
|
|
"mod-period (mod-.) Deincrement the number of windows in the master area",
|
|
"",
|
|
"-- quit, or restart",
|
|
"mod-Shift-q Quit xmonad",
|
|
"mod-q Restart xmonad",
|
|
"mod-[1..9] Switch to workSpace N",
|
|
"",
|
|
"-- Workspaces & screens",
|
|
"mod-Shift-[1..9] Move client to workspace N",
|
|
"mod-{w,e,r} Switch to physical/Xinerama screens 1, 2, or 3",
|
|
"mod-Shift-{w,e,r} Move client to screen 1, 2, or 3",
|
|
"",
|
|
"-- Mouse bindings: default actions bound to mouse events",
|
|
"mod-button1 Set the window to floating mode and move by dragging",
|
|
"mod-button2 Raise the window to the top of the stack",
|
|
"mod-button3 Set the window to floating mode and resize by dragging"]
|