mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-01 04:31:53 -07:00
Merge pull request #221 from liskin/float-dimensions
Use current screen to set dimensions of new floating windows
This commit is contained in:
@@ -2,6 +2,10 @@
|
|||||||
|
|
||||||
## unknown (unknown)
|
## unknown (unknown)
|
||||||
|
|
||||||
|
* Fixed a bug when using multiple screens with different dimensions,
|
||||||
|
causing some floating windows to be smaller/larger than the size they
|
||||||
|
requested.
|
||||||
|
|
||||||
## 0.15 (September 30, 2018)
|
## 0.15 (September 30, 2018)
|
||||||
|
|
||||||
* Reimplement `sendMessage` to deal properly with windowset changes made
|
* Reimplement `sendMessage` to deal properly with windowset changes made
|
||||||
|
@@ -24,6 +24,7 @@ import Data.Maybe
|
|||||||
import Data.Monoid (Endo(..),Any(..))
|
import Data.Monoid (Endo(..),Any(..))
|
||||||
import Data.List (nub, (\\), find)
|
import Data.List (nub, (\\), find)
|
||||||
import Data.Bits ((.|.), (.&.), complement, testBit)
|
import Data.Bits ((.|.), (.&.), complement, testBit)
|
||||||
|
import Data.Function (on)
|
||||||
import Data.Ratio
|
import Data.Ratio
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
@@ -565,13 +566,25 @@ floatLocation w =
|
|||||||
ws <- gets windowset
|
ws <- gets windowset
|
||||||
wa <- io $ getWindowAttributes d w
|
wa <- io $ getWindowAttributes d w
|
||||||
let bw = (fromIntegral . wa_border_width) wa
|
let bw = (fromIntegral . wa_border_width) wa
|
||||||
sc <- fromMaybe (W.current ws) <$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
|
point_sc <- pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
|
||||||
|
managed <- isClient w
|
||||||
|
|
||||||
let sr = screenRect . W.screenDetail $ sc
|
-- ignore pointScreen for new windows unless it's the current
|
||||||
rr = W.RationalRect ((fi (wa_x wa) - fi (rect_x sr)) % fi (rect_width sr))
|
-- screen, otherwise the float's relative size is computed against
|
||||||
((fi (wa_y wa) - fi (rect_y sr)) % fi (rect_height sr))
|
-- a different screen and the float ends up with the wrong size
|
||||||
(fi (wa_width wa + bw*2) % fi (rect_width sr))
|
let sr_eq = (==) `on` fmap (screenRect . W.screenDetail)
|
||||||
(fi (wa_height wa + bw*2) % fi (rect_height sr))
|
sc = fromMaybe (W.current ws) $
|
||||||
|
if managed || point_sc `sr_eq` Just (W.current ws) then point_sc else Nothing
|
||||||
|
sr = screenRect . W.screenDetail $ sc
|
||||||
|
x = (fi (wa_x wa) - fi (rect_x sr)) % fi (rect_width sr)
|
||||||
|
y = (fi (wa_y wa) - fi (rect_y sr)) % fi (rect_height sr)
|
||||||
|
width = fi (wa_width wa + bw*2) % fi (rect_width sr)
|
||||||
|
height = fi (wa_height wa + bw*2) % fi (rect_height sr)
|
||||||
|
-- adjust x/y of unmanaged windows if we ignored or didn't get pointScreen,
|
||||||
|
-- it might be out of bounds otherwise
|
||||||
|
rr = if managed || point_sc `sr_eq` Just sc
|
||||||
|
then W.RationalRect x y width height
|
||||||
|
else W.RationalRect (0.5 - width/2) (0.5 - height/2) width height
|
||||||
|
|
||||||
return (W.screen sc, rr)
|
return (W.screen sc, rr)
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user