How can I set an action to occur on a key release in xmonad?

ぃ、小莉子 提交于 2019-12-09 12:02:39

问题


How can I set an action to occur on a key release in xmonad?

I don't like menu bars and panels. Instead of a panel like xmobar I want to have a full screen page of info, (time, currently selected window and workspace etc) appear when I hold down a key combo and then vanish when I let the keys go. I could code the info page application myself. I can set the info page to spawn on a key press.

I can not set anything to happen on a key release.

How can I set an action to occur on a key release?

I am considering extending xmonad myself to do this. I hope I don't have to though because it'd be really annoying.


回答1:


XMonad passes all received events, including KeyPress events, to the handleEventHook, so this code would be able to react on keyRelease events:

module KeyUp where

import Data.Monoid
import qualified Data.Map as M

import XMonad
import Control.Monad

keyUpEventHook :: Event -> X All
keyUpEventHook e = handle e >> return (All True)

keyUpKeys (XConf{ config = XConfig {XMonad.modMask = modMask} }) = M.fromList $ 
    [ ((modMask, xK_v), io (print "Hi")) ]

handle :: Event -> X ()
handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
    | t == keyRelease = withDisplay $ \dpy -> do
        s  <- io $ keycodeToKeysym dpy code 0
        mClean <- cleanMask m
        ks <- asks keyUpKeys
        userCodeDef () $ whenJust (M.lookup (mClean, s) ks) id
handle _ = return ()

You would use it like that in your xmonad.hs file:

handleEventHook    = handleEventHook defaultConfig `mappend`
                     keyUpEventHook `mappend`
                     fullscreenEventHook

Unfortunately, this does not work yet: It will only react on KeyRelease events that have a corresponding entry in the regular keys configuration. This is due to grayKeys in XMonad.Main, grabbing only keys mentioned in keys. You can work-around this by defining a dummy action for every combination that you want to handle in KeyUp:

myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
    ...
    , ((modMask              , xK_v     ), return ())



回答2:


myStartupHook :: X ()
myStartupHook = do
  XConf { display = dpy, theRoot = rootw } <- ask
  myKeyCode <- io $ (keysymToKeycode dpy xK_Super_R)
  io $ grabKey dpy (myKeyCode) anyModifier rootw True grabModeAsync grabModeAsync
  spawn "~/ScriptsVcs/hideTint2.sh"

myHook :: Event -> X All
myHook e = do
  case e of
    ke@(KeyEvent _ _ _ _ _ _ _ _ _ _ _ _ _ _ _) -> do
      if ev_keycode ke == 134
        then if ev_state ke == 0
          then do
            -- key has been pressed
            spawn "~/ScriptsVcs/showTint2.sh"
          else do
            spawn "~/ScriptsVcs/hideTint2.sh"
        else pure ()
    _ -> pure ()
  pure $ All True

The above is an example. Do take note that a 'key release' could occur with a modifier key (ev_state).



来源:https://stackoverflow.com/questions/6605399/how-can-i-set-an-action-to-occur-on-a-key-release-in-xmonad

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!