X () with side effects

Hello, I am trying to write a function which has side-effects, e.g. call spawn. foo :: X () foo = do io $ spawn "myprogram" doSomethingElseOrReturn foo -- recursion 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 xmonads main. Is there a way I could bypass this and have my windows mapped as soon as I call the program with spawn? I hope this is clear enough.. if not, I'll come back with the actual code I have written. It's some kind of of vi-mode behaviour for xmonad. Pure X actions (like focusing up/down) work without problems but spawning doesn't. Many thanks and best regards, Jochen

On Sun, Aug 14, 2011 at 06:05, Jochen Keil
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 for the something else. If your something else requires communication with X11, you'll need to think about rewriting around the event handler instead.
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. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

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

On Sun, Aug 14, 2011 at 17:03, Jochen Keil
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
seq and par won't do anything useful here (seq has nothing to do with parallelism and par isn't designed for this kind of usage). Also, xmonad doesn't use OS threads, and it's just occurred to me that there's no way to hook the X event loop into GHC's thread scheduler, so forkIO won't actually be useful anyway. :( xfork spawns a subprocess, which would then need to send X events to the main event loop which you would handle in the handleEventHook. This is also how an independent thread would need to communicate.
the same result: the program's window will be mapped only after the function returns.
...this happens with forkIO as well? I'm tempted to say you didn't use it properly; "after the function returns" isn't one of the behaviors I'd expect unless you're trying to synchronize with the thread as well.
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.
That's *why* event passing is how it should be solved. As to the how: sendEvent and the handleEventHook.
timeout <- io $ waitForEvent d 1000000
-- this is oversimplistic: you need to make sure the MyTimeoutEvent corresponds -- to the current vmap and not an earlier one, by storing some kind of id in both. -- You can't simply pass the vmap because it's going to take a trip
*sigh* This is a good way to make xmonad stop processing events. You must *not* do this if you expect xmonad to be usable while waiting. (This is why X.A.Submap doesn't try to handle timeouts.) Instead, you need to have the event loop manage it. Use ExtensibleState to store the keymap state and start time; the handleEventHook recognizes a key, checks the ExtensibleState to see if it's useful, and if so acts on it and returns All False to prevent xmonad's default handler from also acting on the key. Acting on it may involve updating the state to point to a new submap, or performing some xmonad action. You should also forkIO a timeout thread which invokes (delay) (see Control.Concurrent) and then sendEvent to send a timeout event which is also processed by the handleEventHook. (Remember to clear the ExtensibleState as well as invoking releaseKeys.) through the X11
-- server and there's no guarantee the same pointer comes back. handleEventHook (SendEvent {ev_type = e}) | e == MyTimeoutEvent = releaseKeys >> ES.put () >> return (All False) handleEventHook (KeyPress {ev_key = k}) = do vmap <- ES.get -- state of vi keymap -- keyDecision goes here, more or less -- if you update the keymap, delete the
-- the initial key binding then places the vi keymap in ES and spawns a timeout -- thread, allowing the handleEventHook to do the rest.
-- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms
participants (2)
-
Brandon Allbery
-
Jochen Keil