
On Sun, Aug 14, 2011 at 06:05, Jochen Keil
wrote: However, if I call foo from a keybinding
((modMask, xK_x), foo)
the spawned program will run but not mapped. This means that I can see the console output in xmonad stdout/stderr but the window will not pop up. I think this is because of the internal handling of keyevents in
It's because your function is doing stuff instead of listening for X events. If you want to go off and do something else, forkIO a thread I've already tried forkIO, xfork, seq, par, etc. all with more or less
Hi, On 08/14/2011 07:07 PM, Brandon Allbery wrote: the same result: the program's window will be mapped only after the function returns.
for the something else. If your something else requires communication with X11, you'll need to think about rewriting around the event handler instead. I can't see how to do this at the moment. Is this even possible? As far as I understand/stood the xmonad code it's all about grabbing events.
code I have written. It's some kind of of vi-mode behaviour for xmonad.
XMonad.Actions.Submap would be a good starting point for this. Not an ideal one, as it doesn't support timeouts or grabbing an entire submap. Well, at least the timeout issue is solved. :) Concerning the submap. I currently take my regular keymap and AND the complemented modMask from the modifier. Then I feed this into my vi-mode function as keymap.
But maybe you want to take a look for yourself. I've attached the code inline below. Regards, Jochen defaultConfig { keys = myKeyMap conf etc `Data.Map.union` viKeys conf } viKeys (XConfig { XMonad.modMask = modMask }) keyMap = M.fromList $ [ ((modMask, xK_z), viMode modMask xK_z (myKeyHandler keyMap)) ] where cleanMask mod = complement modMask .&. mod myKeyHandler km m k = M.lookup (cleanMask m, k) $ M.mapKeys (\(mod, key) -> (cleanMask mod, key)) $ M.delete (modMask, xK_z) km module XMonad.Actions.ViMode ( viMode ) where import Data.Map as M import Data.Maybe (fromMaybe) import XMonad hiding (workspaces) import qualified XMonad.StackSet as W keyEvent :: Display -> IO (EventType, ButtonMask, Time, KeySym) keyEvent d = do allocaXEvent $ \p -> do maskEvent d (keyPressMask .|. keyReleaseMask) p KeyEvent { ev_event_type = e , ev_state = s , ev_time = t , ev_keycode = kc} <- getEvent p fmap (\ks -> (e, s, t, ks)) $ keycodeToKeysym d kc 0 grabKeys :: X () grabKeys = do XConf {theRoot = root, display = d} <- ask io $ grabKeyboard d root False grabModeAsync grabModeAsync currentTime return () releaseKeys :: X () releaseKeys = do d <- asks display io $ ungrabKeyboard d currentTime viMode :: ButtonMask -> KeySym -> (ButtonMask -> KeySym -> Maybe (X ())) -> X () viMode mod key f = asks display >>= cycleKeys (mod, key, 0, True) f cycleKeys :: (ButtonMask, KeySym, Time, Bool) -> (ButtonMask -> KeySym -> Maybe (X ())) -> Display -> X () cycleKeys (mod, key, last, grab) keyHandler d = do if grab then grabKeys >> cycleKeys (mod, key, last, False) keyHandler d else do io $ flush d timeout <- io $ waitForEvent d 1000000 if timeout then releaseKeys else io (keyEvent d) >>= keyDecision where keyDecision (e, s, t, ks) | e == keyPress && s == mod && ks == key = releaseKeys | e == keyPress = do case keyHandler s ks of Just action -> do action cycleKeys (mod, key, t, False) keyHandler d Nothing -> releaseKeys | otherwise = cycleKeys (mod, key, t, False) keyHandler d