Er. What version of ghc? That sounds like either a ghc runtime bug, or a system configuration issue. In particular, xmonad creates no threads itself, so that would be the ghc runtime's IO manager thread.

On Fri, Nov 30, 2018 at 3:07 PM Dmitriy Matrosov <sgf.dma@gmail.com> wrote:
On 11/30/2018 12:11 AM, Brandon Allbery wrote:
 > Yes. More specifically, it's ultimately using the execve() syscall, via
 > one of the wrappers which propagates the environment (which one depends
 > on whether it's asked to do $PATH search or not).

So.. here is version using environment:

         import XMonad
         import XMonad.Operations
         import XMonad.Util.EZConfig

         import System.Environment
         import Control.Exception

         main :: IO ()
         main = do
                 let xcf = def
                             { modMask = mod4Mask
                             , handleExtraArgs = disableKeysE
                             }
                             `additionalKeys`
                             [ ((mod4Mask, xK_d), disableKeysOn) ]
                 xmonad xcf

         disableKeysOn :: X ()
         disableKeysOn       = do
             trace "Preparing to disable keys and restarting.."
             io $ setEnv "XMONAD_DISABLE_KEYS" "1"
             restart "xmonad" True

         disableKeysE :: [String] -> XConfig Layout -> IO (XConfig Layout)
         disableKeysE _ xcf = do
             me <- lookupEnv "XMONAD_DISABLE_KEYS"
             case me of
               Just _    -> do
                 trace "Disabling all keys."
                 unsetEnv "XMONAD_DISABLE_KEYS"
                 return (xcf {keys = \_ -> mempty})
               Nothing   -> return xcf

It also restarts xmonad on key press (when disabling keys) and all
works fine, but.. xmonad frequently crashes with

         xmonad: failed to create OS thread: Resource temporarily
unavailable

I don't think this crash relates somehow to using environment, and it
happened from time to time before too, but still.. Can you advise,
how to fix it?

 > On Thu, Nov 29, 2018 at 4:07 PM Dmitriy Matrosov <sgf.dma@gmail.com
 > <mailto:sgf.dma@gmail.com>> wrote:
 >
 >     On 11/29/2018 09:50 PM, Brandon Allbery wrote:
 >      > You were talking about restart, between the running xmonad and its
 >      > replacement via executeFile. There, you can use the environment.
 >     There
 >      > is no way to pass information between an invoked "xmonad
 >     --restart" and
 >      > the running xmonad.
 >
 >     You mean, `executeFile` preserves environment? So, i may change
it from
 >     running xmonad (by e.g. keybinding) and then restart it?
 >
 >      > On Thu, Nov 29, 2018 at 6:01 AM Dmitriy Matrosov
 >     <sgf.dma@gmail.com <mailto:sgf.dma@gmail.com>
 >      > <mailto:sgf.dma@gmail.com <mailto:sgf.dma@gmail.com>>> wrote:
 >      >
 >      >
 >      >
 >      >     On November 28, 2018 9:25:00 PM GMT+03:00, Brandon Allbery
 >      >     <allbery.b@gmail.com <mailto:allbery.b@gmail.com>
 >     <mailto:allbery.b@gmail.com <mailto:allbery.b@gmail.com>>> wrote:
 >      >      >Not by default; there's already a bug (
 >      >      >https://github.com/xmonad/xmonad/issues/78) about our not
 >     obeying the
 >      >      >ICCCM
 >      >      >replace protocol unless started by replacing some other WM.
 >      >      >
 >      >      >There's a few other places you can hide extra parameters;
 >     starting
 >      >     that
 >      >      >early, the environment is probably the easiest to use,
provided
 >      >     they're
 >      >      >not
 >      >      >too large (see why there's a state file now).
 >      >
 >      >     Hm, i don't understand how to use environment. I need to pass
 >      >     something to running xmonad process (to which i send
 >      >     XMONAD_RESTART). As far as i know, i can't change
environment of
 >      >     another process..
 >      >
 >      >
 >      >      >On Wed, Nov 28, 2018 at 1:20 PM Dmitriy Matrosov
 >      >     <sgf.dma@gmail.com <mailto:sgf.dma@gmail.com>
 >     <mailto:sgf.dma@gmail.com <mailto:sgf.dma@gmail.com>>>
 >      >      >wrote:
 >      >      >
 >      >      >> Hi.
 >      >      >>
 >      >      >> On 11/21/2018 09:49 PM, Eyal Erez wrote:
 >      >      >> > Hi,
 >      >      >> >
 >      >      >> > I'm getting some collisions between my xmonad
 >     keybindings and an
 >      >      >> > application I'm running (it's a game that is suppose to
 >     run full
 >      >      >screen
 >      >      >> > but in reality just uses a large window).  I was
 >     wondering if I
 >      >      >could
 >      >      >> > suspend or change some keybindings from a script that I
 >     can run
 >      >      >before
 >      >      >> > the app launches and then restore later.
 >      >      >> >
 >      >      >> > Is this at all possible?  Happy to entertain other
options.
 >      >      >>
 >      >      >> Here is proof of concept:
 >      >      >>
 >      >      >>
 >      >      >>          import XMonad
 >      >      >>          import XMonad.Hooks.EwmhDesktops
 >      >      >>
 >      >      >>          import System.Directory
 >      >      >>          import System.FilePath
 >      >      >>
 >      >      >>
 >      >      >>          main :: IO ()
 >      >      >>          main = do
 >      >      >>                  let xcf = ewmh $ def
 >      >      >>                              { modMask = mod4Mask
 >      >      >>                              , handleExtraArgs =
disableKeys
 >      >      >>                              }
 >      >      >>                  xmonad xcf
 >      >      >>
 >      >      >>          disableKeys :: [String] -> XConfig Layout -> IO
 >     (XConfig
 >      >      >Layout)
 >      >      >>          disableKeys _ xcf = do
 >      >      >>              xd <- getXMonadDir
 >      >      >>              let disableFn = xd </> "disable_keys"
 >      >      >>              b <- doesFileExist disableFn
 >      >      >>              if b
 >      >      >>                then do
 >      >      >>                  trace "Disabling all keys."
 >      >      >>                  removeFile disableFn
 >      >      >>                  return (xcf {keys = \_ -> mempty})
 >      >      >>                else return xcf
 >      >      >>
 >      >      >>
 >      >      >> To disable all keys create file `~/.xmonad/disable_keys`
 >     and then
 >      >      >> restart xmonad with `xmonad --restart`. All keys will be
 >     disabled
 >      >      >> _and_ file deleted (to avoid locking yourself), thus next
 >     restart
 >      >      >will
 >      >      >> restore all keys back.
 >      >      >>
 >      >      >> As far as i understand, xmonad grabs keys in
 >     `X.Main.launch` before
 >      >      >> entering main loop. Thus, the one way to change key grab
 >     is to
 >      >      >restart
 >      >      >> xmonad. I need to modify `XConfig` before calling
 >      >     X.Main.launch`, and
 >      >      >> this may be done by `handleExtraArgs` (called in
`launch'` in
 >      >      >> `X.Main.xmonad`). Unfortunately, it seems, that xmonad
 >     does not
 >      >     allow
 >      >      >> to pass extra cmd arguments during restart
 >     (`X.Operations.restart`
 >      >      >> always starts xmonad with name `xmonad` and no
 >     arguments). Also, i
 >      >      >> can't use extensible state in `handleExtraArgs`, because
 >     it runs in
 >      >      >> `IO` (`X` context is not yet built at that time).  Thus,
 >     to pass
 >      >      >> something to it, i may use either file or (probably)
 >      >     `--replace`. The
 >      >      >> above version uses file. And i have no luck with
 >     `--replace`: it
 >      >      >> seems, `xmonad` can't replace itself?..
 >      >      >> _______________________________________________
 >      >      >> xmonad mailing list
 >      >      >> xmonad@haskell.org <mailto:xmonad@haskell.org>
 >     <mailto:xmonad@haskell.org <mailto:xmonad@haskell.org>>
 >      >      >> http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad
 >      >      >>
 >      >     _______________________________________________
 >      >     xmonad mailing list
 >      > xmonad@haskell.org <mailto:xmonad@haskell.org>
 >     <mailto:xmonad@haskell.org <mailto:xmonad@haskell.org>>
 >      > http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad
 >      >
 >      >
 >      >
 >      > --
 >      > brandon s allbery kf8nh
 >      > allbery.b@gmail.com <mailto:allbery.b@gmail.com>
 >     <mailto:allbery.b@gmail.com <mailto:allbery.b@gmail.com>>
 >
 >     _______________________________________________
 >     xmonad mailing list
 >     xmonad@haskell.org <mailto:xmonad@haskell.org>
 >     http://mail.haskell.org/cgi-bin/mailman/listinfo/xmonad
 >
 >
 >
 > --
 > brandon s allbery kf8nh
 > allbery.b@gmail.com <mailto:allbery.b@gmail.com>



--
brandon s allbery kf8nh
allbery.b@gmail.com