{-# OPTIONS_GHC -Wno-missing-signatures #-} {-# OPTIONS_GHC -Wno-orphans #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE PostfixOperators #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} -- Imports import XMonad import Data.Monoid import System.Exit import XMonad.Util.Run import XMonad.Util.SpawnOnce import XMonad.Hooks.DynamicLog import XMonad.Hooks.ManageDocks import XMonad.Layout.Spacing import XMonad.Layout.ThreeColumns import XMonad.Layout.LayoutModifier import XMonad.Layout.Renamed import XMonad.Hooks.SetWMName import XMonad.Util.Cursor import XMonad.Layout.NoBorders import XMonad.Layout.PerWorkspace import XMonad.Hooks.EwmhDesktops import XMonad.Util.EZConfig import XMonad.Util.NamedScratchpad import XMonad.Actions.TopicSpace import XMonad.Prompt import XMonad.Prompt.FuzzyMatch import XMonad.Prompt.Workspace import XMonad.Hooks.WorkspaceHistory (workspaceHistoryHook) import XMonad.Hooks.DynamicProperty import qualified XMonad.StackSet as W import qualified Data.Map as M import Text.Regex.Posix -- colours white :: String = "#dcdccc" yellow :: String = "#efef8f" orange :: String = "#ffcfaf" red :: String = "#dca3a3" blue :: String = "#8cd0d3" darkBlue :: String = "#8c8cbc" green :: String = "#7f9f7f" grey :: String = "#3f3f3f" darkGrey :: String = "#262626" -- variables myTerminal = "st" myBorderWidth = 1 myModMask = mod4Mask -- scratchpads myScratchpads :: [NamedScratchpad] myScratchpads = [ NS "keepassxc" "keepassxc ~/db.kdbx" (title =? "it factum Max Hohlfeld - KeePassXC" <||> title =? "db.kdbx [Gesperrt] - KeePassXC") defaultFloating , NS "nnn" "st -t nnn -e nnnwrapper" (title =? "nnn") (customFloating $ W.RationalRect (1/4) (1/6) (2/4) (4/6)) , NS "vimwiki" "st -t vimwiki -e vwwrapper" (title =? "vimwiki") (customFloating $ W.RationalRect (1/6) (1/6) (2/3) (2/3)) ] -- Topic Space topicItems :: [TopicItem] topicItems = [ noAction "1" "~/" , noAction "2" "~/" , noAction "3" "~/" , noAction "4" "~/" , noAction "5" "~/" , TI "dots" "~/dotfiles" spawnShell , TI "IHD_Backend" "~/projekte/IHD/Tractatio_Backend/" (spawnShell *> spawnShell *> spawnShell) , TI "IHD_Frontend" "~/projekte/IHD/Demonstrare_Frontend/" (spawnShell *> spawnShell *> spawnShell) ] myTopicConfig :: TopicConfig myTopicConfig = def { topicDirs = tiDirs topicItems , topicActions = tiActions topicItems , defaultTopicAction = const (pure ()) -- by default, do nothing , defaultTopic = "1" -- fallback } spawnShellInTopic :: X () -- spawnShellInTopic = currentTopicDir myTopicConfig >>= spawn(myTerminal) ++ " -d " spawnShellInTopic = proc $ inTerm >-> execute "nvim" >-$ currentTopicDir myTopicConfig -- spawnTermInTopic :: X () -- spawnTermInTopic = proc $ termInDir >-$ currentTopicDir topicConfig -- | Execute a program in the topic directory (inside a terminal). -- executeInTopic :: String -> X () -- executeInTopic p = proc $ (termInDir >-$ currentTopicDir topicConfig) >-> executeNoQuote p -- | Spawn editor in the current topic directory. -- spawnEditorInTopic :: X () -- spawnEditorInTopic = proc $ inEditor >-$ currentTopicDir topicConfig -- spawnShell :: X () spawnShell = currentTopicDir myTopicConfig >>= spawnShellIn -- spawnShell = currentTopicDir myTopicConfig >>= \dir -> spawnShellInTopic $ dir " dsfsdf" -- spawnShell = ((spawnShellInTopic "dsf") " dsfsdf") spawnShellIn :: Dir -> X () spawnShellIn dir = spawn $ "st -d " ++ dir spawnShellWith :: String -> X() -- spawnShellWith cmd = spawn $ "st -e " ++ cmd spawnShellWith cmd = currentTopicDir myTopicConfig >>= spawnShellInWith cmd spawnShellInWith :: Dir -> String -> X () spawnShellInWith dir cmd = spawn $ "st -d " ++ dir ++ " -e " ++ cmd -- getDir :: X Dir -> String -- getDir (X dir) = dir -- combine :: String -> String -- combine str = currentTopicDir myTopicConfig . getDir -- getDir = spawnShellInAndExe :: String -> String -> X () spawnShellInAndExe cmd dir = spawn $ "st -d" ++ dir ++ " -e" ++ cmd goto :: Topic -> X () goto = switchTopic myTopicConfig promptedGoto :: X () promptedGoto = workspacePrompt topicPrompt goto promptedShift :: X () promptedShift = workspacePrompt topicPrompt $ windows . W.shift toggleTopic :: X () toggleTopic = switchNthLastFocusedByScreen myTopicConfig 1 topicPrompt :: XPConfig topicPrompt = def { historySize = 0 -- No history in the prompt. , fgColor = white , fgHLight = "#3f3f3f" , bgHLight = red , alwaysHighlight = True -- Current best match , height = 25 , position = Top , promptBorderWidth = myBorderWidth -- Fit in with rest of config , borderColor = red , maxComplRows = Just 5 -- Max rows to show in completion window , searchPredicate = fuzzyMatch , sorter = fuzzySort } -- custom keybinds myAdditionalKeys :: [(String, X ())] myAdditionalKeys = -- xmonad specific [ ("M-q", spawn "xmonad --recompile; xmonad --restart") -- dmenu prompts , ("M-", spawn "dm-recent-aliases") , ("M-p s", spawn "dm-screenshot") , ("M-p c", spawn "dm-confedit") , ("M-p k", spawn "dm-kill") -- scratchpads , ("M-n", namedScratchpadAction myScratchpads "nnn") , ("M-S-a", namedScratchpadAction myScratchpads "keepassxc") , ("M-v", namedScratchpadAction myScratchpads "vimwiki") -- open terminal , ("M-S-", spawn (myTerminal)) -- open browser , ("M-b", spawn "firefox") -- media keys , ("", spawn "pamixer -t") , ("", spawn "pamixer -d 5") , ("", spawn "pamixer -i 5") , ("", spawn "pamixer --default-source -t") -- lock screen , ("M-S-l", spawn "slock") -- mute mic , ("M-S-m", spawn "amixer sset Capture toggle") , ("M-z", promptedGoto) , ("M-S-z", promptedShift) , ("M-S-", toggleTopic) -- close windows , ("M-S-c", kill) ] ++ [ ("M-" ++ m ++ k, f i) | (i, k) <- zip (topicNames topicItems) (map show [1 .. 9 :: Int]) , (f, m) <- [(goto, ""), (windows . W.shift, "S-")] ] -- default keybinds myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $ [ -- Rotate through the available layout algorithms ((modm, xK_space ), sendMessage NextLayout) -- Reset the layouts on the current workspace to default -- , ((modm .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf) -- Resize viewed windows to the correct size -- , ((modm, xK_n ), refresh) -- Move focus to the next window , ((modm, xK_Tab ), windows W.focusDown) -- Move focus to the next window , ((modm, xK_j ), windows W.focusDown) -- Move focus to the previous window , ((modm, xK_k ), windows W.focusUp ) -- Move focus to the master window -- , ((modm, xK_m ), windows W.focusMaster ) -- Swap the focused window and the master window , ((modm, xK_Return), windows W.swapMaster) -- Swap the focused window with the next window , ((modm .|. shiftMask, xK_j ), windows W.swapDown ) -- Swap the focused window with the previous window , ((modm .|. shiftMask, xK_k ), windows W.swapUp ) -- Shrink the master area , ((modm, xK_h ), sendMessage Shrink) -- Expand the master area , ((modm, xK_l ), sendMessage Expand) -- Push window back into tiling , ((modm, xK_t ), withFocused $ windows . W.sink) -- Increment the number of windows in the master area , ((modm , xK_comma ), sendMessage (IncMasterN 1)) -- Deincrement the number of windows in the master area , ((modm , xK_period), sendMessage (IncMasterN (-1))) -- Toggle the status bar gap -- Use this binding with avoidStruts from Hooks.ManageDocks. -- See also the statusBar function from Hooks.DynamicLog. -- , ((modm .|. shiftMask, xK_b ), sendMessage ToggleStruts) -- Quit xmonad -- , ((modm .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) ] ++ -- -- mod-[1..9], Switch to workspace N -- mod-shift-[1..9], Move client to workspace N -- -- [((m .|. modm, k), windows $ f i) -- | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9] -- , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]] -- ++ -- -- 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 -- [((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f)) | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..] , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]] -- Layouts mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a mySpacing i = spacingRaw True (Border i i i i) True (Border i i i i) True myLayout = onWorkspace "6" full $ avoidStruts $ onWorkspace "5" steamThreeCol $ tiled ||| full ||| threeCol where tiled = renamed [CutWordsLeft 1] $ smartBorders $ mySpacing 6 $ Tall 1 (3/100) (1/2) steamThreeCol = renamed [Replace "Three Col"] $ noBorders $ mySpacing 3 $ ThreeCol 1 (3/100) (5/8) threeCol = renamed [Replace "Three Col"] $ smartBorders $ mySpacing 6 $ ThreeCol 1 (3/100) (1/2) full = smartBorders $ Full -- Regex lifted up to use in manageHook (*!?) :: Functor f => f String -> String -> f Bool q *!? x = fmap (=~ x) q -- window rules myManageHook = composeAll . concat $ [ [ resource =? "desktop_window" --> doIgnore ] , [ resource =? "kdesktop" --> doIgnore ] , [ ( className =? "LibreWolf" <&&> role =? "Organizer" ) --> doFloat ] -- Steam and games , [ className =? "Steam" --> doShift "5" ] , [ ( className =? "Steam" <&&> title *!? "Friends List" <||> title *!? "News" ) --> doF W.swapDown ] , [ title =? t <&&> title *!? t --> doShift "6" | t <- myGames ] -- float specific classes , [ className =? c --> doFloat | c <- myFloatingClasses ] -- scratchpads , [ namedScratchpadManageHook myScratchpads ] ] where role = stringProperty "WM_WINDOW_ROLE" myFloatingClasses = ["Gimp", "Origin"] myGames = ["Grim Dawn", "Der Herr der Ringe Onlineā„¢", "Dota 2", "Project Zomboid", "Valheim", "Factorio", "Path of Exile", "Paradox Launcher", "Europa Universalis IV", "Bannerlord"] ------------------------------------------------------------------------ -- Event handling -- * EwmhDesktops users should change this to ewmhDesktopsEventHook -- -- Defines a custom handler function for X Events. The function should -- return (All True) if the default handler is to be run afterwards. To -- combine event hooks use mappend or mconcat from Data.Monoid. -- myEventHook = dynamicPropertyChange "WM_NAME" (title =? "it factum Max Hohlfeld - KeePassXC" <||> title =? "db.kdbx [Gesperrt] - KeePassXC" --> floating) where floating = customFloating $ W.RationalRect (1/8) (1/8) (3/4) (3/4) ------------------------------------------------------------------------ -- Status bars and logging -- Perform an arbitrary action on each internal state change or X event. -- See the 'XMonad.Hooks.DynamicLog' extension for examples. -- -- myLogHook = return () -- Startup hook myStartupHook = do setWMName "LG3D" setDefaultCursor xC_left_ptr --spawnOnce("redshift -c /home/max/.config/redshift/redshiftrc") spawnOnce("feh --bg-fill ~/bg.jpg ~/bg.jpg") -- Main main = do xmproc0 <- spawnPipe "xmobar -x 0 /home/max/.config/xmobar/xmobarrc" xmproc1 <- spawnPipe "xmobar -x 1 /home/max/.config/xmobar/xmobarrc" xmonad $ spawnExternalProcess def $ docks def { -- simple stuff terminal = myTerminal, borderWidth = myBorderWidth, modMask = myModMask, workspaces = topicNames topicItems, normalBorderColor = white, focusedBorderColor = red, -- key bindings keys = myKeys, -- hooks, layouts layoutHook = myLayout, manageHook = myManageHook, handleEventHook = myEventHook, logHook = workspaceHistoryHook >> (dynamicLogWithPP $ filterOutWsPP ["NSP"] $ xmobarPP { ppCurrent = xmobarColor "#dca3a3" "" . wrap "[ " " ]", ppHidden = xmobarColor "#8cd0d3" "", ppLayout = xmobarColor "#8c8cbc" "", ppTitle = xmobarColor "#ffcfaf" "" . shorten 100, ppSep = " | ", ppOutput = \x -> hPutStrLn xmproc0 x >> hPutStrLn xmproc1 x }), startupHook = myStartupHook } `additionalKeysP` myAdditionalKeys