[xmonad] RFC: Handling fullscreen with layouts

Gmail audunskaugen at gmail.com
Wed Jul 7 07:19:48 EDT 2010


As mentioned in another mail, I'm currently experimenting with handling
fullscreening applications in the layout itself, using layout messages.
I'll highlight the approach here.

First, we'll need a new layout message:

data FullscreenMessage = AddFullscreen Window
                          | RemoveFullscreen Window
        deriving (Typeable)
instance Message FullscreenMessage

This message will be sent to all layouts when a window requests fullscreen
through the _NET_WM_STATE protocol, using a special event hook (resembling
the fullscreenEventHook in X.H.EwmhDesktops, but sending messages instead
of modifying the window). Also, we'll need a manage hook that sends an
AddFullscreen on the window if it starts out with the fullscreen property.

Now we can write a simple layout modifier to make the modified layout
respect fullscreen:

data FullscreenFull a = FullscreenFull [a]
        deriving (Read, Show)

instance LayoutModifier FullscreenFull Window where
     -- This handler maintains the modifier's list of fullscreen windows
     pureMess (FullscreenFull fulls) m = case fromMessage m of
       Just (AddFullscreen win) -> Just $ FullscreenFull $ nub $ win:fulls
       Just (RemoveFullscreen win) ->
         Just $ FullscreenFull $ delete win $ fulls
       Nothing -> Nothing

     -- All the fullscreened windows should fill the screen, the rest of the
windows are left in place
     pureModifier (FullscreenFull fulls) rect _ list =
       (zip visfulls (repeat rect) ++ rest, Nothing)
       where visfulls = intersect fulls $ map fst list
             rest = [(w,r) | (w,r) <- list, w `notElem` fulls]

The advantage of this approach is made clearer by a small variant of the
above modifier that only fullscreens the window if it is focused:

data FullscreenFocus a = FullscreenFocus [a]
        deriving (Read, Show)

instance LayoutModifier FullscreenFocus Window where
     -- pureMess like above

     -- The focused window should fill the screen
     pureModifier (FullscreenFocus fulls) rect (Just (W.Stack {W.focus =  
f}))
list =
        (if f `elem` fulls then (f,rect):rest else list, Nothing)
        where rest = [(w,r) | (w,r) <- list, w /= f]
     pureModifier _ _ Nothing list = (list, Nothing)

You can even toggle between such variants using something like
X.L.MultiToggle.

There are a few disadvantages to this approach:
    * Complexity - this is a lot more code than a simple event hook
    * More configuration - you need to add a manage hook and a layout
modifier in addition to the event hook to use this
    * Floating windows are difficult to handle. I have tried to hack  
together
a layout modifier that would call the X monad in order to fullscreen
floating windows, but even if it works it's going to be ugly
    * Youtube fullscreen won't work with this, unless you add another manage
hook like this:
       className =? "Npviewer.bin" --> doFullFloat

I've attached the module I'm currently keeping in my .xmonad/lib
directory, implementing all of this. Does anyone have any thoughts about
it?

-- 
Audun Skaugen
-------------- next part --------------
A non-text attachment was scrubbed...
Name: Fullscreen.hs
Type: application/octet-stream
Size: 3273 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/xmonad/attachments/20100707/e3e6daf6/Fullscreen.obj


More information about the xmonad mailing list