first commit
This commit is contained in:
1
prompt-history
Normal file
1
prompt-history
Normal file
@@ -0,0 +1 @@
|
|||||||
|
fromList [("",["l","Home.1","Browser","Browser.1","Home.2","Media","Home","Home","Programming","5","mail","mail","4","3","2","1","mail","mail","mail","mail","1","mail","mail","mail","1","mail","mail","1","mail","mail","1","","mail","3","2","mail","mail","mail","4","3","2","1","","1","mail","mail","mail","mail","4","3","2","1","mail","vms","vms","2","vms","netflix","netflix","netflix","netflix","ne","netflix","netflix","etflix","1","","mail","mail","1","mail","mail","1","mail","mail","4","3","","2","1","mail","mail","2","4","3","2","1","mail","1","mail","mail","mail","5","4","3","2","mail","mail","mail","ma","mail","ma","mail","mail","mail","1","1","1","1","netfil","ne","1","1","1","4","4","3","netfil","netfil","netfil","ne","3","netfil","ma","mail","mail","5","3","1","2","7","7","7","9","1","9","1","","4","3","2","1","1","3","2","2","3","1","1","1","2","w2","3","2","1","1","1","1","2","1","2","3","3","3","2","3","2","2","2","1","2"]),("New workspace name: ",["1","2"]),("Run or Raise: ",["emacs","firefox","firef"]),("Run: ",["lux -S 20%","lux -S 50%","lux -S 15%","lux -S 40%","lux -S 30%","unclutter","unclutter","unclutter","lux -S 10%","unclutter","compton -b","st","lux -S 20%","redshift","lux -S 20%","systemctl suspend","systemctl suspend","lux -S 10%","lux -S 10%","lux -S 20%","lux -S 10%","systemctl suspend","lux -S 10%","lux -S 10%","lux -S 15%","lux -S 10%"])]
|
BIN
xmonad-x86_64-linux
Executable file
BIN
xmonad-x86_64-linux
Executable file
Binary file not shown.
7
xmonad.errors
Normal file
7
xmonad.errors
Normal file
@@ -0,0 +1,7 @@
|
|||||||
|
|
||||||
|
xmonad.hs:125:63: warning: [-Wdeprecations]
|
||||||
|
In the use of ‘spacing’ (imported from XMonad.Layout.Spacing):
|
||||||
|
Deprecated: "Use spacingRaw instead."
|
||||||
|
|
|
||||||
|
125 | , layoutHook = avoidStruts $ (hiddenWindows $ (maximize $ (spacing 4 $ myLayouts)))
|
||||||
|
| ^^^^^^^
|
476
xmonad.hs
Normal file
476
xmonad.hs
Normal file
@@ -0,0 +1,476 @@
|
|||||||
|
-- imports
|
||||||
|
import XMonad
|
||||||
|
import XMonad.Util.EZConfig
|
||||||
|
import XMonad.Config.Kde
|
||||||
|
import XMonad.Layout.SubLayouts
|
||||||
|
import XMonad.Layout.PerWorkspace
|
||||||
|
import XMonad.Layout.LayoutModifier
|
||||||
|
import XMonad.Layout.Magnifier
|
||||||
|
import XMonad.Layout.Master
|
||||||
|
import XMonad.Layout.Mosaic
|
||||||
|
import XMonad.Layout.MosaicAlt
|
||||||
|
import XMonad.Layout.Spacing
|
||||||
|
import XMonad.Layout.WindowArranger
|
||||||
|
import XMonad.Layout.WindowNavigation as N
|
||||||
|
import XMonad.Layout.Hidden
|
||||||
|
import XMonad.Layout.Groups.Wmii
|
||||||
|
import XMonad.Actions.Submap
|
||||||
|
import XMonad.Hooks.ManageDocks
|
||||||
|
import qualified Data.Map as M
|
||||||
|
import qualified XMonad.Layout.Groups as G
|
||||||
|
import XMonad.Layout.Master
|
||||||
|
import qualified XMonad.Layout.BinarySpacePartition as BSP
|
||||||
|
import XMonad.Hooks.DynamicLog
|
||||||
|
import XMonad.Layout.Hidden
|
||||||
|
import XMonad.Layout.Stoppable
|
||||||
|
import XMonad.Hooks.EwmhDesktops
|
||||||
|
import XMonad.Layout.Spacing
|
||||||
|
import qualified XMonad.StackSet as W
|
||||||
|
import XMonad.Actions.CopyWindow
|
||||||
|
import Data.Monoid
|
||||||
|
import System.Exit
|
||||||
|
import Data.List
|
||||||
|
import XMonad.Layout.ToggleLayouts
|
||||||
|
import XMonad.Layout.LayoutScreens
|
||||||
|
import XMonad.Layout.TwoPane
|
||||||
|
import XMonad.Layout.ZoomRow
|
||||||
|
import XMonad.Layout.Combo
|
||||||
|
import XMonad.Layout.Groups.Examples
|
||||||
|
import XMonad.Layout.BinaryColumn
|
||||||
|
import qualified XMonad.Layout.GridVariants as GV
|
||||||
|
import XMonad.Layout.AutoMaster
|
||||||
|
import XMonad.Layout.Master
|
||||||
|
import qualified XMonad.Layout.MultiToggle as MT
|
||||||
|
import XMonad.Prompt
|
||||||
|
import XMonad.Prompt.RunOrRaise
|
||||||
|
import XMonad.Prompt.Shell
|
||||||
|
import XMonad.Layout.Groups.Helpers
|
||||||
|
import XMonad.Actions.FocusNth
|
||||||
|
import XMonad.Layout.ResizableTile
|
||||||
|
import XMonad.Layout.DwmStyle
|
||||||
|
import XMonad.Layout.Spacing
|
||||||
|
import XMonad.Layout.Maximize
|
||||||
|
import XMonad.Actions.DynamicWorkspaces
|
||||||
|
import XMonad.Actions.Navigation2D
|
||||||
|
import XMonad.Actions.CycleWS
|
||||||
|
import Data.Tree
|
||||||
|
import XMonad.Actions.TreeSelect
|
||||||
|
import XMonad.Hooks.WorkspaceHistory
|
||||||
|
import XMonad.Actions.TagWindows
|
||||||
|
import XMonad.Actions.LinkWorkspaces
|
||||||
|
|
||||||
|
myLayouts =
|
||||||
|
-- subLayout [] (ResizableTall 0 (3/100) (1/2) []) $ (Mirror $ ResizableTall 0 (3/100) (1/2) []) |||
|
||||||
|
BSP.emptyBSP |||
|
||||||
|
rowOfColumns |||
|
||||||
|
Mirror rowOfColumns |||
|
||||||
|
mastered (1/100) (1/2) rowOfColumns
|
||||||
|
|
||||||
|
-- ||| Tall 1 (3/100) (1/2) ||| mosaic 2 [3,2]
|
||||||
|
|
||||||
|
myWorkspaces :: Forest String
|
||||||
|
myWorkspaces = [ Node "Home" -- for everyday activity's
|
||||||
|
[ Node "1" [] -- with 4 extra sub-workspaces, for even more activity's
|
||||||
|
, Node "2" []
|
||||||
|
, Node "3" []
|
||||||
|
, Node "4" []
|
||||||
|
]
|
||||||
|
, Node "Browser"
|
||||||
|
[ Node "1" []
|
||||||
|
, Node "2" []
|
||||||
|
, Node "3" []
|
||||||
|
]
|
||||||
|
, Node "Programming" -- for all your programming needs
|
||||||
|
[ Node "Intelij" []
|
||||||
|
, Node "Docs" [] -- documentation
|
||||||
|
, Node "1" []
|
||||||
|
, Node "2" []
|
||||||
|
]
|
||||||
|
, Node "Mail" []
|
||||||
|
, Node "Media"
|
||||||
|
[ Node "1" []
|
||||||
|
, Node "2" []
|
||||||
|
]
|
||||||
|
]
|
||||||
|
|
||||||
|
myTsConfig = TSConfig { ts_hidechildren = True
|
||||||
|
, ts_background = 0x00000000
|
||||||
|
, ts_font = "xft:Sans-14"
|
||||||
|
, ts_node = (0xff000000, 0xff50d0db)
|
||||||
|
, ts_nodealt = (0xff000000, 0xff10b8d6)
|
||||||
|
, ts_highlight = (0xffffffff, 0xffff0000)
|
||||||
|
, ts_extra = 0xff000000
|
||||||
|
, ts_node_width = 200
|
||||||
|
, ts_node_height = 30
|
||||||
|
, ts_originX = 0
|
||||||
|
, ts_originY = 0
|
||||||
|
, ts_indent = 80
|
||||||
|
, ts_navigate = defaultNavigation
|
||||||
|
}
|
||||||
|
|
||||||
|
-- float krunner and plasmashell
|
||||||
|
myManageHook = composeAll . concat $
|
||||||
|
[ [ className =? c --> doFloat | c <- myFloats] ]
|
||||||
|
|
||||||
|
where myFloats = ["plasmashell","krunner"]
|
||||||
|
|
||||||
|
main = xmonad $ withNavigation2DConfig def $ myconfig
|
||||||
|
|
||||||
|
myconfig = ewmh $ kdeConfig
|
||||||
|
{ manageHook = manageHook kdeConfig <+> myManageHook
|
||||||
|
, borderWidth = 2
|
||||||
|
, workspaces = toWorkspaces myWorkspaces
|
||||||
|
, modMask = mod4Mask
|
||||||
|
-- modifiers for all layouts, avoiding docks, hidding(minimizing) Windows, maximizing windows, window gaps
|
||||||
|
, layoutHook = avoidStruts $ (hiddenWindows $ (maximize $ (spacing 4 $ myLayouts)))
|
||||||
|
, logHook = workspaceHistoryHook >> dynamicLog
|
||||||
|
, terminal = "alacritty"
|
||||||
|
, normalBorderColor = "#1d252c"
|
||||||
|
, focusedBorderColor = "#cd8b00"
|
||||||
|
} `removeKeys`
|
||||||
|
[(mod1Mask .|. shiftMask, n) | n <- [xK_1 .. xK_9]
|
||||||
|
] `additionalKeysP`
|
||||||
|
[ -- ("M-S-<Return>", spawn $ Xmonad.terminal conf)
|
||||||
|
("M-<Space> <Space>", sendMessage NextLayout)
|
||||||
|
, ("M-S-C-r", spawn "xmonad --recompile; xmonad --restart > ~/.xmonad/xmonad.status")
|
||||||
|
, ("M-q", kill1)
|
||||||
|
--groups
|
||||||
|
, ("M-<Space> g k", swapUp)
|
||||||
|
, ("M-<Space> g j", swapDown)
|
||||||
|
, ("M-<Space> g S-k", swapGroupUp)
|
||||||
|
, ("M-<Space> g S-j", swapGroupDown)
|
||||||
|
, ("M-<Space> g C-k", moveToNewGroupUp)
|
||||||
|
, ("M-<Space> g C-j", moveToNewGroupDown)
|
||||||
|
, ("M-<Space> g M1-k", (moveToGroupUp True))
|
||||||
|
, ("M-<Space> g M1-j", (moveToGroupDown True))
|
||||||
|
, ("M-<Space> g i", zoomWindowIn)
|
||||||
|
, ("M-<Space> g o", zoomWindowOut)
|
||||||
|
, ("M-<Space> g S-i", zoomGroupIn)
|
||||||
|
, ("M-<Space> g S-o", zoomGroupOut)
|
||||||
|
, ("M-<Space> g S-f", toggleGroupFull)
|
||||||
|
, ("M-<Space> g f", toggleWindowFull)
|
||||||
|
, ("M-<Space> g r", zoomWindowReset)
|
||||||
|
, ("M-<Space> g n", groupToNextLayout)
|
||||||
|
, ("M-g k", swapUp)
|
||||||
|
, ("M-g j", swapDown)
|
||||||
|
, ("M-g S-k", swapGroupUp)
|
||||||
|
, ("M-g S-j", swapGroupDown)
|
||||||
|
, ("M-g C-k", moveToNewGroupUp)
|
||||||
|
, ("M-g C-j", moveToNewGroupDown)
|
||||||
|
, ("M-g M1-k", (moveToGroupUp True))
|
||||||
|
, ("M-g M1-j", (moveToGroupDown True))
|
||||||
|
, ("M-g i", zoomWindowIn)
|
||||||
|
, ("M-g o", zoomWindowOut)
|
||||||
|
, ("M-g S-i", zoomGroupIn)
|
||||||
|
, ("M-g S-o", zoomGroupOut)
|
||||||
|
, ("M-g S-f", toggleGroupFull)
|
||||||
|
, ("M-g f", toggleWindowFull)
|
||||||
|
, ("M-g r", zoomWindowReset)
|
||||||
|
, ("M-g n", groupToNextLayout)
|
||||||
|
, ("M-i", zoomWindowIn)
|
||||||
|
, ("M-o", zoomWindowOut)
|
||||||
|
, ("M-S-i", zoomGroupIn)
|
||||||
|
, ("M-S-o", zoomGroupOut)
|
||||||
|
-- workspaces
|
||||||
|
, ("M-<Space> <Tab> w", selectWorkspace def)
|
||||||
|
, ("M-<Space> <Tab> <Tab>", selectWorkspace def)
|
||||||
|
, ("M-<Space> e", selectWorkspace def)
|
||||||
|
, ("M-<Space> <Tab> x", removeWorkspace)
|
||||||
|
, ("M-<Space> <Tab> m", withWorkspace def (windows . W.shift))
|
||||||
|
, ("M-<Space> <Tab> c", withWorkspace def (windows . copy))
|
||||||
|
, ("M-<Space> m", withWorkspace def (windows . W.shift))
|
||||||
|
, ("M-<Space> c", withWorkspace def (windows . copy))
|
||||||
|
, ("M-<Space> <Tab> s", addWorkspacePrompt def)
|
||||||
|
, ("M-<Space> <Tab> r", renameWorkspace def)
|
||||||
|
, ("M-<Space> <Tab> j", nextWS)
|
||||||
|
, ("M-<Space> <Tab> k", prevWS)
|
||||||
|
, ("M-<Space> <Tab> S-j", shiftToNext)
|
||||||
|
, ("M-<Space> <Tab> S-k", shiftToPrev)
|
||||||
|
, ("M-<Space> <Tab> l", nextScreen)
|
||||||
|
, ("M-<Space> <Tab> h", prevScreen)
|
||||||
|
, ("M-<Space> <Tab> S-l", shiftNextScreen)
|
||||||
|
, ("M-<Space> <Tab> S-h", shiftPrevScreen)
|
||||||
|
, ("M-<Space> <Tab> z", toggleWS)
|
||||||
|
-- BSP
|
||||||
|
, ("M-M1-h", sendMessage $ BSP.ExpandTowards L)
|
||||||
|
, ("M-M1-l", sendMessage $ BSP.ExpandTowards R)
|
||||||
|
, ("M-M1-j", sendMessage $ BSP.ExpandTowards D)
|
||||||
|
, ("M-M1-k", sendMessage $ BSP.ExpandTowards U)
|
||||||
|
, ("M-<Space> b M1-j", sendMessage $ BSP.ExpandTowards D)
|
||||||
|
, ("M-<Space> b M1-l", sendMessage $ BSP.ShrinkFrom R)
|
||||||
|
, ("M-<Space> b M1-k", sendMessage $ BSP.ExpandTowards U)
|
||||||
|
, ("M-<Space> b M1-j", sendMessage $ BSP.ShrinkFrom D)
|
||||||
|
, ("M-<Space> b M1-C-h", sendMessage $ BSP.ShrinkFrom L)
|
||||||
|
, ("M-<Space> b M1-C-l", sendMessage $ BSP.ExpandTowards R)
|
||||||
|
, ("M-<Space> b M1-C-k", sendMessage $ BSP.ShrinkFrom U)
|
||||||
|
, ("M-<Space> b M1-C-j", sendMessage $ BSP.ExpandTowards D)
|
||||||
|
, ("M-<space> b s", sendMessage $ BSP.Swap)
|
||||||
|
, ("M-<Space> b r", sendMessage $ BSP.Rotate)
|
||||||
|
, ("M-<Space> b b", sendMessage $ BSP.Balance)
|
||||||
|
, ("m-<Space> b e", sendMessage $ BSP.Equalize)
|
||||||
|
, ("M-b M1-h", sendMessage $ BSP.ExpandTowards L)
|
||||||
|
, ("M-b M1-S-h", sendMessage $ BSP.ShrinkFrom R)
|
||||||
|
, ("M-b M1-k", sendMessage $ BSP.ExpandTowards U)
|
||||||
|
, ("M-b M1-S-k", sendMessage $ BSP.ShrinkFrom D)
|
||||||
|
, ("M-b M1-S-l", sendMessage $ BSP.ShrinkFrom L)
|
||||||
|
, ("M-b M1-l", sendMessage $ BSP.ExpandTowards R)
|
||||||
|
, ("M-b M1-S-j", sendMessage $ BSP.ShrinkFrom U)
|
||||||
|
, ("M-b M1-j", sendMessage $ BSP.ExpandTowards D)
|
||||||
|
, ("M-b s", sendMessage $ BSP.Swap)
|
||||||
|
, ("M-b r", sendMessage $ BSP.Rotate)
|
||||||
|
, ("M-b b", sendMessage $ BSP.Balance)
|
||||||
|
, ("m-b e", sendMessage $ BSP.Equalize)
|
||||||
|
--run or Copy
|
||||||
|
, ("M-<Space> r f", runOrCopy "firefox" (className =? "Firefox"))
|
||||||
|
, ("M-<Space> r e", runOrCopy "Doom Emacs" (className =? "Emacs"))
|
||||||
|
, ("M-<Space> r t", runOrCopy "Thunderbird" (className =? "Thunderbrid"))
|
||||||
|
-- Prompts
|
||||||
|
, ("M-p s", shellPrompt def)
|
||||||
|
-- subLayouts
|
||||||
|
-- navigation
|
||||||
|
-- Directional navigation of windows
|
||||||
|
, ("M-l", windowGo R False)
|
||||||
|
, ("M-h", windowGo L False)
|
||||||
|
, ("M-k", windowGo U False)
|
||||||
|
, ("M-j", windowGo D False)
|
||||||
|
|
||||||
|
-- -- Swap adjacent windows
|
||||||
|
, ("M-C-l", windowSwap R False)
|
||||||
|
, ("M-C-h", windowSwap L False)
|
||||||
|
, ("M-C-k", windowSwap U False)
|
||||||
|
, ("M-C-j", windowSwap D False)
|
||||||
|
-- --Arrange Windows
|
||||||
|
, ("M-a", sendMessage Arrange )
|
||||||
|
, ("M-S-a", sendMessage DeArrange )
|
||||||
|
, ("M-S-h", sendMessage (MoveLeft 1))
|
||||||
|
, ("M-S-l", sendMessage (MoveRight 1))
|
||||||
|
, ("M-S-j", sendMessage (MoveDown 1))
|
||||||
|
, ("M-S-k", sendMessage (MoveUp 1))
|
||||||
|
-- , ("M-M1-h", sendMessage (IncreaseLeft 1))
|
||||||
|
-- , ("M-M1-l", sendMessage (IncreaseRight 1))
|
||||||
|
-- , ("M-M1-j", sendMessage (IncreaseDown 1))
|
||||||
|
-- , ("M-M1-k", sendMessage (IncreaseUp 1))
|
||||||
|
-- , ("M-M1-S-h", sendMessage (DecreaseLeft 1))
|
||||||
|
-- , ("M-M1-S-l", sendMessage (DecreaseRight 1))
|
||||||
|
-- , ("M-M1-S-j", sendMessage (DecreaseDown 1))
|
||||||
|
-- , ("M-M1-S-k", sendMessage (DecreaseUp 1))
|
||||||
|
-- -- window
|
||||||
|
, ("M-<Space> w l", windowGo R False)
|
||||||
|
, ("M-<Space> w h", windowGo L False)
|
||||||
|
, ("M-<Space> w k", windowGo U False)
|
||||||
|
, ("M-<Space> w j", windowGo D False)
|
||||||
|
, ("M-<Space> w S-l", windowSwap R False)
|
||||||
|
, ("M-<Space> w S-h", windowSwap L False)
|
||||||
|
, ("M-<Space> w S-k", windowSwap U False)
|
||||||
|
, ("M-<Space> w S-j", windowSwap D False)
|
||||||
|
, ("M-<Space> w C-h", sendMessage (DecreaseLeft 1))
|
||||||
|
, ("M-<Space> w C-l", sendMessage (DecreaseRight 1))
|
||||||
|
, ("M-<Space> w C-j", sendMessage (DecreaseDown 1))
|
||||||
|
, ("M-<Space> w C-k", sendMessage (DecreaseUp 1))
|
||||||
|
, ("M-<Space> w M1-h", sendMessage (IncreaseLeft 1))
|
||||||
|
, ("M-<Space> w M1-l", sendMessage (IncreaseRight 1))
|
||||||
|
, ("M-<Space> w M1-j", sendMessage (IncreaseDown 1))
|
||||||
|
, ("M-<Space> w M1-k", sendMessage (IncreaseUp 1))
|
||||||
|
, ("M-<Space> w m", withFocused hideWindow)
|
||||||
|
, ("M-<Space> w S-m", popOldestHiddenWindow)
|
||||||
|
, ("M-<Space> w C-m", withFocused (sendMessage . maximizeRestore))
|
||||||
|
, ("M-<Space> w i", zoomWindowIn)
|
||||||
|
, ("M-<Space> w o", zoomWindowOut)
|
||||||
|
, ("M-<Space> w S-i", zoomGroupIn)
|
||||||
|
, ("M-<Space> w S-o", zoomGroupOut)
|
||||||
|
, ("M-<Space> w S-f", toggleGroupFull)
|
||||||
|
, ("M-<Space> w f", toggleWindowFull)
|
||||||
|
, ("M-<Space> w r", zoomWindowReset)
|
||||||
|
-- window
|
||||||
|
, ("M-w q", kill1)
|
||||||
|
, ("M-w l", windowGo R False)
|
||||||
|
, ("M-w h", windowGo L False)
|
||||||
|
, ("M-w k", windowGo U False)
|
||||||
|
, ("M-w j", windowGo D False)
|
||||||
|
, ("M-w S-l", windowSwap R False)
|
||||||
|
, ("M-w S-h", windowSwap L False)
|
||||||
|
, ("M-w S-k", windowSwap U False)
|
||||||
|
, ("M-w S-j", windowSwap D False)
|
||||||
|
, ("M-w C-h", sendMessage (DecreaseLeft 1))
|
||||||
|
, ("M-w C-l", sendMessage (DecreaseRight 1))
|
||||||
|
, ("M-w C-j", sendMessage (DecreaseDown 1))
|
||||||
|
, ("M-w C-k", sendMessage (DecreaseUp 1))
|
||||||
|
, ("M-w M1-h", sendMessage (IncreaseLeft 1))
|
||||||
|
, ("M-w M1-l", sendMessage (IncreaseRight 1))
|
||||||
|
, ("M-w M1-j", sendMessage (IncreaseDown 1))
|
||||||
|
, ("M-w M1-k", sendMessage (IncreaseUp 1))
|
||||||
|
, ("M-w m", withFocused hideWindow)
|
||||||
|
, ("M-w S-m", popOldestHiddenWindow)
|
||||||
|
, ("M-w C-m", withFocused (sendMessage . maximizeRestore))
|
||||||
|
, ("M-w i", zoomWindowIn)
|
||||||
|
, ("M-w o", zoomWindowOut)
|
||||||
|
, ("M-w S-i", zoomGroupIn)
|
||||||
|
, ("M-w S-o", zoomGroupOut)
|
||||||
|
, ("M-w S-f", toggleGroupFull)
|
||||||
|
, ("M-w f", toggleWindowFull)
|
||||||
|
, ("M-w r", zoomWindowReset)
|
||||||
|
, ("M-w <Tab> w", selectWorkspace def)
|
||||||
|
, ("M-w <Tab> <Tab>", selectWorkspace def)
|
||||||
|
, ("M-w e", selectWorkspace def)
|
||||||
|
, ("M-e", selectWorkspace def)
|
||||||
|
, ("M-w <Tab> x", removeWorkspace)
|
||||||
|
, ("M-w <Tab> m", withWorkspace def (windows . W.shift))
|
||||||
|
, ("M-w <Tab> c", withWorkspace def (windows . copy))
|
||||||
|
, ("M-c m", withWorkspace def (windows . W.shift))
|
||||||
|
, ("M-c c", withWorkspace def (windows . copy))
|
||||||
|
, ("M-w <Tab> s", addWorkspacePrompt def)
|
||||||
|
, ("M-w <Tab> r", renameWorkspace def)
|
||||||
|
, ("M-w <Tab> j", nextWS)
|
||||||
|
, ("M-w <Tab> k", prevWS)
|
||||||
|
, ("M-w <Tab> S-j", shiftToNext)
|
||||||
|
, ("M-w <Tab> S-k", shiftToPrev)
|
||||||
|
, ("M-w <Tab> l", nextScreen)
|
||||||
|
, ("M-w <Tab> h", prevScreen)
|
||||||
|
, ("M-w <Tab> S-l", shiftNextScreen)
|
||||||
|
, ("M-w <Tab> S-h", shiftPrevScreen)
|
||||||
|
, ("M-w <Tab> z", toggleWS)
|
||||||
|
, ("M-w b M1-h", sendMessage $ BSP.ExpandTowards L)
|
||||||
|
, ("M-w b M1-S-h", sendMessage $ BSP.ShrinkFrom R)
|
||||||
|
, ("M-w b M1-k", sendMessage $ BSP.ExpandTowards U)
|
||||||
|
, ("M-w b M1-S-k", sendMessage $ BSP.ShrinkFrom D)
|
||||||
|
, ("M-w b M1-S-l", sendMessage $ BSP.ShrinkFrom L)
|
||||||
|
, ("M-w b M1-l", sendMessage $ BSP.ExpandTowards R)
|
||||||
|
, ("M-w b M1-S-j", sendMessage $ BSP.ShrinkFrom U)
|
||||||
|
, ("M-w b M1-j", sendMessage $ BSP.ExpandTowards D)
|
||||||
|
-- , ("M-M1-h", sendMessage $ BSP.ExpandTowards L)
|
||||||
|
-- , ("M-M1-S-h", sendMessage $ BSP.ShrinkFrom R)
|
||||||
|
-- , ("M-M1-k", sendMessage $ BSP.ExpandTowards U)
|
||||||
|
-- , ("M-M1-S-k", sendMessage $ BSP.ShrinkFrom D)
|
||||||
|
-- , ("M-M1-S-l", sendMessage $ BSP.ShrinkFrom L)
|
||||||
|
-- , ("M-M1-l", sendMessage $ BSP.ExpandTowards R)
|
||||||
|
-- , ("M-M1-S-j", sendMessage $ BSP.ShrinkFrom U)
|
||||||
|
-- , ("M-M1-j", sendMessage $ BSP.ExpandTowards D)
|
||||||
|
-- , ("M-w b s", sendMessage $ BSP.Swap)
|
||||||
|
, ("M-w b r", sendMessage $ BSP.Rotate)
|
||||||
|
, ("M-w b b", sendMessage $ BSP.Balance)
|
||||||
|
, ("m-w b e", sendMessage $ BSP.Equalize)
|
||||||
|
-- minimiz/maximize
|
||||||
|
, ("M-m", withFocused hideWindow)
|
||||||
|
, ("M-S-m", popOldestHiddenWindow)
|
||||||
|
, ("M-C-m", withFocused (sendMessage . maximizeRestore))
|
||||||
|
, ("M-<F1>", spawn "rofi_run -w")
|
||||||
|
, ("M-<F2>", spawn "rofi_run")
|
||||||
|
, ("M3-<F1>", spawn "rofi_run -w")
|
||||||
|
, ("M3-<F2>", spawn "rofi_run")
|
||||||
|
, ("M-f", treeselectWorkspace myTsConfig myWorkspaces W.greedyView)
|
||||||
|
, ("M-S-f", treeselectWorkspace myTsConfig myWorkspaces W.shift)
|
||||||
|
-- , ("M-C-1", setWorkspaceIndex 1)
|
||||||
|
-- , ("M-C-2", setWorkspaceIndex 2)
|
||||||
|
-- , ("M-C-3", setWorkspaceIndex 3)
|
||||||
|
-- , ("M-C-4", setWorkspaceIndex 4)
|
||||||
|
-- , ("M-C-5", setWorkspaceIndex 5)
|
||||||
|
-- , ("M-C-6", setWorkspaceIndex 6)
|
||||||
|
-- , ("M-C-7", setWorkspaceIndex 7)
|
||||||
|
-- , ("M-C-8", setWorkspaceIndex 8)
|
||||||
|
-- , ("M-C-9", setWorkspaceIndex 9)
|
||||||
|
-- tags
|
||||||
|
, ("M-<Space> t t 1", withFocused (addTag "1"))
|
||||||
|
, ("M-<Space> t t 2", withFocused (addTag "2"))
|
||||||
|
, ("M-<Space> t t 3", withFocused (addTag "3"))
|
||||||
|
, ("M-<Space> t t 4", withFocused (addTag "4"))
|
||||||
|
, ("M-<Space> t t 5", withFocused (addTag "5"))
|
||||||
|
, ("M-<Space> t t 6", withFocused (addTag "6"))
|
||||||
|
, ("M-<Space> t t 7", withFocused (addTag "7"))
|
||||||
|
, ("M-<Space> t t 8", withFocused (addTag "8"))
|
||||||
|
, ("M-<Space> t t 9", withFocused (addTag "9"))
|
||||||
|
, ("M-<Space> t t 0", withFocused (addTag "0"))
|
||||||
|
, ("M-<Space> t f 1", focusUpTaggedGlobal "1")
|
||||||
|
, ("M-<Space> t f 2", focusUpTaggedGlobal "2")
|
||||||
|
, ("M-<Space> t f 3", focusUpTaggedGlobal "3")
|
||||||
|
, ("M-<Space> t f 4", focusUpTaggedGlobal "4")
|
||||||
|
, ("M-<Space> t f 5", focusUpTaggedGlobal "5")
|
||||||
|
, ("M-<Space> t f 6", focusUpTaggedGlobal "6")
|
||||||
|
, ("M-<Space> t f 7", focusUpTaggedGlobal "7")
|
||||||
|
, ("M-<Space> t f 8", focusUpTaggedGlobal "8")
|
||||||
|
, ("M-<Space> t f 9", focusUpTaggedGlobal "9")
|
||||||
|
, ("M-<Space> t f 0", focusUpTaggedGlobal "0")
|
||||||
|
, ("M-<Space> t f C-1", focusDownTaggedGlobal "1")
|
||||||
|
, ("M-<Space> t f C-2", focusDownTaggedGlobal "2")
|
||||||
|
, ("M-<Space> t f C-3", focusDownTaggedGlobal "3")
|
||||||
|
, ("M-<Space> t f C-4", focusDownTaggedGlobal "4")
|
||||||
|
, ("M-<Space> t f C-5", focusDownTaggedGlobal "5")
|
||||||
|
, ("M-<Space> t f C-6", focusDownTaggedGlobal "6")
|
||||||
|
, ("M-<Space> t f C-7", focusDownTaggedGlobal "7")
|
||||||
|
, ("M-<Space> t f C-8", focusDownTaggedGlobal "8")
|
||||||
|
, ("M-<Space> t f C-9", focusDownTaggedGlobal "9")
|
||||||
|
, ("M-<Space> t f C-0", focusDownTaggedGlobal "0")
|
||||||
|
, ("M-<Space> t u", withFocused unTag)
|
||||||
|
, ("M-<Space> t a", tagPrompt def (\s -> withFocused (addTag s)))
|
||||||
|
, ("M-<Space> t x", tagDelPrompt def)
|
||||||
|
, ("M-t a 1", withFocused (addTag "1"))
|
||||||
|
, ("M-t a 2", withFocused (addTag "2"))
|
||||||
|
, ("M-t a 3", withFocused (addTag "3"))
|
||||||
|
, ("M-t a 4", withFocused (addTag "4"))
|
||||||
|
, ("M-t a 5", withFocused (addTag "5"))
|
||||||
|
, ("M-t a 6", withFocused (addTag "6"))
|
||||||
|
, ("M-t a 7", withFocused (addTag "7"))
|
||||||
|
, ("M-t a 8", withFocused (addTag "8"))
|
||||||
|
, ("M-t a 9", withFocused (addTag "9"))
|
||||||
|
, ("M-t a 0", withFocused (addTag "0"))
|
||||||
|
, ("M-t a q", withFocused (addTag "q"))
|
||||||
|
, ("M-t a w", withFocused (addTag "w"))
|
||||||
|
, ("M-t a e", withFocused (addTag "e"))
|
||||||
|
, ("M-t a r", withFocused (addTag "r"))
|
||||||
|
, ("M-t a t", withFocused (addTag "t"))
|
||||||
|
, ("M-t a z", withFocused (addTag "z"))
|
||||||
|
, ("M-t a u", withFocused (addTag "u"))
|
||||||
|
, ("M-t a i", withFocused (addTag "i"))
|
||||||
|
, ("M-t a o", withFocused (addTag "o"))
|
||||||
|
, ("M-t a p", withFocused (addTag "p"))
|
||||||
|
, ("M-t 1", focusUpTaggedGlobal "1")
|
||||||
|
, ("M-t 2", focusUpTaggedGlobal "2")
|
||||||
|
, ("M-t 3", focusUpTaggedGlobal "3")
|
||||||
|
, ("M-t 4", focusUpTaggedGlobal "4")
|
||||||
|
, ("M-t 5", focusUpTaggedGlobal "5")
|
||||||
|
, ("M-t 6", focusUpTaggedGlobal "6")
|
||||||
|
, ("M-t 7", focusUpTaggedGlobal "7")
|
||||||
|
, ("M-t 8", focusUpTaggedGlobal "8")
|
||||||
|
, ("M-t 9", focusUpTaggedGlobal "9")
|
||||||
|
, ("M-t 0", focusUpTaggedGlobal "0")
|
||||||
|
, ("M-t q", focusUpTaggedGlobal "q")
|
||||||
|
, ("M-t w", focusUpTaggedGlobal "w")
|
||||||
|
, ("M-t e", focusUpTaggedGlobal "e")
|
||||||
|
, ("M-t r", focusUpTaggedGlobal "r")
|
||||||
|
, ("M-t t", focusUpTaggedGlobal "t")
|
||||||
|
, ("M-t z", focusUpTaggedGlobal "z")
|
||||||
|
, ("M-t u", focusUpTaggedGlobal "u")
|
||||||
|
, ("M-t i", focusUpTaggedGlobal "i")
|
||||||
|
, ("M-t o", focusUpTaggedGlobal "o")
|
||||||
|
, ("M-t p", focusUpTaggedGlobal "p")
|
||||||
|
, ("M-t S-1", focusDownTaggedGlobal "1")
|
||||||
|
, ("M-t S-2", focusDownTaggedGlobal "2")
|
||||||
|
, ("M-t S-3", focusDownTaggedGlobal "3")
|
||||||
|
, ("M-t S-4", focusDownTaggedGlobal "4")
|
||||||
|
, ("M-t S-5", focusDownTaggedGlobal "5")
|
||||||
|
, ("M-t S-6", focusDownTaggedGlobal "6")
|
||||||
|
, ("M-t S-7", focusDownTaggedGlobal "7")
|
||||||
|
, ("M-t S-8", focusDownTaggedGlobal "8")
|
||||||
|
, ("M-t S-9", focusDownTaggedGlobal "9")
|
||||||
|
, ("M-t S-0", focusDownTaggedGlobal "0")
|
||||||
|
, ("M-t S-q", focusDownTaggedGlobal "q")
|
||||||
|
, ("M-t S-w", focusDownTaggedGlobal "w")
|
||||||
|
, ("M-t S-e", focusDownTaggedGlobal "e")
|
||||||
|
, ("M-t S-r", focusDownTaggedGlobal "r")
|
||||||
|
, ("M-t S-t", focusDownTaggedGlobal "t")
|
||||||
|
, ("M-t S-z", focusDownTaggedGlobal "z")
|
||||||
|
, ("M-t S-u", focusDownTaggedGlobal "u")
|
||||||
|
, ("M-t S-i", focusDownTaggedGlobal "i")
|
||||||
|
, ("M-t S-o", focusDownTaggedGlobal "o")
|
||||||
|
, ("M-t S-p", focusDownTaggedGlobal "p")
|
||||||
|
, ("M-<Space> s",withFocused $ windows . W.sink)
|
||||||
|
-- , ("M-c 1", copy 1)
|
||||||
|
-- , ("M-c 2", copy 2)
|
||||||
|
-- , ("M-c 3", copy 3)
|
||||||
|
-- , ("M-c 4", copy 4)
|
||||||
|
-- , ("M-c 5", copy 5)
|
||||||
|
-- , ("M-c 6", copy 6)
|
||||||
|
-- , ("M-c 7", copy 7)
|
||||||
|
-- , ("M-c 8", copy 8)
|
||||||
|
|
||||||
|
-- , ("M-c 9", copy 9)
|
||||||
|
]
|
608
xmonad.hs.b
Normal file
608
xmonad.hs.b
Normal file
@@ -0,0 +1,608 @@
|
|||||||
|
-- imports
|
||||||
|
import XMonad
|
||||||
|
import XMonad.Util.EZConfig
|
||||||
|
import XMonad.Config.Kde
|
||||||
|
import XMonad.Layout.SubLayouts
|
||||||
|
import XMonad.Layout.PerWorkspace
|
||||||
|
import XMonad.Layout.LayoutModifier
|
||||||
|
import XMonad.Layout.Magnifier
|
||||||
|
import XMonad.Layout.Master
|
||||||
|
import XMonad.Layout.Mosaic
|
||||||
|
import XMonad.Layout.MosaicAlt
|
||||||
|
import XMonad.Layout.Spacing
|
||||||
|
import XMonad.Layout.WindowArranger
|
||||||
|
import XMonad.Layout.WindowNavigation as N
|
||||||
|
import XMonad.Layout.Hidden
|
||||||
|
import XMonad.Layout.Groups.Wmii
|
||||||
|
import XMonad.Actions.Submap
|
||||||
|
import XMonad.Hooks.ManageDocks
|
||||||
|
import qualified Data.Map as M
|
||||||
|
import qualified XMonad.Layout.Groups as G
|
||||||
|
import XMonad.Layout.Master
|
||||||
|
import XMonad.Layout.BinarySpacePartition
|
||||||
|
import XMonad.Hooks.DynamicLog
|
||||||
|
import XMonad.Layout.Hidden
|
||||||
|
import XMonad.Layout.Stoppable
|
||||||
|
import XMonad.Hooks.EwmhDesktops
|
||||||
|
import XMonad.Layout.Spacing
|
||||||
|
import qualified XMonad.StackSet as W
|
||||||
|
import XMonad.Actions.CopyWindow
|
||||||
|
import Data.Monoid
|
||||||
|
import System.Exit
|
||||||
|
import Data.List
|
||||||
|
import XMonad.Layout.ToggleLayouts
|
||||||
|
import XMonad.Layout.LayoutScreens
|
||||||
|
import XMonad.Layout.TwoPane
|
||||||
|
import XMonad.Layout.ZoomRow
|
||||||
|
import XMonad.Layout.Combo
|
||||||
|
import XMonad.Layout.Groups.Examples
|
||||||
|
import XMonad.Layout.BinaryColumn
|
||||||
|
import qualified XMonad.Layout.GridVariants as GV
|
||||||
|
import XMonad.Layout.AutoMaster
|
||||||
|
import XMonad.Layout.Master
|
||||||
|
import qualified XMonad.Layout.MultiToggle as MT
|
||||||
|
import XMonad.Prompt
|
||||||
|
import XMonad.Prompt.RunOrRaise
|
||||||
|
import XMonad.Prompt.Shell
|
||||||
|
import XMonad.Layout.Groups.Helpers
|
||||||
|
import XMonad.Actions.FocusNth
|
||||||
|
import XMonad.Layout.ResizableTile
|
||||||
|
import XMonad.Layout.DwmStyle
|
||||||
|
import XMonad.Layout.Spacing
|
||||||
|
import XMonad.Layout.Maximize
|
||||||
|
import XMonad.Actions.DynamicWorkspaces
|
||||||
|
import XMonad.Actions.Navigation2D
|
||||||
|
import XMonad.Actions.CycleWS
|
||||||
|
|
||||||
|
|
||||||
|
-- -- subLayout [0,1] (windowNavigation $ emptyBSP ||| Tall 5 (3/100) (1/2)) $ Mirror rowOfColumns
|
||||||
|
-- -- subLayout [] (windowNavigation $ emptyBSP) $ windowNavigation $ rowOfColumns
|
||||||
|
-- myLayouts = -- subLayout [] emptyBSP $ (Mirror (BinaryColumn 0.7 16)) |||
|
||||||
|
-- -- sublayout combining resizabletall with an mirrored version of it self both with (initaly) zero slave windows.
|
||||||
|
-- -- this allows multiply resziable columns with multiply rows in each. by incrementing the master window count this can be cahnged to multiply columns
|
||||||
|
-- subLayout [] (ResizableTall 0 (3/100) (1/2) []) $ (Mirror $ ResizableTall 0 (3/100) (1/2) []) |||
|
||||||
|
-- -- subLayout [] (ResizableTall 0 (3/100) (1/2) []) $ emptyBSP |||
|
||||||
|
-- -- subLayout [] emptyBSP $ (Mirror (BinaryColumn 0.7 16)) |||
|
||||||
|
-- -- ResizableTall 1 (3/100) (1/2) [] |||
|
||||||
|
-- -- binarytree based layout splittiing windows with an fibronacci algortithem, expically usefull with hiddWindows enabling one to move windows to different locations in the tree
|
||||||
|
-- emptyBSP |||
|
||||||
|
-- -- masterd Version
|
||||||
|
-- -- mastered (1/100) (1/2) emptyBSP
|
||||||
|
-- -- at start one Column with multiply rows, than more columns kann by created, by moving windows to new groups. winodws and rows can be maximized, taking either the current row(window) or the screen(group)
|
||||||
|
-- wmii shrinkText def |||
|
||||||
|
-- -- rowOfColumns |||
|
||||||
|
-- -- masterd adds an master window to an layout, it can be manipulated with all normal tall layout functions(Inreass/Decreass Master count/size.)
|
||||||
|
-- -- mastered (1/100) (1/2) rowOfColumns
|
||||||
|
-- -- (stoppable rowOfColumns)
|
||||||
|
-- -- ||| Tall 1 (3/100) (1/2) ||| mosaic 2 [3,2]
|
||||||
|
|
||||||
|
myLayouts =
|
||||||
|
subLayout [] (ResizableTall 0 (3/100) (1/2) []) $ (Mirror $ ResizableTall 0 (3/100) (1/2) []) |||
|
||||||
|
emptyBSP |||
|
||||||
|
rowOfColumns |||
|
||||||
|
Mirror rowOfColumns |||
|
||||||
|
mastered (1/100) (1/2) rowOfColumns
|
||||||
|
|
||||||
|
-- ||| Tall 1 (3/100) (1/2) ||| mosaic 2 [3,2]
|
||||||
|
|
||||||
|
myWorkspaces = ["1","2","3","4","5","6","7","8","9"]
|
||||||
|
|
||||||
|
-- float krunner and plasmashell
|
||||||
|
myManageHook = composeAll . concat $
|
||||||
|
[ [ className =? c --> doFloat | c <- myFloats] ]
|
||||||
|
|
||||||
|
where myFloats = ["plasmashell","krunner"]
|
||||||
|
|
||||||
|
-- main config with ewmh and kde compitabillity
|
||||||
|
main = xmonad $ ewmh $ kdeConfig
|
||||||
|
{ manageHook = manageHook kdeConfig <+> myManageHook
|
||||||
|
, borderWidth = 2
|
||||||
|
, workspaces = myWorkspaces
|
||||||
|
, modMask = mod4Mask
|
||||||
|
-- modifiers for all layouts, avoiding docks, hidding(minimizing) Windows, maximizing windows, window gaps
|
||||||
|
, layoutHook = avoidStruts $ (windowNavigation $ (hiddenWindows $ (maximize $ (spacing 6 $ myLayouts))))
|
||||||
|
, logHook = dynamicLog
|
||||||
|
, keys = myKeys
|
||||||
|
, terminal = "st"
|
||||||
|
, normalBorderColor = "#1d252c"
|
||||||
|
, focusedBorderColor = "#cd8b00"
|
||||||
|
}
|
||||||
|
|
||||||
|
-- overwrite all keys
|
||||||
|
myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
|
||||||
|
[
|
||||||
|
-- launch a terminal
|
||||||
|
-- -- [ ((mod4Mask, xK_o), submap . M.fromList $
|
||||||
|
-- ((mod4Mask .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
||||||
|
-- --close focused window
|
||||||
|
-- , ((mod4Mask .|. shiftMask, xK_c ), kill1)
|
||||||
|
-- -- Rotate through the available layout algorithms
|
||||||
|
-- , ((mod4Mask, xK_space ), sendMessage NextLayout)
|
||||||
|
-- -- Reset the layouts on the current workspace to default
|
||||||
|
-- , ((mod4Mask .|. shiftMask, xK_space ), setLayout $ XMonad.layoutHook conf)
|
||||||
|
-- -- Resize viewed windows to the correct size
|
||||||
|
-- , ((mod4Mask, xK_n ), refresh)
|
||||||
|
-- -- Move focus to the next window
|
||||||
|
-- , ((mod4Mask, xK_Tab ), windows W.focusDown)
|
||||||
|
-- -- Move focus to the next window
|
||||||
|
-- , ((mod4Mask, xK_j ), windows W.focusDown)
|
||||||
|
-- -- Move focus to the previous window
|
||||||
|
-- , ((mod4Mask, xK_k ), windows W.focusUp)
|
||||||
|
-- -- Move focus to the master window
|
||||||
|
-- , ((mod4Mask, xK_m ), windows W.focusMaster)
|
||||||
|
-- -- Swap the focused window and the master window
|
||||||
|
-- , ((mod4Mask, xK_Return), windows W.swapMaster)
|
||||||
|
-- -- Swap the focused window with the next window
|
||||||
|
-- , ((mod4Mask .|. shiftMask, xK_j ), windows W.swapDown)
|
||||||
|
-- -- Swap the focused window with the previous window
|
||||||
|
-- , ((mod4Mask .|. shiftMask, xK_k ), windows W.swapUp)
|
||||||
|
-- -- Shrink the master area
|
||||||
|
-- , ((mod4Mask, xK_h ), sendMessage Shrink)
|
||||||
|
-- -- Expand the master area
|
||||||
|
-- , ((mod4Mask, xK_l ), sendMessage Expand)
|
||||||
|
-- -- Push window back into tiling
|
||||||
|
((mod4Mask, xK_t ), withFocused $ windows . W.sink)
|
||||||
|
-- -- Increment the number of windows in the master area
|
||||||
|
, ((mod4Mask , xK_comma ), sendMessage (IncMasterN 1))
|
||||||
|
-- Deincrement the number of windows in the master area
|
||||||
|
, ((mod4Mask , 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 , xK_b ), sendMessage ToggleStruts)
|
||||||
|
-- Quit xmonad
|
||||||
|
--, ((modm .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
||||||
|
---- Restart xmonad
|
||||||
|
, ((modm .|. controlMask .|. shiftMask, xK_r ), spawn "xmonad --recompile; xmonad --restart > ~/.xmonad/xmonad.status")
|
||||||
|
, ((modm .|. controlMask, xK_x), runOrRaisePrompt def)
|
||||||
|
, ((mod4Mask .|. controlMask , xK_s), sendMessage Arrange)
|
||||||
|
, ((mod4Mask .|. controlMask .|. shiftMask, xK_s), sendMessage DeArrange)
|
||||||
|
, ((mod4Mask .|. controlMask , xK_h), sendMessage (MoveLeft 1))
|
||||||
|
, ((mod4Mask .|. controlMask , xK_l), sendMessage (MoveRight 1))
|
||||||
|
, ((mod4Mask .|. controlMask , xK_j), sendMessage (MoveDown 1))
|
||||||
|
, ((mod4Mask .|. controlMask , xK_k), sendMessage (MoveUp 1))
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_h ), sendMessage (IncreaseLeft 1))
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_l), sendMessage (IncreaseRight 1))
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_j ), sendMessage (IncreaseDown 1))
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_k ), sendMessage (IncreaseUp 1))
|
||||||
|
, ((mod4Mask .|. controlMask .|. shiftMask, xK_h ), sendMessage (DecreaseLeft 1))
|
||||||
|
, ((mod4Mask .|. controlMask .|. shiftMask, xK_l), sendMessage (DecreaseRight 1))
|
||||||
|
, ((mod4Mask .|. controlMask .|. shiftMask, xK_j ), sendMessage (DecreaseDown 1))
|
||||||
|
, ((mod4Mask .|. controlMask .|. shiftMask, xK_k ), sendMessage (DecreaseUp 1))
|
||||||
|
, ((mod4Mask, xK_l), sendMessage $ N.Go R)
|
||||||
|
, ((mod4Mask, xK_h ), sendMessage $ N.Go L)
|
||||||
|
, ((mod4Mask, xK_k ), sendMessage $ N.Go U)
|
||||||
|
, ((mod4Mask, xK_j ), sendMessage $ N.Go D)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_l), sendMessage $ N.Swap R)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_h), sendMessage $ N.Swap L)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_k), sendMessage $ N.Swap U)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_j), sendMessage $ N.Swap D)
|
||||||
|
, ((mod4Mask, xK_m), withFocused hideWindow)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_m), popOldestHiddenWindow)
|
||||||
|
, ((mod4Mask, xK_f), toggleGroupFull)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_f), toggleGroupFull)
|
||||||
|
, ((mod4Mask, xK_i), zoomWindowIn)
|
||||||
|
, ((mod4Mask, xK_o), zoomWindowOut)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_f), toggleGroupFull)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_i), zoomGroupIn)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_o), zoomGroupOut)
|
||||||
|
, ((mod4Mask, xK_n), groupToNextLayout)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_l ), sendMessage $ ExpandTowards R)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_h ), sendMessage $ ExpandTowards L)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_j ), sendMessage $ ExpandTowards D)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_k ), sendMessage $ ExpandTowards U)
|
||||||
|
, ((mod4Mask .|. mod1Mask .|. controlMask , xK_l), sendMessage $ ShrinkFrom R)
|
||||||
|
, ((mod4Mask .|. mod1Mask .|. controlMask , xK_h), sendMessage $ ShrinkFrom L)
|
||||||
|
, ((mod4Mask .|. mod1Mask .|. controlMask , xK_j), sendMessage $ ShrinkFrom D)
|
||||||
|
, ((mod4Mask .|. mod1Mask .|. controlMask , xK_k), sendMessage $ ShrinkFrom U)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_r), sendMessage Rotate)
|
||||||
|
, ((mod4Mask, xK_n), sendMessage FocusParent)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_n), sendMessage SelectNode)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_n), sendMessage MoveNode)
|
||||||
|
, ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
||||||
|
--close focused window
|
||||||
|
, ((modm .|. shiftMask, xK_c), kill)
|
||||||
|
-- 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_space ), sendMessage NextLayout)
|
||||||
|
, ((modm, xK_q), kill1)
|
||||||
|
, ((modm .|. shiftMask, xK_a), withFocused (sendMessage . expandWindowAlt))
|
||||||
|
, ((modm .|. shiftMask, xK_z), withFocused (sendMessage . shrinkWindowAlt))
|
||||||
|
, ((modm .|. shiftMask, xK_s), withFocused (sendMessage . tallWindowAlt))
|
||||||
|
, ((modm .|. shiftMask, xK_d), withFocused (sendMessage . wideWindowAlt))
|
||||||
|
, ((modm .|. controlMask, xK_space), sendMessage resetAlt)
|
||||||
|
, ((modm , xK_F1), spawn "rofi_run -w")
|
||||||
|
, ((modm , xK_F2), spawn "rofi_run -r")
|
||||||
|
, ((mod4Mask, xK_b), submap . M.fromList $
|
||||||
|
[ ((controlMask .|. shiftMask, xK_l), sendMessage $ Move R)
|
||||||
|
, ((controlMask .|. shiftMask, xK_h ), sendMessage $ Move L)
|
||||||
|
, ((controlMask .|. shiftMask, xK_k ), sendMessage $ Move U)
|
||||||
|
, ((controlMask .|. shiftMask, xK_j ), sendMessage $ Move D)
|
||||||
|
, ((mod1Mask, xK_l), sendMessage $ ExpandTowards R)
|
||||||
|
, ((mod1Mask, xK_h), sendMessage $ ExpandTowards L)
|
||||||
|
, ((mod1Mask, xK_j), sendMessage $ ExpandTowards D)
|
||||||
|
, ((mod1Mask, xK_k), sendMessage $ ExpandTowards U)
|
||||||
|
, ((mod1Mask .|. controlMask , xK_l), sendMessage $ ShrinkFrom R)
|
||||||
|
, ((mod1Mask .|. controlMask , xK_h), sendMessage $ ShrinkFrom L)
|
||||||
|
, ((mod1Mask .|. controlMask , xK_j), sendMessage $ ShrinkFrom D)
|
||||||
|
, ((mod1Mask .|. controlMask , xK_k), sendMessage $ ShrinkFrom U)
|
||||||
|
, ((0, xK_r), sendMessage $ Rotate)
|
||||||
|
-- , ((0, xK_s ), sendMessage $ Swap)
|
||||||
|
, ((0, xK_n), sendMessage $ FocusParent)
|
||||||
|
, ((controlMask, xK_n), sendMessage $ SelectNode)
|
||||||
|
, ((shiftMask, xK_n), sendMessage $ MoveNode)
|
||||||
|
, ((mod4Mask, xK_a),sendMessage $ Balance)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_a),sendMessage $ Equalize)
|
||||||
|
])
|
||||||
|
, ((mod4Mask, xK_s), submap . M.fromList $
|
||||||
|
[ ((0, xK_k), swapUp)
|
||||||
|
, ((0, xK_j), swapDown)
|
||||||
|
, ((0, xK_u), focusUp)
|
||||||
|
, ((0, xK_d), focusDown)
|
||||||
|
, ((0, xK_s), splitGroup)
|
||||||
|
--, ((0, xK_n), focusGroupUp)
|
||||||
|
--, ((0, xK_m), focusGroupDown)
|
||||||
|
, ((shiftMask, xK_n), swapGroupUp)
|
||||||
|
, ((shiftMask, xK_m), swapGroupDown)
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_u), (moveToGroupUp True))
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_u), (moveToGroupUp True))
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_d), (moveToGroupDown True))
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_d), (moveToGroupDown True))
|
||||||
|
, ((mod1Mask .|. controlMask .|. shiftMask, xK_n), moveToNewGroupUp)
|
||||||
|
, ((mod1Mask .|. controlMask .|. shiftMask, xK_m), moveToNewGroupDown)
|
||||||
|
, ((shiftMask, xK_k), swapGroupUp)
|
||||||
|
, ((shiftMask, xK_j), swapGroupDown)
|
||||||
|
, ((mod1Mask , xK_k), (moveToGroupUp True))
|
||||||
|
, ((mod1Mask , xK_j), (moveToGroupDown True))
|
||||||
|
, ((controlMask, xK_k), moveToNewGroupUp)
|
||||||
|
, ((controlMask, xK_j), moveToNewGroupDown)
|
||||||
|
--, ((0 xK_Return), focusGroupMaster)
|
||||||
|
--, ((shiftMask, xK_Return), swapGroupMaster)
|
||||||
|
, ((0, xK_f), toggleWindowFull)
|
||||||
|
, ((shiftMask, xK_f), toggleGroupFull)
|
||||||
|
, ((shiftMask, xK_plus), zoomGroupIn)
|
||||||
|
, ((shiftMask, xK_minus), zoomGroupOut)
|
||||||
|
, ((0, xK_n), groupToNextLayout)
|
||||||
|
, ((0, xK_minus), zoomWindowOut)
|
||||||
|
, ((0, xK_plus), zoomWindowIn)
|
||||||
|
, ((0, xK_r), zoomWindowReset)
|
||||||
|
])
|
||||||
|
, ((mod4Mask, xK_a), submap . M.fromList $
|
||||||
|
[ ((shiftMask, xK_u), swapUp )
|
||||||
|
, ((shiftMask, xK_d), swapDown)
|
||||||
|
, ((modm, xK_m), withFocused (sendMessage . maximizeRestore))
|
||||||
|
, ((modm .|. shiftMask, xK_e), layoutScreens 2 (TwoPane 0.5 0.5))
|
||||||
|
, ((modm .|. controlMask .|. shiftMask, xK_e), rescreen)
|
||||||
|
, ((0, xK_u), focusUp)
|
||||||
|
, ((0, xK_d), focusDown)
|
||||||
|
, ((0, xK_s), splitGroup)
|
||||||
|
--, ((0, xK_n), focusGroupUp)
|
||||||
|
--, ((0, xK_m), focusGroupDown)
|
||||||
|
, ((shiftMask, xK_n), swapGroupUp)
|
||||||
|
, ((shiftMask, xK_m), swapGroupDown)
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_u), (moveToGroupUp True))
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_d), (moveToGroupDown True))
|
||||||
|
, ((mod1Mask .|. controlMask .|. shiftMask, xK_n), moveToNewGroupUp)
|
||||||
|
, ((mod1Mask .|. controlMask .|. shiftMask, xK_m), moveToNewGroupDown)
|
||||||
|
--, ((0 xK_Return), focusGroupMaster)
|
||||||
|
--, ((shiftMask, xK_Return), swapGroupMaster)
|
||||||
|
, ((0, xK_f), toggleWindowFull)
|
||||||
|
, ((mod4Mask, xK_f), toggleGroupFull)
|
||||||
|
, ((0, xK_i), zoomGroupIn)
|
||||||
|
, ((0, xK_o), zoomGroupOut)
|
||||||
|
, ((0, xK_n), groupToNextLayout)
|
||||||
|
, ((0, xK_t), sendMessage Taller)
|
||||||
|
, ((0, xK_w), sendMessage Wider)
|
||||||
|
, ((0, xK_r), sendMessage Reset)
|
||||||
|
, ((0, xK_c), killAllOtherCopies)
|
||||||
|
, ((0, xK_a), windows copyToAll)
|
||||||
|
, ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
||||||
|
--close focused window
|
||||||
|
, ((modm .|. shiftMask, xK_c), kill1)
|
||||||
|
-- Rotate through the available layout algorithms
|
||||||
|
-- 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)))
|
||||||
|
, ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
|
||||||
|
, ((modm .|. shiftMask, xK_a), withFocused (sendMessage . expandWindowAlt))
|
||||||
|
, ((modm .|. shiftMask, xK_z), withFocused (sendMessage . shrinkWindowAlt))
|
||||||
|
, ((modm .|. shiftMask, xK_s), withFocused (sendMessage . tallWindowAlt))
|
||||||
|
, ((modm .|. shiftMask, xK_d), withFocused (sendMessage . wideWindowAlt))
|
||||||
|
, ((modm .|. controlMask, xK_space), sendMessage resetAlt)
|
||||||
|
, ((0, xK_m), withFocused hideWindow)
|
||||||
|
, ((mod4Mask, xK_m), popOldestHiddenWindow)
|
||||||
|
, ((mod1Mask, xK_m), popNewestHiddenWindow)
|
||||||
|
, ((0, xK_minus), zoomWindowOut)
|
||||||
|
, ((0, xK_plus), zoomWindowIn)
|
||||||
|
, ((0, xK_r), zoomWindowReset)
|
||||||
|
, ((0, xK_f), toggleWindowFull)
|
||||||
|
, ((mod4Mask, xK_minus), zoomColumnOut)
|
||||||
|
, ((mod4Mask, xK_plus), zoomColumnIn)
|
||||||
|
, ((mod4Mask, xK_r), zoomColumnReset)
|
||||||
|
, ((mod4Mask, xK_f), toggleColumnFull)
|
||||||
|
, ((0, xK_u), focusUp)
|
||||||
|
, ((0, xK_d), focusDown)
|
||||||
|
, ((0, xK_s), splitGroup)
|
||||||
|
, ((0, xK_n), focusGroupUp)
|
||||||
|
, ((0, xK_m), focusGroupDown)
|
||||||
|
, ((shiftMask, xK_n), swapGroupUp)
|
||||||
|
, ((shiftMask, xK_m), swapGroupDown)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_u), (moveToGroupUp False))
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_d), (moveToGroupDown False))
|
||||||
|
, ((mod4Mask .|. controlMask .|. shiftMask, xK_u), moveToNewGroupUp)
|
||||||
|
, ((mod4Mask .|. controlMask .|. shiftMask, xK_d), moveToNewGroupDown)
|
||||||
|
])
|
||||||
|
, ((mod4Mask, xK_d), submap . M.fromList $
|
||||||
|
[ ((mod4Mask .|. controlMask, xK_s), toSubl Arrange)
|
||||||
|
, ((controlMask .|. shiftMask, xK_s), toSubl DeArrange)
|
||||||
|
, ((controlMask, xK_h), toSubl (MoveLeft 1))
|
||||||
|
, ((controlMask, xK_l), toSubl (MoveRight 1))
|
||||||
|
, ((controlMask, xK_j), toSubl (MoveDown 1))
|
||||||
|
, ((controlMask, xK_k), toSubl (MoveUp 1))
|
||||||
|
, ((shiftMask, xK_h ), toSubl (IncreaseLeft 1))
|
||||||
|
, ((shiftMask, xK_l), toSubl (IncreaseRight 1))
|
||||||
|
, ((shiftMask, xK_j ), toSubl (IncreaseDown 1))
|
||||||
|
, ((shiftMask, xK_k ), toSubl (IncreaseUp 1))
|
||||||
|
, ((controlMask .|. shiftMask, xK_h), toSubl (DecreaseLeft 1))
|
||||||
|
, ((controlMask .|. shiftMask, xK_l), toSubl (DecreaseRight 1))
|
||||||
|
, ((controlMask .|. shiftMask, xK_j), toSubl (DecreaseDown 1))
|
||||||
|
, ((controlMask .|. shiftMask, xK_k), toSubl (DecreaseUp 1))
|
||||||
|
, ((0, xK_l), toSubl $ N.Go R)
|
||||||
|
, ((0, xK_h ), toSubl $ N.Go L)
|
||||||
|
, ((0, xK_k ), toSubl $ N.Go U)
|
||||||
|
, ((0, xK_j ), toSubl $ N.Go D)
|
||||||
|
, ((controlMask, xK_l), toSubl $ N.Swap R)
|
||||||
|
, ((controlMask, xK_h ), toSubl $ N.Swap L)
|
||||||
|
, ((controlMask, xK_k ), toSubl $ N.Swap U)
|
||||||
|
, ((controlMask, xK_j ), toSubl $ N.Swap D)
|
||||||
|
, ((0, xK_e), withFocused (toSubl . expandWindowAlt))
|
||||||
|
, ((0, xK_s), withFocused (toSubl . shrinkWindowAlt))
|
||||||
|
, ((0, xK_t), withFocused (toSubl . tallWindowAlt))
|
||||||
|
, ((0, xK_w), withFocused (toSubl . wideWindowAlt))
|
||||||
|
, ((0, xK_space), toSubl resetAlt)
|
||||||
|
, ((0, xK_n), toSubl NextLayout)
|
||||||
|
, ((mod4Mask, xK_j), windows W.focusDown)
|
||||||
|
-- Move focus to the previous window
|
||||||
|
, ((mod4Mask, xK_k), windows W.focusUp)
|
||||||
|
-- Move focus to the master window
|
||||||
|
, ((mod4Mask, xK_m), windows W.focusMaster)
|
||||||
|
-- Swap the focused window and the master window
|
||||||
|
, ((mod4Mask, xK_Return), windows W.swapMaster)
|
||||||
|
-- Swap the focused window with the next window
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_j), windows W.swapDown)
|
||||||
|
-- Swap the focused window with the previous window
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_k), windows W.swapUp)
|
||||||
|
-- Shrink the master area
|
||||||
|
, ((mod4Mask, xK_h ), toSubl Shrink)
|
||||||
|
-- Expand the master area
|
||||||
|
, ((mod4Mask, xK_l ), toSubl Expand)
|
||||||
|
-- Push window back into tiling
|
||||||
|
, ((mod4Mask, xK_t ), withFocused $ windows . W.sink)
|
||||||
|
-- Increment the number of windows in the master area
|
||||||
|
, ((mod4Mask , xK_comma ), toSubl (IncMasterN 1))
|
||||||
|
-- Deincrement the number of windows in the master area
|
||||||
|
, ((mod4Mask, xK_period), toSubl (IncMasterN (-1)))
|
||||||
|
, ((modm, xK_a), toSubl MirrorShrink)
|
||||||
|
, ((modm, xK_z), toSubl MirrorExpand)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_h), sendMessage $ pullGroup L)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_l), sendMessage $ pullGroup R)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_k), sendMessage $ pullGroup U)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_j), sendMessage $ pullGroup D)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_h), sendMessage $ pushGroup L)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_l), sendMessage $ pushGroup R)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_k), sendMessage $ pushGroup U)
|
||||||
|
, ((mod4Mask .|. mod1Mask, xK_j), sendMessage $ pushGroup D)
|
||||||
|
, ((controlMask .|. mod1Mask, xK_h), sendMessage $ pullWindow L)
|
||||||
|
, ((controlMask .|. mod1Mask, xK_l), sendMessage $ pullWindow R)
|
||||||
|
, ((controlMask .|. mod1Mask, xK_k), sendMessage $ pullWindow U)
|
||||||
|
, ((controlMask .|. mod1Mask, xK_j), sendMessage $ pullWindow D)
|
||||||
|
, ((mod1Mask, xK_h), sendMessage $ pushWindow L)
|
||||||
|
, ((mod1Mask, xK_l), sendMessage $ pushWindow R)
|
||||||
|
, ((mod1Mask, xK_k), sendMessage $ pushWindow U)
|
||||||
|
, ((mod1Mask, xK_j), sendMessage $ pushWindow D)
|
||||||
|
, ((controlMask, xK_m), withFocused (sendMessage . MergeAll))
|
||||||
|
, ((controlMask, xK_u), withFocused (sendMessage . UnMerge))
|
||||||
|
, ((controlMask, xK_period), onGroup W.focusUp')
|
||||||
|
, ((controlMask, xK_comma), onGroup W.focusDown')
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_u), (moveToGroupUp False))
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_d), (moveToGroupDown False))
|
||||||
|
, ((modm, xK_a), toSubl MirrorShrink)
|
||||||
|
, ((modm, xK_z), toSubl MirrorExpand)
|
||||||
|
])
|
||||||
|
, ((mod4Mask, xK_z), submap . M.fromList $
|
||||||
|
[
|
||||||
|
((0, xK_f), runOrCopy "firefox" (className =? "Firefox"))
|
||||||
|
, ((0, xK_e), runOrCopy "emacs" (className =? "emacs"))
|
||||||
|
, ((0, xK_t), runOrCopy "main" (className =? "st"))
|
||||||
|
])
|
||||||
|
, ((mod4Mask, xK_plus), sendMessage MirrorExpand)
|
||||||
|
, ((mod4Mask, xK_minus), sendMessage MirrorShrink)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_plus), toSubl MirrorExpand)
|
||||||
|
, ((mod4Mask .|. shiftMask, xK_minus), toSubl MirrorShrink)
|
||||||
|
, ((mod4Mask .|. controlMask, xK_c), shellPrompt def)
|
||||||
|
, ((mod4Mask, xK_w), submap . M.fromList $
|
||||||
|
[ ((0, xK_x), removeWorkspace)
|
||||||
|
, ((0, xK_a), selectWorkspace def)
|
||||||
|
, ((0, xK_w), selectWorkspace def)
|
||||||
|
, ((0, xK_m), withWorkspace def (windows . W.shift))
|
||||||
|
, ((0, xK_m), withWorkspace def (windows . copy))
|
||||||
|
, ((0, xK_c), withWorkspace def (windows . W.shift))
|
||||||
|
, ((0, xK_c), withWorkspace def (windows . copy))
|
||||||
|
, ((0, xK_s), addWorkspacePrompt def)
|
||||||
|
, ((0, xK_r), renameWorkspace def)
|
||||||
|
, ((0,xK_j), nextWS)
|
||||||
|
, ((0,xK_k), prevWS)
|
||||||
|
, ((shiftMask, xK_j), shiftToNext)
|
||||||
|
, ((shiftMask, xK_k), shiftToPrev)
|
||||||
|
, ((0,xK_l), nextScreen)
|
||||||
|
, ((0,xK_h), prevScreen)
|
||||||
|
, ((shiftMask, xK_l), shiftNextScreen)
|
||||||
|
, ((shiftMask, xK_h), shiftPrevScreen)
|
||||||
|
, ((0,xK_z), toggleWS)
|
||||||
|
])
|
||||||
|
, ((mod4Mask, xK_space), submap . M.fromList $
|
||||||
|
[ ((0, xK_space), sendMessage NextLayout)
|
||||||
|
, ((0, xK_w), submap . M.fromList $
|
||||||
|
[ ((0, xK_x), removeWorkspace)
|
||||||
|
, ((0, xK_a), selectWorkspace def)
|
||||||
|
, ((0, xK_w), selectWorkspace def)
|
||||||
|
, ((0, xK_m), withWorkspace def (windows . W.shift))
|
||||||
|
, ((0, xK_m), withWorkspace def (windows . copy))
|
||||||
|
, ((0, xK_c), withWorkspace def (windows . W.shift))
|
||||||
|
, ((0, xK_c), withWorkspace def (windows . copy))
|
||||||
|
, ((0, xK_s), addWorkspacePrompt def)
|
||||||
|
, ((0, xK_r), renameWorkspace def)
|
||||||
|
, ((0,xK_j), nextWS)
|
||||||
|
, ((0,xK_k), prevWS)
|
||||||
|
, ((shiftMask, xK_j), shiftToNext)
|
||||||
|
, ((shiftMask, xK_k), shiftToPrev)
|
||||||
|
, ((0,xK_l), nextScreen)
|
||||||
|
, ((0,xK_h), prevScreen)
|
||||||
|
, ((shiftMask, xK_l), shiftNextScreen)
|
||||||
|
, ((shiftMask, xK_h), shiftPrevScreen)
|
||||||
|
, ((0,xK_z), toggleWS)
|
||||||
|
, ((0, xK_k), swapUp)
|
||||||
|
, ((0, xK_j), swapDown)
|
||||||
|
, ((0, xK_u), focusUp)
|
||||||
|
, ((0, xK_d), focusDown)
|
||||||
|
, ((0, xK_s), splitGroup)
|
||||||
|
--, ((0, xK_n), focusGroupUp)
|
||||||
|
--, ((0, xK_m), focusGroupDown)
|
||||||
|
, ((shiftMask, xK_n), swapGroupUp)
|
||||||
|
, ((shiftMask, xK_m), swapGroupDown)
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_u), (moveToGroupUp True))
|
||||||
|
, ((mod1Mask .|. shiftMask, xK_d), (moveToGroupDown True))
|
||||||
|
, ((mod1Mask .|. controlMask .|. shiftMask, xK_n), moveToNewGroupUp)
|
||||||
|
, ((mod1Mask .|. controlMask .|. shiftMask, xK_m), moveToNewGroupDown)
|
||||||
|
, ((shiftMask, xK_k), swapGroupUp)
|
||||||
|
, ((shiftMask, xK_j), swapGroupDown)
|
||||||
|
, ((mod1Mask , xK_k), (moveToGroupUp True))
|
||||||
|
, ((mod1Mask , xK_j), (moveToGroupDown True))
|
||||||
|
, ((controlMask, xK_k), moveToNewGroupUp)
|
||||||
|
, ((0, xK_m), moveToNewGroupUp)
|
||||||
|
, ((controlMask, xK_j), moveToNewGroupDown)
|
||||||
|
--, ((0 xK_Return), focusGroupMaster)
|
||||||
|
--, ((shiftMask, xK_Return), swapGroupMaster)
|
||||||
|
, ((0, xK_f), toggleWindowFull)
|
||||||
|
, ((shiftMask, xK_f), toggleGroupFull)
|
||||||
|
, ((shiftMask, xK_plus), zoomGroupIn)
|
||||||
|
, ((shiftMask, xK_minus), zoomGroupOut)
|
||||||
|
, ((0, xK_n), groupToNextLayout)
|
||||||
|
, ((0, xK_minus), zoomWindowOut)
|
||||||
|
, ((0, xK_plus), zoomWindowIn)
|
||||||
|
, ((0, xK_r), zoomWindowReset)
|
||||||
|
])
|
||||||
|
-- -- ((0, xK_b), submap . M.fromList $
|
||||||
|
-- -- [
|
||||||
|
-- -- ((mod1Mask, xK_l), sendMessage $ ExpandTowards R)
|
||||||
|
-- -- , ((mod1Mask, xK_h), sendMessage $ ExpandTowards L)
|
||||||
|
-- -- , ((mod1Mask, xK_j), sendMessage $ ExpandTowards D)
|
||||||
|
-- -- , ((mod1Mask, xK_k), sendMessage $ ExpandTowards U)
|
||||||
|
-- -- , ((controlMask, xK_l), sendMessage $ ShrinkFrom R)
|
||||||
|
-- -- , ((controlMask, xK_h), sendMessage $ ShrinkFrom L)
|
||||||
|
-- -- , ((controlMask, xK_j), sendMessage $ ShrinkFrom D)
|
||||||
|
-- -- , ((controlMask, xK_k), sendMessage $ ShrinkFrom U)
|
||||||
|
-- -- , ((0, xK_r), sendMessage Rotate)
|
||||||
|
-- -- -- , ((modm, xK_s ), sendMessage Swap)
|
||||||
|
-- -- , ((0, xK_n), sendMessage FocusParent)
|
||||||
|
-- -- , ((controlMask,xK_n ), sendMessage SelectNode)
|
||||||
|
-- -- , ((shiftMask, xK_n), sendMessage MoveNode)
|
||||||
|
-- -- , ((0, xK_a), sendMessage Balance)
|
||||||
|
-- -- , ((shiftMask, dMessage Equalize)
|
||||||
|
-- -- ])
|
||||||
|
])
|
||||||
|
-- , ((mod4Mask, xK_space), submap . M.fromList $
|
||||||
|
-- [((0, xK_b), submap . M.fromList $
|
||||||
|
-- [
|
||||||
|
-- ((mod1Mask, xK_l), sendMessage $ ExpandTowards R)
|
||||||
|
-- , ((mod1Mask, xK_h), sendMessage $ ExpandTowards L)
|
||||||
|
-- , ((mod1Mask, xK_j), sendMessage $ ExpandTowards D)
|
||||||
|
-- , ((mod1Mask, xK_k), sendMessage $ ExpandTowards U)
|
||||||
|
-- , ((controlMask, xK_l), sendMessage $ ShrinkFrom R)
|
||||||
|
-- , ((controlMask, xK_h), sendMessage $ ShrinkFrom L)
|
||||||
|
-- , ((controlMask, xK_j), sendMessage $ ShrinkFrom D)
|
||||||
|
-- , ((controlMask, xK_k), sendMessage $ ShrinkFrom U)
|
||||||
|
-- , ((0, xK_r), sendMessage Rotate)
|
||||||
|
-- -- , ((modm, xK_s ), sendMessage Swap)
|
||||||
|
-- , ((0, xK_n), sendMessage FocusParent)
|
||||||
|
-- , ((controlMask,xK_n ), sendMessage SelectNode)
|
||||||
|
-- , ((shiftMask, xK_n), sendMessage MoveNode)
|
||||||
|
-- , ((0, xK_a), sendMessage Balance)
|
||||||
|
-- , ((shiftMask, dMessage Equalize)
|
||||||
|
-- ])
|
||||||
|
-- , ((0, xK_space), sendMessage NextLayout)
|
||||||
|
-- , ((0, xK_w), submap . M.fromList $
|
||||||
|
-- [ ((0, xK_x), removeWorkspace)
|
||||||
|
-- , ((0, xK_a ), selectWorkspace def)
|
||||||
|
-- , ((0, xK_w ), selectWorkspace def)
|
||||||
|
-- , ((0, xK_m ), withWorkspace def (windows . W.shift))
|
||||||
|
-- , ((0, xK_m ), withWorkspace def (windows . copy))
|
||||||
|
-- , ((0, xK_c ), withWorkspace def (windows . W.shift))
|
||||||
|
-- , ((0, xK_c ), withWorkspace def (windows . copy))
|
||||||
|
-- , ((0, xK_s ), addWorkspacePrompt def)
|
||||||
|
-- , ((0, xK_r ), renameWorkspace def)
|
||||||
|
-- , ((0, xK_j), nextWS)
|
||||||
|
-- , ((0, xK_k), prevWS)
|
||||||
|
-- , ((shiftMask, xK_j), shiftToNext)
|
||||||
|
-- , ((shiftMask, xK_k), shiftToPrev)
|
||||||
|
-- , ((0, xK_l), nextScreen)
|
||||||
|
-- , ((0, xK_h), prevScreen)
|
||||||
|
-- , ((shiftMask, xK_l), shiftNextScreen)
|
||||||
|
-- , ((shiftMask, xK_h), shiftPrevScreen)
|
||||||
|
-- , ((0, xK_z), toggleWS)
|
||||||
|
-- ])
|
||||||
|
-- ])
|
||||||
|
]
|
||||||
|
++
|
||||||
|
--
|
||||||
|
-- MOD-[1..9], Switch to workspace N
|
||||||
|
-- mod-shift-[1..9], Move client to workspace N
|
||||||
|
-- mod-control-[1..9], Copy client to workspace N
|
||||||
|
--
|
||||||
|
[((m .|. mod4Mask, k), windows $ f i)
|
||||||
|
| (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
|
||||||
|
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask), (copy, controlMask)]
|
||||||
|
]
|
||||||
|
|
||||||
|
-- ++
|
||||||
|
-- [((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f))
|
||||||
|
-- | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
|
||||||
|
-- mod-[1..9] %! Switch to workspace of index N
|
||||||
|
-- mod-control-[1..9] %! Set index N to the current workspace
|
||||||
|
++
|
||||||
|
zip (zip (repeat (modm)) [xK_1..xK_9]) (map (withWorkspaceIndex W.greedyView) [1..])
|
||||||
|
++
|
||||||
|
zip (zip (repeat (modm .|. controlMask)) [xK_1..xK_9]) (map (setWorkspaceIndex) [1..])-- , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
|
||||||
|
|
118
xmonad.status
Normal file
118
xmonad.status
Normal file
@@ -0,0 +1,118 @@
|
|||||||
|
[Home] : Hidden Maximize Spacing BSP
|
||||||
|
[Home] : Hidden Maximize Spacing BSP
|
||||||
|
[Home] : Hidden Maximize Spacing BSP
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : Plasma
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : KRunner â krunner
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : Plasma
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] : Hidden Maximize Spacing BSP : Plasma
|
||||||
|
Home [Programming] : Hidden Maximize Spacing BSP
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : Plasma
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Unhandled CSI] action='t', args=[22, 0, 0], intermediates=[]
|
||||||
|
[Unhandled CSI] action='l', args=[1005], intermediates=[63]
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : Plasma
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home.2] Programming : Hidden Maximize Spacing BSP
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : Plasma
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
23999
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Unhandled CSI] action='t', args=[22, 0, 0], intermediates=[]
|
||||||
|
[Unhandled CSI] action='l', args=[1005], intermediates=[63]
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : emacs@linux-8f87
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tree Style Tab 3.0.14 - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tree Style Tab 3.0.14 - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Sitzungswiederherstellung - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tree Style Tab 3.0.14 - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tree Style Tab 3.0.14 - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Veelink DisplayPort zu HDMI Adapter 4K 60Hz: Amazon.de: Elektronik - Mozilla ...
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Â - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Veelink DisplayPort zu HDMI Adapter 4K 60Hz: Amazon.de: Elektronik - Mozilla ...
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : k41 : zsh â Konsole
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
Home [Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
Home [Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
Home [Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
Home [Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[unhandled osc_dispatch]: [['1','2',],['7',],] at line 754
|
||||||
|
Home [Browser.3] Programming : Hidden Maximize Spacing BSP
|
||||||
|
Home [Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
Home [Programming] : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
Home Programming [l] : Hidden Maximize Spacing BSP
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : emacs-gtk@linux-8f87
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : emacs-gtk@linux-8f87
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : emacs-x11@linux-8f87
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : emacs-gtk@linux-8f87
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Alacritty
|
||||||
|
[Unhandled CSI] action='t', args=[22, 0, 0], intermediates=[]
|
||||||
|
[Unhandled CSI] action='l', args=[1005], intermediates=[63]
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Tridactyl Top Tips & New Tab Page - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Page Not Found - structix Git - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Sign In - structix Git - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : structix/vorlesungen: Notizen aus den Vorlesungen - structix Git - Mozilla Fi...
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Neues Repository - structix Git - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Neues Repository - structix Git - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : mohammed/xmonad - structix Git - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : 1:zsh
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : mohammed/xmonad - structix Git - Mozilla Firefox
|
||||||
|
[Home] Programming : Hidden Maximize Spacing BSP : 1:zsh
|
Reference in New Issue
Block a user