modern_lisp-machine/xmonad/xmonad.hs

166 lines
5.5 KiB
Haskell
Raw Normal View History

2024-03-02 19:12:23 +00:00
import XMonad
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers
import XMonad.Hooks.StatusBar
import XMonad.Hooks.StatusBar.PP
import XMonad.StackSet as W -- float purposes
import XMonad.Actions.MouseResize
import XMonad.Util.EZConfig
import XMonad.Util.Loggers
import XMonad.Util.Ungrab
import XMonad.Layout.Magnifier
import XMonad.Layout.ThreeColumns
import XMonad.Layout.Spacing
import XMonad.Hooks.EwmhDesktops
import XMonad.Util.SpawnOnce (spawnOnce)
2024-03-03 02:42:19 +00:00
2024-03-02 19:12:23 +00:00
-- run or raise
2024-03-03 02:42:19 +00:00
import XMonad.Actions.WindowGo (raiseMaybe, runOrRaise)
2024-03-02 19:12:23 +00:00
import XMonad.ManageHook (className)
import XMonad.StackSet (RationalRect(..))
--
2024-03-03 02:42:19 +00:00
import XMonad.Layout.Decoration
2024-03-02 19:12:23 +00:00
import XMonad.Layout.Simplest
import XMonad.Layout.SimplestFloat
import XMonad.Layout.Spacing
2024-03-03 14:50:09 +00:00
import XMonad.Actions.PerWindowKeys
2024-03-15 15:28:51 +00:00
import XMonad.Actions.FindEmptyWorkspace
import XMonad.Layout.Grid
import XMonad.Layout.PerScreen (ifWider)
2024-03-16 15:41:42 +00:00
import XMonad.StackSet
import XMonad.Layout
import XMonad.Layout.Reflect
2024-03-16 17:39:02 +00:00
import XMonad.Layout.WindowArranger
-- Window Rearragement
import Data.List (find)
import XMonad.Actions.EasyMotion (selectWindow)
import XMonad.Actions.FocusNth (swapNth)
import qualified XMonad.StackSet as W
2024-06-13 20:33:15 +00:00
import XMonad.Layout.LimitWindows
2024-03-16 17:39:02 +00:00
2024-03-02 19:12:23 +00:00
main :: IO ()
main = xmonad
. ewmhFullscreen
. ewmh
. withEasySB (statusBarProp "xmobar" (pure myXmobarPP)) defToggleStrutsKey
$ myConfig
2024-03-15 15:28:51 +00:00
2024-03-02 19:12:23 +00:00
myConfig = def
{ modMask = mod4Mask -- Rebind Mod to the Super key
2024-03-16 17:39:02 +00:00
, layoutHook = windowArrange myLayout -- Use custom layouts
2024-06-01 05:00:40 +00:00
, terminal = "kitty"
2024-03-03 02:42:19 +00:00
, focusedBorderColor = "#000000"
2024-03-02 19:12:23 +00:00
, manageHook = myManageHook -- Match on certain windows
, startupHook = do
-- other startup commands
2024-04-15 20:06:54 +00:00
-- spawnOnce "xrandr --output DisplayPort-0 --mode 1366x768 --pos 1366x0 --rotate left --output HDMI-A-0 --primary --mode 1366x768 --pos 0x0 --rotate normal --output DVI-D-0 --off"
spawnOnce "xrandr --output HDMI-A-0 --mode 1366x768 --pos 0x0 --rotate normal"
2024-03-02 19:12:23 +00:00
spawnOnce "xrdb /home/hashirama/.Xresources"
2024-03-20 19:24:52 +00:00
spawnOnce "/home/hashirama/.local/bin/rotate_wallpapers.sh"
spawnOnce "picom -b"
2024-03-03 02:42:19 +00:00
spawnOnce "polybar top-monitor-1"
2024-03-15 15:28:51 +00:00
spawnOnce "fcitx5 -d -r"
2024-04-15 20:06:54 +00:00
spawnOnce "emacs --daemon"
2024-03-02 19:12:23 +00:00
}
2024-03-03 14:50:09 +00:00
2024-03-02 19:12:23 +00:00
`additionalKeysP`
[ ("M-d", spawn "rofi -show run")
, ("M-s", spawn "bash -c dictpopup")
2024-04-15 20:06:54 +00:00
, ("M-S-e", spawn "flameshot full --path=/mnt/Data/mpv-screenshots/screenshots/light_novels")
2024-03-02 19:12:23 +00:00
, ("M-e", runOrRaise "goldendict" (className =? "GoldenDict-ng"))
2024-06-01 05:00:40 +00:00
, ("M-p", runOrRaise "librewolf" (className =? "librewolf-default"))
, ("M-S-g", spawn "~/.local/bin/mpv-tube.sh")
, ("M-S-c", spawn "emacsclient --eval '(emacs-everywhere)'")
, ("M-S-p", runOrRaise "nyxt" (className =? "Nyxt"))
2024-03-02 19:12:23 +00:00
, ("M-t", withFocused $ windows . W.sink) -- Toggle float for the focused window
2024-03-15 15:28:51 +00:00
, ("M-`", runOrRaise "emacs" (className =? "Emacs"))
2024-03-03 00:54:29 +00:00
, ("M-S-q", return ()) -- Unbind Mod + Shift + Q, to avoid quiting the wm.
2024-03-03 02:42:19 +00:00
, ("M-q", kill) -- Change the keybinding for closing windows to Mod + Q
2024-07-12 04:59:24 +00:00
, ("M-m", spawn "mpv --audio-pitch-correction=yes --vf=setpts=PTS/1 --idle")
2024-03-15 15:28:51 +00:00
, ("M-S-r", spawn "~/.local/bin/run_anki.sh")
2024-04-15 20:06:54 +00:00
, ("M-S-d", spawn "~/.local/bin/recent_journal.py | popup")
2024-03-15 15:28:51 +00:00
, ("M-r", runOrRaise "~/.local/bin/run_anki.sh" (className =? "Anki"))
2024-04-15 20:06:54 +00:00
, ("M-g", runOrRaise "foliate" (className =? "com.github.johnfactotum.Foliate"))
2024-03-20 19:24:52 +00:00
, ("M-S-f", sendToEmptyWorkspace) -- View an empty workspace
2024-03-15 15:28:51 +00:00
, ("M-f", viewEmptyWorkspace) -- View an empty workspace
, ("M-S-w", spawn "flameshot gui --path=/mnt/Data/mpv-screenshots/screenshots")
, ("M-w", spawn "~/.local/bin/copy_image.sh")
2024-03-16 17:39:02 +00:00
, ("M-v", easySwap)
2024-03-02 19:12:23 +00:00
]
2024-03-16 17:39:02 +00:00
easySwap :: X ()
easySwap = do
win <- selectWindow def
stack <- gets $ W.index . windowset
let match = find ((win ==) . Just . fst) $ zip stack [0 ..]
whenJust match $ swapNth . snd
2024-03-02 19:12:23 +00:00
myManageHook :: ManageHook
myManageHook = composeAll
[ className =? "Gimp" --> doFloat
, isDialog --> doFloat
]
myTheme :: Theme
myTheme = def
2024-03-03 02:42:19 +00:00
{ decoHeight = 20
2024-03-02 19:12:23 +00:00
-- Add other theme properties as needed
}
2024-06-13 20:33:15 +00:00
myLayout = limitWindows 2 $ Tall 1 0.03 0.5 ||| Full
2024-03-16 15:41:42 +00:00
toggleLayout :: X ()
toggleLayout = do
currentLayout <- gets (W.layout . W.workspace . W.current . windowset)
case description currentLayout of
"Tall" -> sendMessage $ JumpToLayout "Mirror Tall"
_ -> sendMessage $ JumpToLayout "Tall"
2024-03-02 19:12:23 +00:00
myXmobarPP :: PP
myXmobarPP = def
2024-03-03 02:42:19 +00:00
{ ppSep = cyan ""
2024-03-02 19:12:23 +00:00
, ppTitleSanitize = xmobarStrip
, ppCurrent = wrap " " "" . xmobarBorder "Top" "#8be9fd" 2
, ppHidden = white . wrap " " ""
, ppHiddenNoWindows = lowWhite . wrap " " ""
, ppUrgent = red . wrap (yellow "!") (yellow "!")
, ppOrder = \[ws, l, _, wins] -> [ws, l, wins]
, ppExtras = [logTitles formatFocused formatUnfocused]
}
where
2024-03-03 02:42:19 +00:00
formatFocused = wrap (white "[") (white "]") . cyan . ppWindow
formatUnfocused = wrap (lowWhite "[") (lowWhite "]") . vividGreen . ppWindow
2024-03-02 19:12:23 +00:00
2024-03-03 02:42:19 +00:00
-- | Windows should have *some* title, which should not exceed a
2024-03-02 19:12:23 +00:00
-- sane length.
ppWindow :: String -> String
ppWindow = xmobarRaw . (\w -> if null w then "untitled" else w) . shorten 30
2024-03-03 02:42:19 +00:00
cyan, vividGreen, lowWhite, red, white, yellow :: String -> String
cyan = xmobarColor "#8be9fd" ""
vividGreen = xmobarColor "#50fa7b" ""
white = xmobarColor "#f8f8f2" ""
yellow = xmobarColor "#f1fa8c" ""
red = xmobarColor "#ff5555" ""
lowWhite = xmobarColor "#bbbbbb" ""