diff options
Diffstat (limited to '')
-rw-r--r-- | src/lib/XMonad/Custom/Bindings.hs (renamed from src/XMonad/Custom/Bindings.hs) | 34 |
1 files changed, 16 insertions, 18 deletions
diff --git a/src/XMonad/Custom/Bindings.hs b/src/lib/XMonad/Custom/Bindings.hs index de0fd26..208ccdf 100644 --- a/src/XMonad/Custom/Bindings.hs +++ b/src/lib/XMonad/Custom/Bindings.hs @@ -1,12 +1,13 @@ {-# LANGUAGE LambdaCase #-} -- | --- Module : XMonad.Custom.Bindings --- Copyright : (c) 2018-2020 Azat Bahawi <azahi@teknik.io> --- License : BSD3-style (see LICENSE) --- Maintainer : Azat Bahawi <azahi@teknik.io> --- Stability : unstable --- Portability : unportable +-- Module : XMonad.Custom.Bindings +-- Description : Key bindings and keys configuration +-- Copyright : (c) Azat Bahawi 2018-2021 +-- SPDX-License-Identifier : GPL-3.0-or-later +-- Maintainer : azahi@teknik.io +-- Stability : experimental +-- Portability : non-portable -- module XMonad.Custom.Bindings @@ -29,10 +30,8 @@ import XMonad.Actions.DynamicWorkspaces import qualified XMonad.Actions.FlexibleManipulate as F import XMonad.Actions.FloatSnap -import XMonad.Actions.FloatSnapSpaced import XMonad.Actions.MessageFeedback import XMonad.Actions.Navigation2D -import XMonad.Actions.PerConditionKeys import XMonad.Actions.Promote import XMonad.Actions.UpdatePointer import XMonad.Actions.WithAll @@ -70,6 +69,7 @@ wsKeys = map show [1 .. 9 :: Int] zipKeys :: [a] -> [[a]] -> [t1] -> (t1 -> b) -> [([a], b)] zipKeys m ks as f = zipWith (\k d -> (m ++ k, f d)) ks as + zipKeys' :: [a] -> [[a]] -> [t1] -> (t1 -> t2 -> b) -> t2 -> [([a], b)] zipKeys' m ks as f b = zipWith (\k d -> (m ++ k, f d b)) ks as @@ -126,8 +126,9 @@ rawKeys c = withUpdatePointer $ concatMap ($ c) keymaps keysBase :: XConfig Layout -> [(String, X ())] keysBase _ = [ ("M-S-q", confirmPrompt hotPromptTheme "Quit XMonad?" $ io exitSuccess) - , ("M-q" , spawn "xmonad --restart") -- TODO Replace with interal calls - , ("M-C-q", spawn "xmonad --recompile && xmonad --restart") + , ("M-q" , spawn "xmonad --restart") + , -- TODO Replace with interal calls + ("M-C-q", spawn "xmonad --recompile && xmonad --restart") , ("M-x" , shellPrompt promptTheme) , ("M-w" , windowPrompt promptTheme Goto allWindows) , ("M-S-w", windowPrompt promptTheme Bring allWindows) @@ -135,8 +136,9 @@ keysBase _ = keysSystem :: XConfig Layout -> [(String, X ())] keysSystem _ = - [ ("M-C-g" , return ()) -- TODO Replace scripts with internal functions - , ("<XF86ScreenSaver>", spawn "~/.xmonad/scripts/screenlock.sh") + [ ("M-C-g" , return ()) + , -- TODO Replace scripts with internal functions + ("<XF86ScreenSaver>", spawn "~/.xmonad/scripts/screenlock.sh") , ("M-<Print>", spawn "~/.xmonad/scripts/xshot-upload.sh") , ("M-S-<Print>", spawn "~/.xmonad/scripts/xshot-select-upload.sh") , ("M-C-c", spawn "~/.xmonad/scripts/toggle-compton.sh") @@ -189,17 +191,13 @@ keysWindows _ = [ ("M-d" , kill) , ("M-S-d", confirmPrompt hotPromptTheme "Kill all" killAll) , ("M-a" , toggleCopyToAll) - , ("M-e" , withFocused hideWindow) -- FIXME This is so broken + , ("M-e" , withFocused hideWindow) , ("M-S-e", popOldestHiddenWindow) , ("M-p" , promote) , ("M-g", withFocused $ sendMessage . MergeAll) , ("M-S-g", withFocused $ sendMessage . UnMerge) , ("M-u" , focusUrgent) , ("M-s" , windows S.focusMaster) - , ( "M-'" - , bindOn LD [("Tabs", windows S.focusDown), ("", onGroup S.focusDown')] - ) - , ("M-;", bindOn LD [("Tabs", windows S.focusUp), ("", onGroup S.focusUp')]) , ("M-S-'", windows S.swapDown) , ("M-S-;", windows S.swapUp) ] @@ -245,7 +243,7 @@ mouseBindings XConfig{} = M.fromList , \w -> focus w >> F.mouseWindow F.position w - >> ifClick (snapSpacedMagicMove gapFull (Just 50) (Just 50) w) + >> ifClick (snapMagicMove (Just 50) (Just 50) w) >> windows S.shiftMaster ) , ( (modMask, button3) |