refactor: xmonad qwerty file
This commit is contained in:
parent
b3345f64fe
commit
6231bc2a3b
@ -1,43 +1,49 @@
|
|||||||
{-# LANGUAGE BlockArguments #-}
|
-- imports
|
||||||
-- Imports
|
|
||||||
import XMonad
|
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.Layout.LimitWindows
|
|
||||||
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.Prompt.Shell
|
|
||||||
import XMonad.Hooks.WorkspaceHistory (workspaceHistoryHook)
|
|
||||||
import XMonad.Hooks.DynamicProperty
|
|
||||||
import qualified XMonad.StackSet as W
|
import qualified XMonad.StackSet as W
|
||||||
import qualified Data.Map as M
|
|
||||||
import Text.Regex.Posix
|
import XMonad.Actions.TopicSpace (TopicConfig (..), TopicItem (..), noAction, tiDirs, tiActions, currentTopicDir, switchNthLastFocusedByScreen, switchTopic, topicNames)
|
||||||
|
import XMonad.Actions.Search (SearchEngine, openstreetmap, hackage, wikipedia, youtube, searchEngine, promptSearch, selectSearch)
|
||||||
|
|
||||||
|
import XMonad.Hooks.DynamicLog (PP(..), dynamicLogWithPP, filterOutWsPP, xmobarPP, xmobarColor, wrap, shorten)
|
||||||
|
import XMonad.Hooks.ManageDocks (ToggleStruts(..), avoidStruts, docks)
|
||||||
|
import XMonad.Hooks.DynamicProperty (dynamicPropertyChange)
|
||||||
|
import XMonad.Hooks.SetWMName (setWMName)
|
||||||
|
import XMonad.Hooks.WorkspaceHistory (workspaceHistoryHook)
|
||||||
|
|
||||||
|
import XMonad.Layout.Spacing (Spacing, spacingRaw, Border (..))
|
||||||
|
import XMonad.Layout.LayoutModifier (ModifiedLayout)
|
||||||
|
import XMonad.Layout.Renamed (renamed, Rename (..))
|
||||||
|
import XMonad.Layout.NoBorders (noBorders, smartBorders)
|
||||||
|
|
||||||
import XMonad.Util.WorkspaceCompare ( getSortByIndex, filterOutWs )
|
import XMonad.Util.WorkspaceCompare ( getSortByIndex, filterOutWs )
|
||||||
|
import XMonad.Util.NamedScratchpad (NamedScratchpad (NS), customFloating, defaultFloating, namedScratchpadAction, namedScratchpadManageHook)
|
||||||
|
import XMonad.Util.Run (proc, inProgram, termInDir, (>-$), (>->), execute, spawnPipe, spawnExternalProcess, hPutStrLn)
|
||||||
|
import XMonad.Util.Cursor (setDefaultCursor)
|
||||||
|
import XMonad.Util.SpawnOnce (spawnOnce)
|
||||||
|
import XMonad.Util.EZConfig (additionalKeysP)
|
||||||
|
|
||||||
|
import XMonad.Prompt (XPConfig (..), mkXPrompt, mkComplFunFromList', XPPosition (..))
|
||||||
|
import XMonad.Prompt.Workspace (Wor(..))
|
||||||
|
import XMonad.Prompt.FuzzyMatch (fuzzyMatch, fuzzySort)
|
||||||
|
import XMonad.Prompt.Shell (shellPrompt, unsafePrompt)
|
||||||
|
|
||||||
|
import Text.Regex.Posix ((=~))
|
||||||
|
|
||||||
-- variables
|
-- variables
|
||||||
myTerminal = "alacritty"
|
myTerminal = "alacritty"
|
||||||
|
myBrowser = "librewolf"
|
||||||
myBorderWidth = 1
|
myBorderWidth = 1
|
||||||
myNormalBorderColor = "#dcdccc"
|
|
||||||
myFocusedBorderColor = "#dca3a3"
|
|
||||||
myModMask = mod4Mask
|
myModMask = mod4Mask
|
||||||
|
white = "#dcdccc"
|
||||||
|
yellow = "#efef8f"
|
||||||
|
orange = "#ffcfaf"
|
||||||
|
red = "#dca3a3"
|
||||||
|
blue = "#8cd0d3"
|
||||||
|
darkBlue = "#8c8cbc"
|
||||||
|
green = "#7f9f7f"
|
||||||
|
grey = "#3f3f3f"
|
||||||
|
darkGrey = "#262626"
|
||||||
|
|
||||||
-- scratchpads
|
-- scratchpads
|
||||||
myScratchpads :: [NamedScratchpad]
|
myScratchpads :: [NamedScratchpad]
|
||||||
@ -48,9 +54,11 @@ myScratchpads =
|
|||||||
, NS "vimwiki" "st -t vimwiki -e vwwrapper" (title =? "vimwiki") (customFloating $ W.RationalRect (1/6) (1/6) (2/3) (2/3))
|
, NS "vimwiki" "st -t vimwiki -e vwwrapper" (title =? "vimwiki") (customFloating $ W.RationalRect (1/6) (1/6) (2/3) (2/3))
|
||||||
, NS "keepassxc" "keepassxc ~/dokumente/Database.kdbx" (title =? "Database.kdbx - KeePassXC" <||> title =? "Database.kdbx [Gesperrt] - KeePassXC") defaultFloating
|
, NS "keepassxc" "keepassxc ~/dokumente/Database.kdbx" (title =? "Database.kdbx - KeePassXC" <||> title =? "Database.kdbx [Gesperrt] - KeePassXC") defaultFloating
|
||||||
, NS "discord" "firejail discord" (title *!? "Discord") (customFloating $ W.RationalRect (1/10) (1/10) (8/10) (8/10))
|
, NS "discord" "firejail discord" (title *!? "Discord") (customFloating $ W.RationalRect (1/10) (1/10) (8/10) (8/10))
|
||||||
|
, NS "qalculate" "qalculate-gtk" (title =? "Qalculate!") (customFloating $ W.RationalRect (3/6) (1/6) (1/6) (1/6))
|
||||||
|
, NS "pavucontrol" "pavucontrol" (title =? "Lautstärkeregler") (customFloating $ W.RationalRect (1/6) (1/6) (2/3) (2/3))
|
||||||
]
|
]
|
||||||
|
|
||||||
-- Topic Space
|
-- topic space
|
||||||
topicItems :: [TopicItem]
|
topicItems :: [TopicItem]
|
||||||
topicItems =
|
topicItems =
|
||||||
[ noAction "1" "~/"
|
[ noAction "1" "~/"
|
||||||
@ -58,7 +66,7 @@ topicItems =
|
|||||||
, noAction "3" "~/"
|
, noAction "3" "~/"
|
||||||
, noAction "4" "~/"
|
, noAction "4" "~/"
|
||||||
, noAction "5" "~/"
|
, noAction "5" "~/"
|
||||||
, TI "recipes" "~/projekte/recipes" (switchToLayout "Programming" *> spawnShellAndExecute "hugo server" *> proc (inProgram "librewolf") *> spawnEditor)
|
, TI "recipes" "~/projekte/recipes" (switchToLayout "Programming" *> spawnShellAndExecute "hugo server" *> proc (inProgram myBrowser) *> spawnEditor)
|
||||||
, TI "alkaa" "~/projekte/alkaa" (switchToLayout "Programming" *> spawnShell *> spawnEditor)
|
, TI "alkaa" "~/projekte/alkaa" (switchToLayout "Programming" *> spawnShell *> spawnEditor)
|
||||||
, TI "steam" "~" (switchToLayout "Steam" *> spawn "steam")
|
, TI "steam" "~" (switchToLayout "Steam" *> spawn "steam")
|
||||||
, TI "game" "~" (switchToLayout "Full")
|
, TI "game" "~" (switchToLayout "Full")
|
||||||
@ -70,8 +78,8 @@ myTopicConfig :: TopicConfig
|
|||||||
myTopicConfig = def
|
myTopicConfig = def
|
||||||
{ topicDirs = tiDirs topicItems
|
{ topicDirs = tiDirs topicItems
|
||||||
, topicActions = tiActions topicItems
|
, topicActions = tiActions topicItems
|
||||||
, defaultTopicAction = const (pure ()) -- by default, do nothing
|
, defaultTopicAction = const (pure ())
|
||||||
, defaultTopic = "1" -- fallback
|
, defaultTopic = "1"
|
||||||
}
|
}
|
||||||
|
|
||||||
spawnShell :: X ()
|
spawnShell :: X ()
|
||||||
@ -98,22 +106,38 @@ myWorkSpacePrompt c job = do ws <- gets (W.workspaces . windowset)
|
|||||||
|
|
||||||
topicPrompt :: XPConfig
|
topicPrompt :: XPConfig
|
||||||
topicPrompt = def
|
topicPrompt = def
|
||||||
{ historySize = 0 -- No history in the prompt.
|
{ historySize = 0
|
||||||
, fgColor = "#dcdccc"
|
, fgColor = white
|
||||||
, fgHLight = "#3f3f3f"
|
, fgHLight = grey
|
||||||
, bgHLight = "#dca3a3"
|
, bgHLight = red
|
||||||
, alwaysHighlight = True -- Current best match
|
, alwaysHighlight = True
|
||||||
, font = "xft:Iosevka-11"
|
, font = "xft:Iosevka-11"
|
||||||
, height = 25
|
, height = 25
|
||||||
, position = CenteredAt 0.45 0.3
|
, position = CenteredAt 0.45 0.3
|
||||||
, promptBorderWidth = myBorderWidth -- Fit in with rest of config
|
, promptBorderWidth = myBorderWidth
|
||||||
, borderColor = "#dca3a3"
|
, borderColor = red
|
||||||
, maxComplRows = Just 10 -- Max rows to show in completion window
|
, maxComplRows = Just 10
|
||||||
, maxComplColumns = Just 1
|
, maxComplColumns = Just 1
|
||||||
, searchPredicate = fuzzyMatch
|
, searchPredicate = fuzzyMatch
|
||||||
, sorter = fuzzySort
|
, sorter = fuzzySort
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- search
|
||||||
|
searx :: SearchEngine
|
||||||
|
searx = searchEngine "searx" "https://search.tfld.de/search?q="
|
||||||
|
|
||||||
|
wiktionary :: SearchEngine
|
||||||
|
wiktionary = searchEngine "wiktionary" "https://wiktionary.org/w/index.php?search="
|
||||||
|
|
||||||
|
searchList :: [(String, SearchEngine)]
|
||||||
|
searchList = [ ("o", openstreetmap)
|
||||||
|
, ("h", hackage)
|
||||||
|
, ("w", wikipedia)
|
||||||
|
, ("y", youtube)
|
||||||
|
, ("s", searx)
|
||||||
|
, ("t", wiktionary)
|
||||||
|
]
|
||||||
|
|
||||||
-- keybindings
|
-- keybindings
|
||||||
myAdditionalKeys :: [(String, X ())]
|
myAdditionalKeys :: [(String, X ())]
|
||||||
myAdditionalKeys =
|
myAdditionalKeys =
|
||||||
@ -131,9 +155,8 @@ myAdditionalKeys =
|
|||||||
, ("M-.", sendMessage ToggleStruts)
|
, ("M-.", sendMessage ToggleStruts)
|
||||||
|
|
||||||
-- dmenu prompts
|
-- dmenu prompts
|
||||||
, ("M-<Return>", spawn "dm-recent-aliases")
|
, ("M-<Return>", spawn "dmenu_run")
|
||||||
, ("M-p p", shellPrompt topicPrompt)
|
, ("M-p s", spawn "dmenu_scrreenshot")
|
||||||
, ("M-p s", spawn "dm-screenshot")
|
|
||||||
, ("M-p k", spawn "dm-kill")
|
, ("M-p k", spawn "dm-kill")
|
||||||
|
|
||||||
-- scratchpads
|
-- scratchpads
|
||||||
@ -144,14 +167,16 @@ myAdditionalKeys =
|
|||||||
|
|
||||||
, ("M-S-a", namedScratchpadAction myScratchpads "keepassxc")
|
, ("M-S-a", namedScratchpadAction myScratchpads "keepassxc")
|
||||||
, ("M-n", namedScratchpadAction myScratchpads "nnn")
|
, ("M-n", namedScratchpadAction myScratchpads "nnn")
|
||||||
|
, ("M-s a", namedScratchpadAction myScratchpads "pavucontrol")
|
||||||
|
, ("M-s q", namedScratchpadAction myScratchpads "qalculate")
|
||||||
|
|
||||||
-- some shortcuts for prorgrams
|
-- some shortcuts for prorgrams
|
||||||
, ("M-S-<Return>", spawnShell)
|
, ("M-S-<Return>", spawnShell)
|
||||||
, ("M-b", spawn "librewolf")
|
, ("M-b", spawn myBrowser)
|
||||||
|
|
||||||
-- layout
|
-- layout
|
||||||
, ("M-t t", switchToLayout "Tall")
|
, ("M-t t", switchToLayout "Tall")
|
||||||
, ("M-t h", switchToLayout "Programming")
|
, ("M-t p", switchToLayout "Programming")
|
||||||
, ("M-t f", switchToLayout "Full")
|
, ("M-t f", switchToLayout "Full")
|
||||||
|
|
||||||
, ("M-S-f", withFocused $ windows . W.sink)
|
, ("M-S-f", withFocused $ windows . W.sink)
|
||||||
@ -178,9 +203,12 @@ myAdditionalKeys =
|
|||||||
| (i, k) <- zip (topicNames topicItems) (map show [1 .. 5 :: Int])
|
| (i, k) <- zip (topicNames topicItems) (map show [1 .. 5 :: Int])
|
||||||
, (f, m) <- [(switchTopic myTopicConfig, ""), (windows . W.shift, "S-")]
|
, (f, m) <- [(switchTopic myTopicConfig, ""), (windows . W.shift, "S-")]
|
||||||
]
|
]
|
||||||
|
-- Search commands
|
||||||
|
++ [("M-d " ++ k, promptSearch topicPrompt f) | (k,f) <- searchList ]
|
||||||
|
++ [("M-S-d " ++ k, selectSearch f) | (k,f) <- searchList ]
|
||||||
|
|
||||||
-- Layouts
|
-- Layouts
|
||||||
mySpacing :: Integer -> l a -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l a
|
mySpacing :: Integer -> l a -> ModifiedLayout Spacing l a
|
||||||
mySpacing i = spacingRaw True (Border i i i i) True (Border i i i i) True
|
mySpacing i = spacingRaw True (Border i i i i) True (Border i i i i) True
|
||||||
|
|
||||||
myLayout = avoidStruts $ tiling ||| hacking ||| full ||| steam
|
myLayout = avoidStruts $ tiling ||| hacking ||| full ||| steam
|
||||||
@ -188,7 +216,7 @@ myLayout = avoidStruts $ tiling ||| hacking ||| full ||| steam
|
|||||||
tiling = renamed [Replace "Tall"] $ smartBorders $ mySpacing 6 $ Tall 1 (3/100) (1/2)
|
tiling = renamed [Replace "Tall"] $ smartBorders $ mySpacing 6 $ Tall 1 (3/100) (1/2)
|
||||||
hacking = renamed [Replace "Programming"] $ smartBorders $ mySpacing 6 $ Tall 1 (3/100) (5/8)
|
hacking = renamed [Replace "Programming"] $ smartBorders $ mySpacing 6 $ Tall 1 (3/100) (5/8)
|
||||||
full = noBorders Full
|
full = noBorders Full
|
||||||
steam = renamed [Replace "Steam"] $ noBorders $ mySpacing 3 $ limitWindows 2 $ ThreeCol 1 (3/100) (5/8)
|
steam = renamed [Replace "Steam"] $ noBorders $ mySpacing 3 $ Tall 1 (3/100) (6/8)
|
||||||
|
|
||||||
-- Regex lifted up to use in manageHook
|
-- Regex lifted up to use in manageHook
|
||||||
(*!?) :: Functor f => f String -> String -> f Bool
|
(*!?) :: Functor f => f String -> String -> f Bool
|
||||||
@ -202,7 +230,7 @@ myManageHook = composeAll . concat $
|
|||||||
|
|
||||||
-- Steam and games
|
-- Steam and games
|
||||||
, [ className =? "Steam" --> doShift "steam" ]
|
, [ className =? "Steam" --> doShift "steam" ]
|
||||||
, [ ( className =? "Steam" <&&> title *!? "Friends List" <||> title *!? "News" ) --> doF W.swapDown ]
|
, [ (title *!? "Friends List" <||> title *!? "News" ) --> doF W.swapDown ]
|
||||||
, [ title =? t <&&> title *!? t --> doShift "game" | t <- myGames ]
|
, [ title =? t <&&> title *!? t --> doShift "game" | t <- myGames ]
|
||||||
|
|
||||||
-- float specific classes
|
-- float specific classes
|
||||||
@ -216,15 +244,6 @@ myManageHook = composeAll . concat $
|
|||||||
myFloatingClasses = ["Gimp", "Origin"]
|
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"]
|
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 =? "Database.kdbx - KeePassXC" <||> title =? "Database.kdbx [Gesperrt] - KeePassXC" --> floating)
|
myEventHook = dynamicPropertyChange "WM_NAME" (title =? "Database.kdbx - KeePassXC" <||> title =? "Database.kdbx [Gesperrt] - KeePassXC" --> floating)
|
||||||
where floating = customFloating $ W.RationalRect (1/8) (1/8) (3/4) (3/4)
|
where floating = customFloating $ W.RationalRect (1/8) (1/8) (3/4) (3/4)
|
||||||
|
|
||||||
@ -232,30 +251,28 @@ myEventHook = dynamicPropertyChange "WM_NAME" (title =? "Database.kdbx - KeePass
|
|||||||
myStartupHook = do
|
myStartupHook = do
|
||||||
setWMName "LG3D"
|
setWMName "LG3D"
|
||||||
setDefaultCursor xC_left_ptr
|
setDefaultCursor xC_left_ptr
|
||||||
spawnOnce("redshift -c /home/max/.config/redshift/redshiftrc")
|
spawnOnce "redshift -c /home/max/.config/redshift/redshiftrc"
|
||||||
spawnOnce("feh --bg-fill ~/bilder/bg.jpg")
|
spawnOnce "feh --bg-fill ~/bilder/bg.jpg"
|
||||||
spawnOnce("/usr/bin/syncthing -no-browser -logfile=default")
|
spawnOnce "/usr/bin/syncthing -no-browser -logfile=default"
|
||||||
|
|
||||||
-- Main
|
-- Main
|
||||||
main = do
|
main = do
|
||||||
xmproc <- spawnPipe "xmobar /home/max/.config/xmobar/xmobarrc"
|
xmproc <- spawnPipe "xmobar /home/max/.config/xmobar/xmobarrc"
|
||||||
xmonad $ spawnExternalProcess def $ docks $ def {
|
xmonad $ spawnExternalProcess def $ docks $ def {
|
||||||
-- simple stuff
|
|
||||||
terminal = myTerminal,
|
terminal = myTerminal,
|
||||||
borderWidth = myBorderWidth,
|
borderWidth = myBorderWidth,
|
||||||
modMask = myModMask,
|
modMask = myModMask,
|
||||||
workspaces = topicNames topicItems,
|
workspaces = topicNames topicItems,
|
||||||
normalBorderColor = myNormalBorderColor,
|
normalBorderColor = white,
|
||||||
focusedBorderColor = myFocusedBorderColor,
|
focusedBorderColor = red,
|
||||||
-- hooks, layouts
|
|
||||||
layoutHook = myLayout,
|
layoutHook = myLayout,
|
||||||
manageHook = myManageHook,
|
manageHook = myManageHook,
|
||||||
handleEventHook = myEventHook,
|
handleEventHook = myEventHook,
|
||||||
logHook = workspaceHistoryHook >> (dynamicLogWithPP $ filterOutWsPP ["NSP"] $ xmobarPP {
|
logHook = workspaceHistoryHook >> dynamicLogWithPP (filterOutWsPP ["NSP"] $ xmobarPP {
|
||||||
ppCurrent = xmobarColor "#dca3a3" "" . wrap "[ " " ]",
|
ppCurrent = xmobarColor red "" . wrap "[ " " ]",
|
||||||
ppHidden = xmobarColor "#8cd0d3" "",
|
ppHidden = xmobarColor blue "",
|
||||||
ppLayout = xmobarColor "#8c8cbc" "",
|
ppLayout = xmobarColor darkBlue "",
|
||||||
ppTitle = xmobarColor "#ffcfaf" "" . shorten 90,
|
ppTitle = xmobarColor orange "" . shorten 90,
|
||||||
ppSep = " | ",
|
ppSep = " | ",
|
||||||
ppOutput = hPutStrLn xmproc
|
ppOutput = hPutStrLn xmproc
|
||||||
}),
|
}),
|
||||||
|
Loading…
Reference in New Issue
Block a user