[xmonad] GLFW fullscreen

Dmitriy Matrosov sgf.dma at gmail.com
Mon Mar 6 20:03:29 UTC 2017


On 03/05/2017 03:08 PM, Tuncer Ayaz wrote:
>
> My patches are for fixing mupdf-gl (the GLFW created OpenGL viewer).
>
> desktopConfig, which is what I use in my extended version of
> example-config.hs, has basic EWMH enabled. Nonetheless, I've added
> handleEventHook with EwmhDesktops.fullscreenEventHook, but it didn't
> make a difference.
>
> I think you tried the x11 viewer and not glfw. Test mupdf-gl instead.
>

Ah, yes, i've tried `mupdf-x11`. But now, i think, i found the reason why
fullscreen doesn't work: as Brandon Allbery noted, the problem is in
advertising EWMH. It turns out, two atoms are missed in `_NET_SUPPORTED`:
`_NET_WM_STATE` and `_NET_WM_STATE_FULLSCREEN`. Without them glfw goes with
"override redirect" way and fullscreen does not work properly. Here is the
relevant code from `glfw/src/x11_window.c`:

    static void updateWindowMode(_GLFWwindow* window)
    {
        if (window->monitor)
        {
            if (_glfw.x11.xinerama.available &&
                _glfw.x11.NET_WM_FULLSCREEN_MONITORS)
            {
                sendEventToWM(window,
                              _glfw.x11.NET_WM_FULLSCREEN_MONITORS,
                              window->monitor->x11.index,
                              window->monitor->x11.index,
                              window->monitor->x11.index,
                              window->monitor->x11.index,
                              0);
            }

            if (_glfw.x11.NET_WM_STATE && _glfw.x11.NET_WM_STATE_FULLSCREEN)
            {
                sendEventToWM(window,
                              _glfw.x11.NET_WM_STATE,
                              _NET_WM_STATE_ADD,
                              _glfw.x11.NET_WM_STATE_FULLSCREEN,
                              0, 1, 0);
            }
            else
            {
                // This is the butcher's way of removing window decorations
                // Setting the override-redirect attribute on a window makes the
                // window manager ignore the window completely (ICCCM,
section 4)
                // The good thing is that this makes undecorated full
screen windows
                // easy to do; the bad thing is that we have to do everything
                // manually and some things (like iconify/restore) won't work at
                // all, as those are tasks usually performed by the
window manager

                XSetWindowAttributes attributes;
                attributes.override_redirect = True;
                XChangeWindowAttributes(_glfw.x11.display,
                                        window->x11.handle,
                                        CWOverrideRedirect,
                                        &attributes);

                window->x11.overrideRedirect = GLFW_TRUE;
            }

The right way is when (_glfw.x11.NET_WM_STATE &&
_glfw.x11.NET_WM_STATE_FULLSCREEN) == True.

So, apart from regular `XMonad.Hooks.EwmhDesktops` i need to advertise two
more atoms in `_NET_SUPPORTED`. Here is xmonad config working for me:

    import Data.Maybe
    import Control.Monad
    import XMonad
    import XMonad.Hooks.EwmhDesktops

    addNETSupported :: Atom -> X ()
    addNETSupported x   = withDisplay $ \dpy -> do
        r               <- asks theRoot
        a_NET_SUPPORTED <- getAtom "_NET_SUPPORTED"
        a               <- getAtom "ATOM"
        liftIO $ do
          sup <- (join . maybeToList) <$> getWindowProperty32 dpy
a_NET_SUPPORTED r
          when (fromIntegral x `notElem` sup) $
            changeProperty32 dpy r a_NET_SUPPORTED a propModeAppend
[fromIntegral x]

    addEWMHFullscreen :: X ()
    addEWMHFullscreen   = do
        wms <- getAtom "_NET_WM_STATE"
        wfs <- getAtom "_NET_WM_STATE_FULLSCREEN"
        mapM_ addNETSupported [wms, wfs]

    main :: IO ()
    main    = xmonad . ewmh $ def
                        { modMask = mod4Mask
                        , handleEventHook = fullscreenEventHook <+>
handleEventHook def
                        , startupHook = startupHook def >> addEWMHFullscreen
                        }


More information about the xmonad mailing list