X.Prelude: Add safeGetWindowAttributes

Move the function from X.U.DebugWindow, where it was defined already.
This is a safe version of getWindowAttributes, returning a Maybe instead
of throwing an exception, in case the window attributes could not be
retrieved.
This commit is contained in:
slotThe 2021-10-22 12:17:26 +02:00
parent 6cb2796fc0
commit 528b9d9fde
2 changed files with 12 additions and 8 deletions

View File

@ -1,4 +1,5 @@
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
-------------------------------------------------------------------- --------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Prelude -- Module : XMonad.Prelude
@ -20,8 +21,12 @@ module XMonad.Prelude (
(!?), (!?),
NonEmpty((:|)), NonEmpty((:|)),
notEmpty, notEmpty,
safeGetWindowAttributes,
) where ) where
import Foreign (alloca, peek)
import XMonad
import Control.Applicative as Exports import Control.Applicative as Exports
import Control.Monad as Exports import Control.Monad as Exports
import Data.Bool as Exports import Data.Bool as Exports
@ -68,3 +73,10 @@ chunksOf i xs = chunk : chunksOf i rest
notEmpty :: HasCallStack => [a] -> NonEmpty a notEmpty :: HasCallStack => [a] -> NonEmpty a
notEmpty [] = error "unexpected empty list" notEmpty [] = error "unexpected empty list"
notEmpty (x:xs) = x :| xs notEmpty (x:xs) = x :| xs
-- | A safe version of 'Graphics.X11.Extras.getWindowAttributes'.
safeGetWindowAttributes :: Window -> X (Maybe WindowAttributes)
safeGetWindowAttributes w = withDisplay $ \dpy -> io . alloca $ \p ->
xGetWindowAttributes dpy w p >>= \case
0 -> pure Nothing
_ -> Just <$> peek p

View File

@ -153,14 +153,6 @@ wrap s = ' ' : '"' : wrap' s ++ "\""
| otherwise = s' : wrap' ss | otherwise = s' : wrap' ss
wrap' "" = "" wrap' "" = ""
-- Graphics.X11.Extras.getWindowAttributes is bugggggggy
safeGetWindowAttributes :: Display -> Window -> IO (Maybe WindowAttributes)
safeGetWindowAttributes d w = alloca $ \p -> do
s <- xGetWindowAttributes d w p
case s of
0 -> return Nothing
_ -> Just <$> peek p
-- and so is getCommand -- and so is getCommand
safeGetCommand :: Display -> Window -> X [String] safeGetCommand :: Display -> Window -> X [String]
safeGetCommand d w = do safeGetCommand d w = do