summaryrefslogtreecommitdiffstats
path: root/XMonad/Operations.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Operations.hs')
-rw-r--r--XMonad/Operations.hs29
1 files changed, 22 insertions, 7 deletions
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index a88ce06..ad6f8b1 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -29,6 +29,7 @@ import Data.Ratio
import qualified Data.Map as M
import Control.Applicative
+import Control.Arrow ((&&&))
import Control.Monad.Reader
import Control.Monad.State
import qualified Control.Exception.Extensible as C
@@ -91,10 +92,11 @@ windows f = do
let oldvisible = concatMap (W.integrate' . W.stack . W.screenWorkspace) $ W.screens old
newwindows = W.allWindows ws \\ W.allWindows old
ws = f old
- XConf { display = d } <- ask
+ XConf { display = d , normalBorder = nbc, focusedBorder = fbc } <- ask
mapM_ setInitialProperties newwindows
+ whenJust (W.peek old) $ \otherw -> setFrameBackground d otherw nbc
modify (\s -> s { windowset = ws })
-- notify non visibility
@@ -127,6 +129,8 @@ windows f = do
mapM_ (uncurry tileWindow) rects
+ whenJust (W.peek ws) $ \w -> setFrameBackground d w fbc
+
mapM_ reveal visible
setTopFocus
@@ -142,6 +146,13 @@ windows f = do
isMouseFocused <- asks mouseFocused
unless isMouseFocused $ clearEvents enterWindowMask
asks (logHook . config) >>= userCodeDef ()
+ where
+ setFrameBackground :: Display -> Window -> Pixel -> X ()
+ setFrameBackground d w p = do
+ frame <- getsWindowState wsFrame w
+ io $ do
+ setWindowBackground d frame p
+ clearWindow d frame
-- | Produce the actual rectangle from a screen and a ratio on that screen.
scaleRationalRect :: Rectangle -> W.RationalRect -> Rectangle
@@ -178,15 +189,20 @@ reveal w = withDisplay $ \d -> do
setWMState w normalState
io $ mapWindow d w
whenX (isClient w) $ do
- frame <- getsWindowState wsFrame w
+ (frame, bw) <- getsWindowState (wsFrame &&& wsBorderWidth) w
io $ do
mapWindow d frame
(_, x, y, width, height, _, _) <- getGeometry d frame
- moveResizeWindow d w 0 0 width height
+ let least1 n = max 1 n
+ x' = x + (fi $ bwLeft bw)
+ y' = y + (fi $ bwTop bw)
+ width' = least1 (width - bwLeft bw - bwRight bw)
+ height' = least1 (height - bwTop bw - bwBottom bw)
+ moveResizeWindow d w (fi $ bwLeft bw) (fi $ bwTop bw) width' height'
-- send absolute ConfigureNotify
allocaXEvent $ \event -> do
setEventType event configureNotify
- setConfigureEvent event w w (fi x) (fi y) (fi width) (fi height) 0 0 False
+ setConfigureEvent event w w (fi x') (fi y') (fi width') (fi height') 0 0 False
sendEvent d w False structureNotifyMask event
modifyWindowState (\ws -> ws { wsMapped = True }) w
where
@@ -221,10 +237,9 @@ clearEvents mask = withDisplay $ \d -> io $ do
-- rectangle, including its border.
tileWindow :: Window -> Rectangle -> X ()
tileWindow w r = withDisplay $ \d -> do
- let bw = 0
-- give all windows at least 1x1 pixels
- let least x | x <= bw*2 = 1
- | otherwise = x - bw*2
+ let least x | x <= 0 = 1
+ | otherwise = x
frame <- getsWindowState wsFrame w
io $ moveResizeWindow d frame (rect_x r) (rect_y r) (least $ rect_width r) (least $ rect_height r)