summaryrefslogtreecommitdiffstats
path: root/XMonad/Operations.hs
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Operations.hs')
-rw-r--r--XMonad/Operations.hs38
1 files changed, 8 insertions, 30 deletions
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index c005335..c82cb2f 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -49,25 +49,10 @@ import Graphics.X11.Xlib.Extras
-- border set, and its event mask set.
--
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)
-
- rr <- snd `fmap` floatLocation w
- -- ensure that float windows don't go over the edge of the screen
- let adjust (W.RationalRect x y wid h) | x + wid > 1 || y + h > 1 || x < 0 || y < 0
- = 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
- | otherwise = W.insertUp w ws
- where i = W.tag $ W.screenWorkspace $ W.current ws
-
+manage w = whenX (not <$> isClient w) $ do
mh <- asks (manageHook . config)
g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
- windows (g . f)
+ windows (g . W.insertUp w)
-- | unmanage. A window no longer exists, remove it from the window
-- list, on whatever workspace it is.
@@ -127,7 +112,6 @@ windows f = do
this = W.view n ws
n = W.tag wsp
tiled = (W.stack . W.screenWorkspace . W.current $ this)
- >>= W.filter (`M.notMember` W.floating ws)
>>= W.filter (`notElem` vis)
viewrect = screenRect $ W.screenDetail w
@@ -137,15 +121,9 @@ windows f = do
runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
updateLayout n ml'
- let m = W.floating ws
- flt = [(fw, scaleRationalRect viewrect r)
- | fw <- filter (flip M.member m) (W.index this)
- , Just r <- [M.lookup fw m]]
- vs = flt ++ rs
-
- io $ restackWindows d (map fst vs)
+ io $ restackWindows d (map fst rs)
-- return the visible windows for this workspace:
- return vs
+ return rs
let visible = map fst rects
@@ -470,7 +448,7 @@ pointWithin x y r = x >= rect_x r &&
y < rect_y r + fromIntegral (rect_height r)
-- | Make a tiled window floating, using its suggested rectangle
-float :: Window -> X ()
+{-float :: Window -> X ()
float w = do
(sc, rr) <- floatLocation w
windows $ \ws -> W.float w rr . fromMaybe ws $ do
@@ -478,7 +456,7 @@ float w = do
guard $ i `elem` concatMap (map W.tag . W.screenWorkspaces) (W.screens ws)
f <- W.peek ws
sw <- W.lookupWorkspace sc ws
- return (W.focusWindow f . W.shiftWin sw w $ ws)
+ return (W.focusWindow f . W.shiftWin sw w $ ws)-}
-- ---------------------------------------------------------------------
-- Mouse handling
@@ -504,7 +482,7 @@ mouseDrag f done = do
return z
-- | XXX comment me
-mouseMoveWindow :: Window -> X ()
+{-mouseMoveWindow :: Window -> X ()
mouseMoveWindow w = whenX (isClient w) $ withDisplay $ \d -> do
io $ raiseWindow d w
wa <- io $ getWindowAttributes d w
@@ -526,7 +504,7 @@ mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
io $ resizeWindow d w `uncurry`
applySizeHintsContents sh (ex - fromIntegral (wa_x wa),
ey - fromIntegral (wa_y wa)))
- (float w)
+ (float w)-}
-- ---------------------------------------------------------------------
-- | Support for window size hints