summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorDon Stewart <dons@galois.com>2008-03-21 22:41:29 +0100
committerDon Stewart <dons@galois.com>2008-03-21 22:41:29 +0100
commit64665f209a610726ff612c6604a02fa603a3c401 (patch)
treea5c705c2304c8b1685b32d63d5612e8cf35fcaa4 /XMonad
parentbf5fb84b0920581504f3f3a29bcb94f6b153be01 (diff)
downloadmetatile-64665f209a610726ff612c6604a02fa603a3c401.tar
metatile-64665f209a610726ff612c6604a02fa603a3c401.zip
Revert float location patch. Not Xinerama safe
darcs-hash:20080321214129-cba2c-5eeb181514381837404a0cddcc74c78b8b044b67
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/ManageHook.hs2
-rw-r--r--XMonad/Operations.hs16
2 files changed, 9 insertions, 9 deletions
diff --git a/XMonad/ManageHook.hs b/XMonad/ManageHook.hs
index 904b99f..072fe1f 100644
--- a/XMonad/ManageHook.hs
+++ b/XMonad/ManageHook.hs
@@ -71,7 +71,7 @@ doF = return . Endo
-- | Move the window to the floating layer.
doFloat :: ManageHook
-doFloat = ask >>= \w -> doF . W.float w =<< liftX (floatLocation w)
+doFloat = ask >>= \w -> doF . W.float w . snd =<< liftX (floatLocation w)
-- | Map the window and remove it from the 'WindowSet'.
doIgnore :: ManageHook
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index 9d6164b..1953cb3 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -56,7 +56,7 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
isTransient <- isJust <$> io (getTransientForHint d w)
- rr <- floatLocation w
+ (sc, rr) <- 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
@@ -64,7 +64,7 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
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.workspace $ W.current ws
+ where i = fromMaybe (W.tag . W.workspace . W.current $ ws) $ W.lookupWorkspace sc ws
mh <- asks (manageHook . config)
g <- fmap appEndo (runQuery mh w) `catchX` return id
@@ -392,7 +392,7 @@ initColor dpy c = C.handle (\_ -> return Nothing) $
-- | Given a window, find the screen it is located on, and compute
-- the geometry of that window wrt. that screen.
-floatLocation :: Window -> X (W.RationalRect)
+floatLocation :: Window -> X (ScreenId, W.RationalRect)
floatLocation w = withDisplay $ \d -> do
ws <- gets windowset
wa <- io $ getWindowAttributes d w
@@ -406,7 +406,7 @@ floatLocation w = withDisplay $ \d -> do
(fi (wa_width wa + bw*2) % fi (rect_width sr))
(fi (wa_height wa + bw*2) % fi (rect_height sr))
- return rr
+ return (W.screen $ sc, rr)
where fi x = fromIntegral x
pointWithin :: Integer -> Integer -> Rectangle -> Bool
pointWithin x y r = x >= fi (rect_x r) &&
@@ -417,12 +417,12 @@ floatLocation w = withDisplay $ \d -> do
-- | Make a tiled window floating, using its suggested rectangle
float :: Window -> X ()
float w = do
- rr <- floatLocation w
+ (sc, rr) <- floatLocation w
windows $ \ws -> W.float w rr . fromMaybe ws $ do
- i <- W.findTag w ws
+ i <- W.findTag w ws
guard $ i `elem` map (W.tag . W.workspace) (W.screens ws)
- f <- W.peek ws
- sw <- W.lookupWorkspace (W.screen $ W.current ws) ws
+ f <- W.peek ws
+ sw <- W.lookupWorkspace sc ws
return (W.focusWindow f . W.shiftWin sw w $ ws)
-- ---------------------------------------------------------------------