Search code examples
haskellxmonad

Remove borders from windows of specific class


I'm trying to write a layout modifier very similar that would allow me to remove borders based on class name property of the windows. The code is largely based on XMonad.Layout.NoBorders with the exception of the logic executing in the X monad to allow filtering based on className. The code I've got so far is:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}

module  XMonad.Layout.ExcludeBorders  where

import           Control.Monad
import           Data.Monoid
import           XMonad
import           XMonad.Layout.LayoutModifier
import           XMonad.StackSet hiding (filter)

setBorders :: [Window] -> Dimension -> X ()
setBorders ws bw =
  withDisplay $ \d -> mapM_ (\w -> io $ setWindowBorderWidth d w bw) ws

data ExcludeBorders p a =
  ExcludeBorders p
                 [a]
  deriving (Eq, Read, Show)

excludeBorders :: p -> l a -> ModifiedLayout (ExcludeBorders p) l a
excludeBorders qs = ModifiedLayout (ExcludeBorders qs [])

instance (Show p, Read (ExcludeBorders p Window), Excludes p) =>
         LayoutModifier (ExcludeBorders p) Window where
  unhook (ExcludeBorders _p s) = asks (borderWidth . config) >>= setBorders s
  redoLayout (ExcludeBorders p _s) _ mst wrs = do
    ws <- withWindowSet (\wset -> excludes p wset mst wrs)
    setBorders ws 0
    return (wrs, Just $ ExcludeBorders p ws)

class Excludes p where
  excludes ::
       p
    -> WindowSet
    -> Maybe (Stack Window)
    -> [(Window, Rectangle)]
    -> X [Window]

data ExcludeProp =
  ExcludeClassName String
  deriving (Eq, Read, Show)

instance Excludes [ExcludeProp] where
  excludes qs _wset mst _wrs =
    flip filterM (integrate' mst) $ \w ->
      fmap (getAny . mconcat) .
      sequenceA . map (fmap Any . flip runQuery w . toQuery) $
      qs

toQuery :: ExcludeProp -> Query Bool
toQuery (ExcludeClassName s) = className =? s

which can be used in the layout hook as follows:

excludeBorders [ExcludeClassName "Krunner", ExcludeClassName "plasmashell"]

Unfortunately as is it doesn't have the desired effect, or any effect at all.. Being completely new to writing layout modifiers I'm not sure what I'm doing wrong, and perhaps I misunderstand how the redoLayout function is supposed to work. Any pointers would be appreciated.


EDIT: Some further testing shows this may be a peculiarity of KDE / plasma windows and / or issue with my config rather that anything to do with my code.


Solution

  • Turns out the main logic was fine except for not accounting for floating windows. Changing the Excludes instance as follows:

    instance Excludes [ExcludeProp] where
      excludes qs wset mst _wrs =
        let ws = integrate' mst ++ [w | (w, _) <- Map.toList . floating $ wset]
        in flip filterM ws $ \w ->
             fmap (getAny . mconcat) .
             sequenceA . map (fmap Any . flip runQuery w . toQuery) $
             qs
    

    makes it work for my use case.