Skip to content

Commit

Permalink
Added X.H.ManageHelpers.isMinimized, BSP: ignore hidden windows
Browse files Browse the repository at this point in the history
  • Loading branch information
Samuli Thomasson authored and SimSaladin committed May 17, 2021
1 parent 41ba7fd commit 340e2db
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 8 deletions.
6 changes: 6 additions & 0 deletions XMonad/Hooks/ManageHelpers.hs
Expand Up @@ -34,6 +34,7 @@ module XMonad.Hooks.ManageHelpers (
isInProperty,
isKDETrayWindow,
isFullscreen,
isMinimized,
isDialog,
pid,
transientTo,
Expand Down Expand Up @@ -157,6 +158,11 @@ isInProperty p v = ask >>= \w -> liftX $ do
isFullscreen :: Query Bool
isFullscreen = isInProperty "_NET_WM_STATE" "_NET_WM_STATE_FULLSCREEN"

-- | A predicate to check whether a window is hidden (minimized).
-- See also "XMonad.Actions.Minimize".
isMinimized :: Query Bool
isMinimized = isInProperty "_NET_WM_STATE" "_NET_WM_STATE_HIDDEN"

-- | A predicate to check whether a window is a dialog.
isDialog :: Query Bool
isDialog = isInProperty "_NET_WM_WINDOW_TYPE" "_NET_WM_WINDOW_TYPE_DIALOG"
Expand Down
22 changes: 14 additions & 8 deletions XMonad/Layout/BinarySpacePartition.hs
Expand Up @@ -36,6 +36,7 @@ module XMonad.Layout.BinarySpacePartition (
import XMonad
import XMonad.Prelude
import qualified XMonad.StackSet as W
import XMonad.Hooks.ManageHelpers (isMinimized)
import XMonad.Util.Stack hiding (Zipper)
import XMonad.Util.Types

Expand Down Expand Up @@ -675,20 +676,23 @@ replaceFloating wsm = do
getFloating :: X [Window]
getFloating = (M.keys . W.floating) <$> gets windowset -- all floating windows

getHidden :: X [Window]
getHidden = (W.integrate' <$> getStackSet) >>= filterM (runQuery isMinimized)

getStackSet :: X (Maybe (W.Stack Window))
getStackSet = (W.stack . W.workspace . W.current) <$> gets windowset -- windows on this WS (with floating)

getScreenRect :: X Rectangle
getScreenRect = (screenRect . W.screenDetail . W.current) <$> gets windowset

withoutFloating :: [Window] -> Maybe (W.Stack Window) -> Maybe (W.Stack Window)
withoutFloating fs = maybe Nothing (unfloat fs)
withoutFloating :: [Window] -> [Window] -> Maybe (W.Stack Window) -> Maybe (W.Stack Window)
withoutFloating fs hs = maybe Nothing (unfloat fs hs)

-- ignore messages if current focus is on floating window, otherwise return stack without floating
unfloat :: [Window] -> W.Stack Window -> Maybe (W.Stack Window)
unfloat fs s = if W.focus s `elem` fs
unfloat :: [Window] -> [Window] -> W.Stack Window -> Maybe (W.Stack Window)
unfloat fs hs s = if W.focus s `elem` fs
then Nothing
else Just $ s{W.up = W.up s \\ fs, W.down = W.down s \\ fs}
else Just $ s{W.up = W.up s \\ (fs ++ hs), W.down = W.down s \\ (fs ++ hs)}

instance LayoutClass BinarySpacePartition Window where
doLayout b r s = do
Expand Down Expand Up @@ -722,9 +726,10 @@ instance LayoutClass BinarySpacePartition Window where
| otherwise = do
ws <- getStackSet
fs <- getFloating
hs <- getHidden
r <- getScreenRect
-- removeBorder $ refWins $ getSelectedNode b
let lws = withoutFloating fs ws -- tiled windows on WS
let lws = withoutFloating fs hs ws -- tiled windows on WS
lfs = maybe [] W.integrate ws \\ maybe [] W.integrate lws -- untiled windows on WS
b' = handleMesg r -- transform tree (concerns only tiled windows)
ws' = adjustStack ws lws lfs b' -- apply transformation to window stack, reintegrate floating wins
Expand Down Expand Up @@ -762,6 +767,7 @@ handleResize :: BinarySpacePartition Window -> WindowArrangerMsg -> X (Maybe (Bi
handleResize b (SetGeometry newrect@(Rectangle _ _ w h)) = do
ws <- getStackSet
fs <- getFloating
hs <- getHidden
case W.focus <$> ws of
Nothing -> return Nothing
Just win -> do
Expand All @@ -770,7 +776,7 @@ handleResize b (SetGeometry newrect@(Rectangle _ _ w h)) = do
let (xsc,ysc) = (fi w % fi ow, fi h % fi oh)
(xsc',ysc') = (rough xsc, rough ysc)
dirs = changedDirs oldrect newrect (fi mx,fi my)
n = elemIndex win $ maybe [] W.integrate $ withoutFloating fs ws
n = elemIndex win $ maybe [] W.integrate $ withoutFloating fs hs ws
-- unless (isNothing dir) $ debug $
-- show (fi x-fi ox,fi y-fi oy) ++ show (fi w-fi ow,fi h-fi oh)
-- ++ show dir ++ " " ++ show win ++ " " ++ show (mx,my)
Expand Down Expand Up @@ -801,7 +807,7 @@ updateNodeRef b force r = do
else return b
b'' <- if force then return b'{getSelectedNode=noRef} else return b'
renderBorders r b''
where getCurrFocused = maybe 0 index <$> (withoutFloating <$> getFloating <*> getStackSet)
where getCurrFocused = maybe 0 index <$> (withoutFloating <$> getFloating <*> getHidden <*> getStackSet)

-- create border around focused node if necessary
renderBorders :: Rectangle -> BinarySpacePartition a -> X (BinarySpacePartition a)
Expand Down

0 comments on commit 340e2db

Please sign in to comment.