aboutsummaryrefslogtreecommitdiffstats
path: root/Operations.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-10-01 18:46:27 +0200
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-10-01 18:46:27 +0200
commit3f3d11efe8c1b5b3577169450d703c0ca6e6d58e (patch)
treeaf00ef4ba8c6f9fd4021f93747fd9929eaf32e1e /Operations.hs
parentc5906882f03a5a01e3458e0fdd20e5f426d696bc (diff)
downloadxmonad-3f3d11efe8c1b5b3577169450d703c0ca6e6d58e.tar.gz
xmonad-3f3d11efe8c1b5b3577169450d703c0ca6e6d58e.tar.xz
xmonad-3f3d11efe8c1b5b3577169450d703c0ca6e6d58e.zip
First cut at manageHook
darcs-hash:20071001164627-a5988-bf9560048dd0abaf2298a1eb5c0e1fc7e9654c16.gz
Diffstat (limited to 'Operations.hs')
-rw-r--r--Operations.hs10
1 files changed, 5 insertions, 5 deletions
diff --git a/Operations.hs b/Operations.hs
index ee58161..3e447be 100644
--- a/Operations.hs
+++ b/Operations.hs
@@ -20,7 +20,7 @@ module Operations where
import XMonad
import qualified StackSet as W
-import {-# SOURCE #-} Config (borderWidth,logHook,numlockMask,possibleLayouts)
+import {-# SOURCE #-} Config (borderWidth,logHook,manageHook,numlockMask,possibleLayouts)
import Data.Maybe
import Data.List (nub, (\\), find, partition)
@@ -49,8 +49,6 @@ import Graphics.X11.Xlib.Extras
--
manage :: Window -> X ()
manage w = whenX (fmap not $ isClient w) $ withDisplay $ \d -> do
- setInitialProperties w
-
sh <- io $ getWMNormalHints d w
let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
@@ -62,10 +60,11 @@ manage w = whenX (fmap not $ isClient w) $ withDisplay $ \d -> do
= W.RationalRect (0.5 - wid/2) (0.5 - h/2) wid h
adjust r = r
- let f ws | isFixedSize || isTransient = W.float w (adjust rr) . W.insertUp w . W.view i $ ws
+ f ws | isFixedSize || isTransient = W.float w (adjust rr) . W.insertUp w . W.view i $ ws
| otherwise = W.insertUp w ws
where i = fromMaybe (W.tag . W.workspace . W.current $ ws) $ W.lookupWorkspace sc ws
- windows f
+ g <- manageHook w
+ windows (g . f)
-- | unmanage. A window no longer exists, remove it from the window
-- list, on whatever workspace it is.
@@ -119,6 +118,7 @@ windows f = do
let oldvisible = concatMap (W.integrate' . W.stack . W.workspace) $ W.current old : W.visible old
ws = f old
XConf { display = d , normalBorder = nbc, focusedBorder = fbc } <- ask
+ mapM_ setInitialProperties (W.allWindows ws \\ W.allWindows old)
whenJust (W.peek old) $ \otherw -> io $ setWindowBorder d otherw nbc
modify (\s -> s { windowset = ws })