Reword XMonad config

Signed-off-by: MagicRB <richard@brezak.sk>
This commit is contained in:
MagicRB 2023-10-03 23:47:31 +02:00
parent 26d8b6dac3
commit 8cebc0b293
No known key found for this signature in database
GPG key ID: 08D5287CC5DDCA0E

View file

@ -13,6 +13,7 @@
{-# LANGUAGE BlockArguments
#-}
{-# LANGUAGE LambdaCase #-}
import XMonad
import Data.Monoid
@ -44,6 +45,8 @@ import Control.Monad
import qualified XMonad.StackSet as W
import qualified Data.Map as M
import XMonad.Actions.Navigation2D
import XMonad.Layout.Cross (simpleCross)
myTerminal = "xterm"
@ -52,11 +55,37 @@ myClickJustFocuses = False
-- > workspaces = ["web", "irc", "code" ] ++ map show [4..9]
myWorkspaces = withScreens 2 $ map show ([1..9] ++ [0])
toggleFloat = withFocused (\windowId -> do
{ floats <- gets (W.floating . windowset);
if windowId `M.member` floats
then withFocused $ windows . W.sink
else float windowId })
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
modm :: KeyMask
modm = mod4Mask
@ -72,7 +101,7 @@ myKeymap c =
, ("M-e", spawn "dmenu_run")
-- close focused window
, ("M-S-q", io (exitWith ExitSuccess))
, ("M-S-q", io exitSuccess)
-- Rotate through the available layout algorithms
, ("M-<Space>", sendMessage NextLayout)
@ -83,55 +112,17 @@ myKeymap c =
-- Resize viewed windows to the correct size
, ("M-b", refresh)
-- Move focus to the next window
, ("M-<Tab>", windows W.focusDown)
-- Move focus to the next window
, ("M-n", windows W.focusDown)
-- Move focus to the previous window
, ("M-r", windows W.focusUp)
-- Move focus to the master window
, ("M-p", windows W.focusMaster)
-- Swap the focused window and the master window
, ("M-<RET>", windows W.swapMaster)
-- Swap the focused window with the next window
, ("M-S-n", windows W.swapDown)
-- Swap the focused window with the previous window
, ("M-S-r", windows W.swapUp)
-- Shrink the master area
, ("M-t", sendMessage Shrink)
-- Expand the master area
, ("M-s", sendMessage Expand)
-- Push window back into tiling
, ("M-y", toggleFloat)
, ("M-y", withFocused toggleFloat)
-- Increment the number of windows in the master area
, ("M-w", sendMessage (IncMasterN 1))
-- Deincrement the number of windows in the master area
, ("M-m", sendMessage (IncMasterN (-1)))
, ("M-d", warpToWindow 0.5 0.5)
-- 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\"")
-- Toggle the status bar gap
-- Use this binding with avoidStruts from Hooks.ManageDocks.
-- See also the statusBar function from Hooks.DynamicLog.
--
, ("M-b", sendMessage ToggleStruts)
-- Quit xmonad
, ("M-S-k", kill)
@ -139,14 +130,38 @@ myKeymap c =
, ("M-k", spawn "reload")
-- float keys
, ("M-g", withFocused (keysResizeWindow (-10, 0) (0, 0)))
, ("M-c", withFocused (keysResizeWindow ( 0, 10) (0, 0)))
, ("M-l", withFocused (keysResizeWindow ( 0,-10) (0, 0)))
, ("M-ß", withFocused (keysResizeWindow ( 10, 0) (0, 0)))
, ("M-S-g", withFocused (xMoveWindow (-10, 0)))
, ("M-S-c", withFocused (xMoveWindow ( 0, 10)))
, ("M-S-l", withFocused (xMoveWindow ( 0,-10)))
, ("M-S-ß", withFocused (xMoveWindow ( 10, 0)))
, ("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 W.focusUp
_ -> windowGo U False >> centerMouse)
, ("M-n", getCurrentLayout >>= \case
"Tabbed Simplest" -> windows 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")
@ -165,25 +180,153 @@ myKeymap c =
, ("M-<F1>", spawn "auxmenu")
, ("M-<F11>", withDisplay $ \dpy -> withFocused $ \win -> do
wmstate <- getAtom "_NET_WM_STATE"
fullsc <- getAtom "_NET_WM_STATE_FULLSCREEN"
wstate <- fromMaybe [] `fmap` getProp32 wmstate win
let
ptype = 4
chWstate f = io $ changeProperty32 dpy win wmstate ptype propModeReplace (f wstate)
isFull = fromIntegral fullsc `elem` wstate
when (not isFull) $ do
chWstate (fromIntegral fullsc:)
windows $ W.float win $ W.RationalRect 0 0 1 1
when isFull $ do
chWstate $ delete (fromIntegral fullsc)
windows $ W.sink win)
, ("M-<F11>", withDisplay $ \dpy -> withFocused $ \window -> toggleFullscreen dpy window)
]
++
--
--
--
--
--
--
--
--
-- 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-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client 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-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client 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-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
--
--
--
--
--
--
-- mod-[1..9], Switch to workspace N
-- mod-[1..9], Switch to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client 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-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
--
--
--
--
--
--
-- mod-[1..9], Switch to workspace N
-- mod-[1..9], Switch to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
--
--
--
--
-- mod-[1..9], Switch to workspace N
-- mod-[1..9], Switch to workspace N
-- mod-shift-[1..9], Move client to workspace N
-- mod-shift-[1..9], Move client to workspace N
--
--
--
-- mod-[1..9], Switch to workspace N
-- mod-shift-[1..9], Move client to workspace N
@ -194,8 +337,43 @@ myKeymap 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-{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
-- 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..]
@ -240,7 +418,7 @@ myMouseBindings (XConfig {XMonad.modMask = modm}) = M.fromList $
-- The available layouts. Note that each layout is separated by |||,
-- which denotes layout choice.
--
myLayout = smartBorders tiled ||| smartBorders simpleTabbed ||| smartBorders emptyBSP ||| noBorders Full
myLayout = smartBorders simpleTabbed ||| smartBorders emptyBSP
where
-- default tiling algorithm partitions the screen into two panes
tiled = Tall nmaster delta ratio
@ -274,7 +452,15 @@ spawnBar screen = pure $ statusBarPropTo ("_XMONAD_LOG_" <> screenString ) ("pol
-- main = xmonad $ ewmh $ docks $ defaults
main = do
getEnv "PATH" >>= \path -> setEnv "PATH" (path <> ":/home/main/.xmonad/runenv/bin")
pure defaults <&> dynamicSBs spawnBar <&> docks >>= xmonad
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