Prefer safe alternatives to getWindowAttributes

Whenever possible, prefer the safe wrappers withWindowAttributes or
safeGetWindowAttributes to getWindowAttributes.

Places where these are not applicable are limited to layouts, where
there is not good "default value" to give back in case these calls fail.
In these cases, we let the exception handling of the layout mechanism
handle it and fall back to the Full layout.

Fixes: https://github.com/xmonad/xmonad-contrib/issues/146
This commit is contained in:
slotThe
2021-10-23 12:29:19 +02:00
parent 528b9d9fde
commit b6a8069e44
19 changed files with 101 additions and 123 deletions

View File

@@ -23,17 +23,9 @@ module XMonad.Layout.FixedColumn (
FixedColumn(..)
) where
import Graphics.X11.Xlib (Window, rect_width)
import Graphics.X11.Xlib.Extras ( getWMNormalHints
, getWindowAttributes
, sh_base_size
, sh_resize_inc
, wa_border_width)
import XMonad.Prelude (fromMaybe, msum, (<&>))
import XMonad.Core (X, LayoutClass(..), fromMessage, io, withDisplay)
import XMonad.Layout (Resize(..), IncMasterN(..), tile)
import XMonad.StackSet as W
import XMonad
import XMonad.Prelude
import qualified XMonad.StackSet as W
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
@@ -82,9 +74,10 @@ instance LayoutClass FixedColumn Window where
-- columns wide, using @inc@ as a resize increment for windows that
-- don't have one
widthCols :: Int -> Int -> Window -> X Int
widthCols inc n w = withDisplay $ \d -> io $ do
sh <- getWMNormalHints d w
bw <- fromIntegral . wa_border_width <$> getWindowAttributes d w
widthCols inc n w = do
d <- asks display
bw <- asks $ fi . borderWidth . config
sh <- io $ getWMNormalHints d w
let widthHint f = f sh <&> fromIntegral . fst
oneCol = fromMaybe inc $ widthHint sh_resize_inc
base = fromMaybe 0 $ widthHint sh_base_size

View File

@@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
{-# LANGUAGE ParallelListComp, PatternGuards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE LambdaCase #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.LayoutHints
@@ -32,8 +33,8 @@ import XMonad(LayoutClass(runLayout), mkAdjust, Window,
Dimension, Position, Rectangle(Rectangle), D,
X, refresh, Event(..), propertyNotify, wM_NORMAL_HINTS,
(<&&>), io, applySizeHints, whenX, isClient, withDisplay,
getWindowAttributes, getWMNormalHints, WindowAttributes(..))
import XMonad.Prelude (All (..), fromJust, join, maximumBy, on, sortBy)
getWMNormalHints, WindowAttributes(..))
import XMonad.Prelude
import qualified XMonad.StackSet as W
import XMonad.Layout.Decoration(isInStack)
@@ -264,8 +265,9 @@ hintsEventHook _ = return (All True)
-- | True if the window's current size does not satisfy its size hints.
hintsMismatch :: Window -> X Bool
hintsMismatch w = withDisplay $ \d -> io $ do
wa <- getWindowAttributes d w
sh <- getWMNormalHints d w
let dim = (fromIntegral $ wa_width wa, fromIntegral $ wa_height wa)
return $ dim /= applySizeHints 0 sh dim
hintsMismatch w = safeGetWindowAttributes w >>= \case
Nothing -> pure False
Just wa -> do
sh <- withDisplay $ \d -> io (getWMNormalHints d w)
let dim = (fromIntegral $ wa_width wa, fromIntegral $ wa_height wa)
return $ dim /= applySizeHints 0 sh dim

View File

@@ -62,8 +62,9 @@ import qualified XMonad.StackSet as W
-- | Modify all screens.
layoutScreens :: LayoutClass l Int => Int -> l Int -> X ()
layoutScreens nscr _ | nscr < 1 = trace $ "Can't layoutScreens with only " ++ show nscr ++ " screens."
layoutScreens nscr l =
do rtrect <- asks theRoot >>= getWindowRectangle
layoutScreens nscr l = asks theRoot >>= \w -> withDisplay $ \d ->
withWindowAttributes d w $ \attrs ->
do let rtrect = windowRectangle attrs
(wss, _) <- runLayout (W.Workspace "" l (Just $ W.Stack { W.focus=1, W.up=[],W.down=[1..nscr-1] })) rtrect
windows $ \ws@W.StackSet{ W.current = v, W.visible = vs, W.hidden = hs } ->
let x = W.workspace v
@@ -88,11 +89,9 @@ layoutSplitScreen nscr l =
map (\v -> if W.screen v>W.screen c then v{W.screen = W.screen v + fromIntegral (nscr-1)} else v) vs
, W.hidden = ys }
getWindowRectangle :: Window -> X Rectangle
getWindowRectangle w = withDisplay $ \d ->
do a <- io $ getWindowAttributes d w
return $ Rectangle (fromIntegral $ wa_x a) (fromIntegral $ wa_y a)
(fromIntegral $ wa_width a) (fromIntegral $ wa_height a)
windowRectangle :: WindowAttributes -> Rectangle
windowRectangle a = Rectangle (fromIntegral $ wa_x a) (fromIntegral $ wa_y a)
(fromIntegral $ wa_width a) (fromIntegral $ wa_height a)
newtype FixedLayout a = FixedLayout [Rectangle] deriving (Read,Show)