mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Factor our common logic for floating windows
Factour out the code used to detect whether a window should be floating in Operations.hs in a new function named isFixedSizeOrTransient Modify willFloat to use the factored out code from Opeartions.hs
This commit is contained in:
parent
b6af6bb86a
commit
c2e632a2b9
@ -27,7 +27,7 @@ import Control.Monad.Reader
|
||||
import Data.Maybe
|
||||
import Data.Monoid
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Operations (floatLocation, reveal)
|
||||
import XMonad.Operations (floatLocation, reveal, isFixedSizeOrTransient)
|
||||
|
||||
-- | Lift an 'X' action to a 'Query'.
|
||||
liftX :: X a -> Query a
|
||||
@ -108,11 +108,7 @@ getStringProperty d w p = do
|
||||
|
||||
-- | Return whether the window will be a floating window or not
|
||||
willFloat :: Query Bool
|
||||
willFloat = ask >>= \w -> liftX $ withDisplay $ \d -> do
|
||||
sh <- io $ getWMNormalHints d w
|
||||
let isFixedSize = isJust (sh_min_size sh) && sh_min_size sh == sh_max_size sh
|
||||
isTransient <- isJust <$> io (getTransientForHint d w)
|
||||
return (isFixedSize || isTransient)
|
||||
willFloat = ask >>= \w -> liftX $ withDisplay $ \d -> isFixedSizeOrTransient d w
|
||||
|
||||
-- | Modify the 'WindowSet' with a pure function.
|
||||
doF :: (s -> s) -> Query (Endo s)
|
||||
|
@ -18,7 +18,7 @@ module XMonad.Operations (
|
||||
manage, unmanage, killWindow, kill, isClient,
|
||||
setInitialProperties, setWMState, setWindowBorderWithFallback,
|
||||
hide, reveal, tileWindow,
|
||||
setTopFocus, focus,
|
||||
setTopFocus, focus, isFixedSizeOrTransient,
|
||||
|
||||
-- * Manage Windows
|
||||
windows, refresh, rescreen, modifyWindowSet, windowBracket, windowBracket_, clearEvents, getCleanedScreenInfo,
|
||||
@ -78,6 +78,16 @@ import Graphics.X11.Xlib.Extras
|
||||
-- ---------------------------------------------------------------------
|
||||
-- Window manager operations
|
||||
|
||||
-- | Detect whether a window has fixed size or is transient. This check
|
||||
-- can be used to determine whether the window should be floating or not
|
||||
--
|
||||
isFixedSizeOrTransient :: Display -> Window -> X Bool
|
||||
isFixedSizeOrTransient d w = do
|
||||
sh <- io $ getWMNormalHints d w
|
||||
let isFixedSize = isJust (sh_min_size sh) && sh_min_size sh == sh_max_size sh
|
||||
isTransient <- isJust <$> io (getTransientForHint d w)
|
||||
return (isFixedSize || isTransient)
|
||||
|
||||
-- |
|
||||
-- Add a new window to be managed in the current workspace.
|
||||
-- Bring it into focus.
|
||||
@ -87,10 +97,8 @@ import Graphics.X11.Xlib.Extras
|
||||
--
|
||||
manage :: Window -> X ()
|
||||
manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
|
||||
sh <- io $ getWMNormalHints d w
|
||||
|
||||
let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
|
||||
isTransient <- isJust <$> io (getTransientForHint d w)
|
||||
shouldFloat <- isFixedSizeOrTransient d w
|
||||
|
||||
rr <- snd `fmap` floatLocation w
|
||||
-- ensure that float windows don't go over the edge of the screen
|
||||
@ -98,7 +106,7 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
|
||||
= W.RationalRect (0.5 - wid/2) (0.5 - h/2) wid h
|
||||
adjust r = r
|
||||
|
||||
f ws | isFixedSize || isTransient = W.float w (adjust rr) . W.insertUp w . W.view i $ ws
|
||||
f ws | shouldFloat = W.float w (adjust rr) . W.insertUp w . W.view i $ ws
|
||||
| otherwise = W.insertUp w ws
|
||||
where i = W.tag $ W.workspace $ W.current ws
|
||||
|
||||
|
Loading…
x
Reference in New Issue
Block a user