mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-11 18:21:51 -07:00
Hide windows that are not supposed to be visible
This commit is contained in:
@@ -21,7 +21,7 @@ import qualified StackSet as W
|
|||||||
import {-# SOURCE #-} Config (borderWidth,logHook,numlockMask)
|
import {-# SOURCE #-} Config (borderWidth,logHook,numlockMask)
|
||||||
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.List (genericIndex, intersectBy)
|
import Data.List (genericIndex, intersectBy, nub, (\\))
|
||||||
import Data.Bits ((.|.), (.&.), complement)
|
import Data.Bits ((.|.), (.&.), complement)
|
||||||
import Data.Ratio
|
import Data.Ratio
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
@@ -84,9 +84,7 @@ swapMaster = windows W.swapMaster
|
|||||||
|
|
||||||
-- | shift. Move a window to a new workspace, 0 indexed.
|
-- | shift. Move a window to a new workspace, 0 indexed.
|
||||||
shift :: WorkspaceId -> X ()
|
shift :: WorkspaceId -> X ()
|
||||||
shift n = withFocused hide >> windows (W.shift n)
|
shift n = windows (W.shift n)
|
||||||
-- TODO: get rid of the above hide. 'windows' should handle all hiding and
|
|
||||||
-- revealing of windows
|
|
||||||
|
|
||||||
-- | view. Change the current workspace to workspace at offset n (0 indexed).
|
-- | view. Change the current workspace to workspace at offset n (0 indexed).
|
||||||
view :: WorkspaceId -> X ()
|
view :: WorkspaceId -> X ()
|
||||||
@@ -131,12 +129,13 @@ windows :: (WindowSet -> WindowSet) -> X ()
|
|||||||
windows f = do
|
windows f = do
|
||||||
sendMessage ModifyWindows
|
sendMessage ModifyWindows
|
||||||
XState { windowset = old, layouts = fls, xineScreens = xinesc, statusGaps = gaps } <- get
|
XState { windowset = old, layouts = fls, xineScreens = xinesc, statusGaps = gaps } <- get
|
||||||
let ws = f old
|
let oldvisible = concatMap (W.integrate . W.stack . W.workspace) $ W.current old : W.visible old
|
||||||
|
ws = f old
|
||||||
modify (\s -> s { windowset = ws })
|
modify (\s -> s { windowset = ws })
|
||||||
d <- asks display
|
d <- asks display
|
||||||
|
|
||||||
-- for each workspace, layout the currently visible workspaces
|
-- for each workspace, layout the currently visible workspaces
|
||||||
forM_ (W.current ws : W.visible ws) $ \w -> do
|
visible <- fmap concat $ forM (W.current ws : W.visible ws) $ \w -> do
|
||||||
let n = W.tag (W.workspace w)
|
let n = W.tag (W.workspace w)
|
||||||
this = W.view n ws
|
this = W.view n ws
|
||||||
Just l = fmap fst $ M.lookup n fls
|
Just l = fmap fst $ M.lookup n fls
|
||||||
@@ -185,17 +184,16 @@ windows f = do
|
|||||||
-- pass to the last tiled window that had focus.
|
-- pass to the last tiled window that had focus.
|
||||||
-- urgh : not our delete policy, but close.
|
-- urgh : not our delete policy, but close.
|
||||||
|
|
||||||
|
-- return the visible windows for this workspace:
|
||||||
|
return (map fst rs ++ flt)
|
||||||
|
|
||||||
setTopFocus
|
setTopFocus
|
||||||
logHook
|
logHook
|
||||||
-- io performGC -- really helps, but seems to trigger GC bugs?
|
-- io performGC -- really helps, but seems to trigger GC bugs?
|
||||||
|
|
||||||
-- We now go to some effort to compute the minimal set of windows to hide.
|
-- hide every window that was potentially visible before, but is not
|
||||||
-- The minimal set being only those windows which weren't previously hidden,
|
-- given a position by a layout now.
|
||||||
-- which is the intersection of previously visible windows with those now hidden
|
mapM_ hide (nub oldvisible \\ visible)
|
||||||
mapM_ hide . concatMap (W.integrate . W.stack) $
|
|
||||||
intersectBy (\w x -> W.tag w == W.tag x)
|
|
||||||
(map W.workspace $ W.current old : W.visible old)
|
|
||||||
(W.hidden ws)
|
|
||||||
|
|
||||||
clearEnterEvents
|
clearEnterEvents
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user