summaryrefslogtreecommitdiffstats
path: root/src/XMonad
diff options
context:
space:
mode:
authorMichal Minar <miminar@redhat.com>2015-08-02 08:51:46 +0200
committerMichal Minar <miminar@redhat.com>2015-08-02 08:51:46 +0200
commitaf86d65c6cdd4a5ad03afb40d6fbd2cd34170b77 (patch)
tree86c0ddb58e926234623a6d35ddcb031a2544107f /src/XMonad
parent0506d39822e666a2d08eafce73206dfb1a1c03af (diff)
downloadxminad-af86d65c6cdd4a5ad03afb40d6fbd2cd34170b77.tar.gz
xminad-af86d65c6cdd4a5ad03afb40d6fbd2cd34170b77.tar.xz
xminad-af86d65c6cdd4a5ad03afb40d6fbd2cd34170b77.zip
Cleaned up keys
Signed-off-by: Michal Minar <miminar@redhat.com>
Diffstat (limited to 'src/XMonad')
-rw-r--r--src/XMonad/Local/Keys.hs404
1 files changed, 209 insertions, 195 deletions
diff --git a/src/XMonad/Local/Keys.hs b/src/XMonad/Local/Keys.hs
index 9a794e5..0a21614 100644
--- a/src/XMonad/Local/Keys.hs
+++ b/src/XMonad/Local/Keys.hs
@@ -52,209 +52,223 @@ keyBindings :: XConfig l -> M.Map (KeyMask, KeySym) (X())
keyBindings conf = EZ.mkKeymap conf $ emacsKeys conf
emacsKeys :: XConfig l -> [(String, X())]
-emacsKeys = \conf -> map prefix (emacsKeys' conf) ++ keys
+emacsKeys = \conf -> map prefix (keysMissingPrefix conf) ++ unprefixedKeys
where
prefix :: (String, a) -> (String, a)
prefix (k, a) = (modm ++ "-" ++ k, a)
- emacsKeys' :: XConfig l -> [(String, X())]
- emacsKeys' conf = [
- -- Applications
- (";", Local.spawnShell Nothing)
- , ("S-;", Local.spawnExplorer)
- , ("S-.", namedScratchpadAction namedScratchpads "guake")
- , ("p", Shell.shellPrompt xpConfig)
- , ("S-p", Local.mateRun)
-
- -- Layouts
- , ("<Space>", sendMessage NextLayout)
- , ("C-<Space>", SUB.submap $ EZ.mkKeymap conf $ concat
- [ [(k, a), (modm ++ "-C-" ++ k, a)]
- | (k, a) <- [ ("3", sendMessage (Toggle "ThreeCol"))
- , ("x", sendMessage (MT.Toggle REFLECTX))
- , ("y", sendMessage (MT.Toggle REFLECTY))
- ]
- ])
- , ("<F5>", refresh)
- , ("C-j", sendMessage $ Go D)
- , ("C-k", sendMessage $ Go U)
- , ("C-h", sendMessage $ Go L)
- , ("C-l", sendMessage $ Go R)
- , ("j", BW.focusDown)
- , ("k", BW.focusUp)
- , ("m", windows W.focusMaster)
- , ("S-j", windows W.swapDown)
- , ("S-k", windows W.swapUp)
- , ("C-.", onGroup W.focusUp')
- , ("C-,", onGroup W.focusDown')
- , ("h", sendMessage Shrink)
- , ("l", sendMessage Expand)
- , ("<Return>", windows W.focusMaster)
- , ("S-<Return>", DwmP.dwmpromote)
- , ("t", withFocused $ windows . W.sink)
- , (",", sendMessage (IncMasterN 1))
- , (".", sendMessage (IncMasterN (-1)))
-
- -- keybindings for sublayouts
- , ("g", SUB.submap $ defaultSublMap conf)
- , ("<Left>", sendMessage $ pullGroup L)
- , ("<Right>", sendMessage $ pullGroup R)
- , ("<Up>", sendMessage $ pullGroup U)
- , ("<Down>", sendMessage $ pullGroup D)
- , ("C-m", withFocused (sendMessage . MergeAll))
- , ("C-u", withFocused (sendMessage . UnMerge))
-
- -- boring windows
- , ("b", BW.markBoring)
- , ("S-b", BW.clearBoring)
-
- -- minimized widnows
- , ("z", withFocused minimizeWindow)
- , ("S-z", sendMessage RestoreNextMinimizedWin)
-
- -- Toggle full screen
- , ("<F12>", sendMessage ToggleStruts >> refresh)
-
- -- Windows
- , ("S-c", kill)
- , ("C-S-c", WithAll.killAll)
- , ("x", spawn "xkill")
-
- -- Compositing
- , ("S-x", SUB.submap $ EZ.mkKeymap conf $ concat
- [ [(k, a), (modm ++ "-S-" ++ k, a)]
- | (k, a) <- [ ("r", spawn "systemctl --user restart compositing")
- , ("s", spawn "systemctl --user stop compositing")]
- ])
-
- -- Workspaces
- , ("<Tab>", Local.toggleWS)
- , ("S-<Tab>", Local.toggleWSSwitch)
- , ("C-<Right>", moveTo Next nonEmptyWs)
- , ("]", moveTo Next $ WSIs nonEmptyWsPred)
- , ("C-<Left>", moveTo Prev $ WSIs nonEmptyWsPred)
- , ("[", moveTo Prev $ WSIs nonEmptyWsPred)
- , ("-", SUB.submap $ EZ.mkKeymap conf
- [ (m ++ show k, _withNthWorkspace f i)
- | (k, i) <- (zip ([1..9] ++ [0]) [10..] :: [(Int, Int)])
- , (f, m) <- concat
- [ [ -- switch to ith workspace
- (W.greedyView, m)
- -- shift focused to ith workspace
- , (\ws -> W.greedyView ws . W.shift ws, m ++ "S-")
- ]
- | m <- ["", modm ++ "-"]
+ keysMissingPrefix conf = concat $
+ [ genericKeys conf
+ , switchWorkspaceKeys
+ , switchScreenKeys
+ ]
+
+-- need to be prefixed with modifier
+genericKeys :: XConfig l -> [(String, X())]
+genericKeys conf = [
+ -- Applications
+ (";", Local.spawnShell Nothing)
+ , ("S-;", Local.spawnExplorer)
+ , ("S-.", namedScratchpadAction namedScratchpads "guake")
+ , ("p", Shell.shellPrompt xpConfig)
+ , ("S-p", Local.mateRun)
+
+ -- Layouts
+ , ("<Space>", sendMessage NextLayout)
+ , ("C-<Space>", SUB.submap $ EZ.mkKeymap conf $ concat
+ [ [(k, a), (modm ++ "-C-" ++ k, a)]
+ | (k, a) <- [ ("3", sendMessage (Toggle "ThreeCol"))
+ , ("x", sendMessage (MT.Toggle REFLECTX))
+ , ("y", sendMessage (MT.Toggle REFLECTY))
]
- ])
-
- , ("n", promptedNewWorkspace False)
- , ("S-n", promptedNewWorkspace True)
- , ("S-<Backspace>", WithAll.killAll >> DW.removeWorkspace)
- , ("S-r", DW.renameWorkspace xpConfig)
- , ("c", TD.changeDir xpConfig)
-
- , ("r", swapScreens)
-
- , ("a", TS.currentTopicAction topicConfig)
-
- -- Grid Select workspace
- , ("i", goToSelected Local.gsConfig)
- , ("s", gsw)
- , ("S-s", gswShift)
-
- -- xmonad
- , ("q", SUB.submap $ EZ.mkKeymap conf $ concat
- [ [(k, a), (modm ++ "-" ++ k, a)]
- | (k, a) <- [ ("c", spawn "xmonad --recompile; xmonad --restart")
- , ("r", spawn "xmonad --restart")
- , ("u", spawn "undock")
- , ("S-u", spawn "undock -s")
- , ("e", spawn "monitor-hotplug")
- , ("s", spawn "mate-session-save --shutdown-dialog")
- , ("q", spawn "mate-session-save --logout")
- , ("l", spawn "mate-screensaver-command --lock")
- ]
- ])
- , ("C-q", spawn "mate-screensaver-command --lock")
-
- -- namedScratchpads
- , ("C-S-t", namedScratchpadAction namedScratchpads "htop")
- , ("C-S-a", namedScratchpadAction namedScratchpads "stardict")
- , ("C-S-n", namedScratchpadAction namedScratchpads "notes")
- , ("C-S-u", namedScratchpadAction namedScratchpads "charmap")
- , ("C-S-l", namedScratchpadAction namedScratchpads "alarm")
- , ("C-S-p", namedScratchpadAction namedScratchpads "volctl")
-
- -- misc
- , ("S-h", PSsh.sshPrompt xpConfig)
- --, ("<Print>", spawn "xfce4-screenshooter")
- , ("y", spawn "xfce4-popup-clipman")
- , ("<Print>", spawn "mate-screenshot")
- , ("C-<Print>", spawn "mate-screenshot -w")
- , ("S-<Print>", spawn "mate-screenshot -a")
-
- -- MPD
- -- mov current playing song in mpd to thrash
- , ("<Delete>", spawn "mpcrm")
- , ("<XF86Forward>",
- io $ return . fromRight =<< MPD.withMPD MPD.next)
- , ("<XF86Back>",
- io $ return . fromRight =<< MPD.withMPD MPD.previous)
- ]
- ++ [ (m ++ show i, _withNthWorkspace f ((i + 9) `mod` 10))
- | i <- [1..9] ++ [0]
- , (f, m) <- [ (W.greedyView, "") -- switch to ith workspace
- -- shift focused to ith workspace
- , (\ws -> W.greedyView ws . W.shift ws, "S-")
- ]
- ]
- ++ [ (m ++ k, screenWorkspace sc >>= flip whenJust (windows . f))
- | (k, sc) <- zip ["w", "e"] [0..]
- , (f, m) <- [(W.view, ""), (W.shift, "S-")]
+ ])
+ , ("<F5>", refresh)
+ , ("C-j", sendMessage $ Go D)
+ , ("C-k", sendMessage $ Go U)
+ , ("C-h", sendMessage $ Go L)
+ , ("C-l", sendMessage $ Go R)
+ , ("j", BW.focusDown)
+ , ("k", BW.focusUp)
+ , ("m", windows W.focusMaster)
+ , ("S-j", windows W.swapDown)
+ , ("S-k", windows W.swapUp)
+ , ("C-.", onGroup W.focusUp')
+ , ("C-,", onGroup W.focusDown')
+ , ("h", sendMessage Shrink)
+ , ("l", sendMessage Expand)
+ , ("<Return>", windows W.focusMaster)
+ , ("S-<Return>", DwmP.dwmpromote)
+ , ("t", withFocused $ windows . W.sink)
+ , (",", sendMessage (IncMasterN 1))
+ , (".", sendMessage (IncMasterN (-1)))
+
+ -- keybindings for sublayouts
+ , ("g", SUB.submap $ defaultSublMap conf)
+ , ("<Left>", sendMessage $ pullGroup L)
+ , ("<Right>", sendMessage $ pullGroup R)
+ , ("<Up>", sendMessage $ pullGroup U)
+ , ("<Down>", sendMessage $ pullGroup D)
+ , ("C-m", withFocused (sendMessage . MergeAll))
+ , ("C-u", withFocused (sendMessage . UnMerge))
+
+ -- boring windows
+ , ("b", BW.markBoring)
+ , ("S-b", BW.clearBoring)
+
+ -- minimized widnows
+ , ("z", withFocused minimizeWindow)
+ , ("S-z", sendMessage RestoreNextMinimizedWin)
+
+ -- Toggle full screen
+ , ("<F12>", sendMessage ToggleStruts >> refresh)
+
+ -- Windows
+ , ("S-c", kill)
+ , ("C-S-c", WithAll.killAll)
+ , ("x", spawn "xkill")
+
+ -- Compositing
+ , ("S-x", SUB.submap $ EZ.mkKeymap conf $ concat
+ [ [(k, a), (modm ++ "-S-" ++ k, a)]
+ | (k, a) <- [ ("r", spawn "systemctl --user restart compositing")
+ , ("s", spawn "systemctl --user stop compositing")]
+ ])
+
+ -- Workspaces
+ , ("<Tab>", Local.toggleWS)
+ , ("S-<Tab>", Local.toggleWSSwitch)
+ , ("C-<Right>", moveTo Next nonEmptyWs)
+ , ("]", moveTo Next $ WSIs nonEmptyWsPred)
+ , ("C-<Left>", moveTo Prev $ WSIs nonEmptyWsPred)
+ , ("[", moveTo Prev $ WSIs nonEmptyWsPred)
+ , ("-", SUB.submap $ EZ.mkKeymap conf
+ [ (m ++ show k, withNthWorkspace f i)
+ | (k, i) <- (zip ([1..9] ++ [0]) [10..] :: [(Int, Int)])
+ , (f, m) <- concat
+ [ [ -- switch to ith workspace
+ (W.greedyView, m)
+ -- shift focused to ith workspace
+ , (\ws -> W.greedyView ws . W.shift ws, m ++ "S-")
+ ]
+ | m <- ["", modm ++ "-"]
]
+ ])
- -- no prefix
- keys :: [(String, X())]
- keys = [
- ("<XF86Calculator>",
- namedScratchpadAction namedScratchpads "calculator")
- , ("<XF86Mail>", TS.switchTopic topicConfig "mail")
- , ("<XF86Terminal>", Local.spawnShell Nothing)
- , ("<XF86Explorer>", spawn "Terminal")
- , ("<XF86HomePage>", TS.switchTopic topicConfig "web")
-
- -- mpc
- , ("<XF86AudioPlay>",
- io $ return . fromRight =<< MPD.withMPD MPD.toggle)
- , ("<XF86AudioStop>",
- io $ return . fromRight =<< MPD.withMPD MPD.stop)
- , ("<XF86AudioNext>",
- io $ return . fromRight =<< MPD.withMPD MPD.next)
- , ("<XF86AudioPrev>",
- io $ return . fromRight =<< MPD.withMPD MPD.previous)
-
- -- volume
- , ("<XF86AudioMute>", void toggleMute)
- , ("<XF86AudioRaiseVolume>", void (raiseVolume 4))
- , ("<XF86AudioLowerVolume>", void (lowerVolume 4))
-
- -- brightness
- , ("<XF86MonBrightnessUp>", spawn "xbacklight +10")
- , ("<XF86MonBrightnessDown>", spawn "xbacklight -10")
- , ("S-<XF86MonBrightnessUp>", spawn "xbacklight +20")
- , ("S-<XF86MonBrightnessDown>", spawn "xbacklight -20")
- , ("C-<XF86MonBrightnessUp>", spawn "xbacklight -set 100")
- , ("C-<XF86MonBrightnessDown>", spawn "xbacklight -set 0")
- ]
+ , ("n", promptedNewWorkspace False)
+ , ("S-n", promptedNewWorkspace True)
+ , ("S-<Backspace>", WithAll.killAll >> DW.removeWorkspace)
+ , ("S-r", DW.renameWorkspace xpConfig)
+ , ("c", TD.changeDir xpConfig)
+
+ , ("r", swapScreens)
+
+ , ("a", TS.currentTopicAction topicConfig)
+
+ -- Grid Select workspace
+ , ("i", goToSelected Local.gsConfig)
+ , ("s", gsw)
+ , ("S-s", gswShift)
+
+ -- xmonad
+ , ("q", SUB.submap $ EZ.mkKeymap conf $ concat
+ [ [(k, a), (modm ++ "-" ++ k, a)]
+ | (k, a) <- [ ("c", spawn "xmonad --recompile; xmonad --restart")
+ , ("r", spawn "xmonad --restart")
+ , ("u", spawn "undock")
+ , ("S-u", spawn "undock -s")
+ , ("e", spawn "monitor-hotplug")
+ , ("s", spawn "mate-session-save --shutdown-dialog")
+ , ("q", spawn "mate-session-save --logout")
+ , ("l", spawn "mate-screensaver-command --lock")
+ ]
+ ])
+ , ("C-q", spawn "mate-screensaver-command --lock")
+
+ -- namedScratchpads
+ , ("C-S-t", namedScratchpadAction namedScratchpads "htop")
+ , ("C-S-a", namedScratchpadAction namedScratchpads "stardict")
+ , ("C-S-n", namedScratchpadAction namedScratchpads "notes")
+ , ("C-S-u", namedScratchpadAction namedScratchpads "charmap")
+ , ("C-S-l", namedScratchpadAction namedScratchpads "alarm")
+ , ("C-S-p", namedScratchpadAction namedScratchpads "volctl")
+
+ -- misc
+ , ("S-h", PSsh.sshPrompt xpConfig)
+ --, ("<Print>", spawn "xfce4-screenshooter")
+ , ("y", spawn "xfce4-popup-clipman")
+ , ("<Print>", spawn "mate-screenshot")
+ , ("C-<Print>", spawn "mate-screenshot -w")
+ , ("S-<Print>", spawn "mate-screenshot -a")
+
+ -- MPD
+ -- mov current playing song in mpd to thrash
+ , ("<Delete>", spawn "mpcrm")
+ , ("<XF86Forward>",
+ io $ return . fromRight =<< MPD.withMPD MPD.next)
+ , ("<XF86Back>",
+ io $ return . fromRight =<< MPD.withMPD MPD.previous)
+ ]
+
+
+switchWorkspaceKeys :: [(String, X())]
+switchWorkspaceKeys =
+ [ (m ++ show i, withNthWorkspace f ((i + 9) `mod` 10))
+ | i <- [1..9] ++ [0]
+ , (f, m) <- [ (W.greedyView, "") -- switch to ith workspace
+ -- shift focused to ith workspace
+ , (\ws -> W.greedyView ws . W.shift ws, "S-")
+ ]
+ ]
+
+switchScreenKeys :: [(String, X())]
+switchScreenKeys =
+ [ (m ++ k, screenWorkspace sc >>= flip whenJust (windows . f))
+ | (k, sc) <- zip ["w", "e"] [0..]
+ , (f, m) <- [(W.view, ""), (W.shift, "S-")]
+ ]
+
+-- no prefix
+unprefixedKeys :: [(String, X())]
+unprefixedKeys = [
+ ("<XF86Calculator>",
+ namedScratchpadAction namedScratchpads "calculator")
+ , ("<XF86Mail>", TS.switchTopic topicConfig "mail")
+ , ("<XF86Terminal>", Local.spawnShell Nothing)
+ , ("<XF86Explorer>", spawn "Terminal")
+ , ("<XF86HomePage>", TS.switchTopic topicConfig "web")
+
+ -- mpc
+ , ("<XF86AudioPlay>",
+ io $ return . fromRight =<< MPD.withMPD MPD.toggle)
+ , ("<XF86AudioStop>",
+ io $ return . fromRight =<< MPD.withMPD MPD.stop)
+ , ("<XF86AudioNext>",
+ io $ return . fromRight =<< MPD.withMPD MPD.next)
+ , ("<XF86AudioPrev>",
+ io $ return . fromRight =<< MPD.withMPD MPD.previous)
+
+ -- volume
+ , ("<XF86AudioMute>", void toggleMute)
+ , ("<XF86AudioRaiseVolume>", void (raiseVolume 4))
+ , ("<XF86AudioLowerVolume>", void (lowerVolume 4))
+
+ -- brightness
+ , ("<XF86MonBrightnessUp>", spawn "xbacklight +10")
+ , ("<XF86MonBrightnessDown>", spawn "xbacklight -10")
+ , ("S-<XF86MonBrightnessUp>", spawn "xbacklight +20")
+ , ("S-<XF86MonBrightnessDown>", spawn "xbacklight -20")
+ , ("C-<XF86MonBrightnessUp>", spawn "xbacklight -set 100")
+ , ("C-<XF86MonBrightnessDown>", spawn "xbacklight -set 0")
+ ]
- _withNthWorkspace :: (String -> WindowSet -> WindowSet) -> Int -> X ()
- _withNthWorkspace job wnum = do
- sortfunc <- getSortByIndex
- ws <- gets ( map W.tag . sortfunc . namedScratchpadFilterOutWorkspace
- . W.workspaces . windowset )
- case drop wnum ws of
- (w:_) -> windows $ job w
- [] -> return ()
+withNthWorkspace :: (String -> WindowSet -> WindowSet) -> Int -> X ()
+withNthWorkspace job wnum = do
+ sortfunc <- getSortByIndex
+ ws <- gets ( map W.tag . sortfunc . namedScratchpadFilterOutWorkspace
+ . W.workspaces . windowset )
+ case drop wnum ws of
+ (w:_) -> windows $ job w
+ [] -> return ()
nonEmptyWsPred :: X (WindowSpace -> Bool)
nonEmptyWsPred = do