Remove manageHook from Main.hs-boot

This commit is contained in:
Spencer Janssen 2007-11-01 07:53:08 +00:00
parent 23035e944b
commit b0b43050f4
4 changed files with 7 additions and 5 deletions

View File

@ -20,8 +20,8 @@ module Main where
-- Useful imports
--
import Control.Monad.Reader ( asks )
import XMonad hiding (workspaces)
import qualified XMonad (workspaces)
import XMonad hiding (workspaces, manageHook)
import qualified XMonad (workspaces, manageHook)
import Layouts
import Operations
import qualified StackSet as W
@ -253,6 +253,7 @@ defaultConfig = XConfig { borderWidth = 1 -- Width of the window border in pixel
--
-- See the 'DynamicLog' extension for examples.
, logHook = return ()
, XMonad.manageHook = manageHook
}
-- % The main function

View File

@ -2,4 +2,3 @@ module Main where
import Graphics.X11.Xlib (KeyMask,Window)
import XMonad
numlockMask :: KeyMask
manageHook :: Window -> String -> String -> String -> X (WindowSet -> WindowSet)

View File

@ -37,7 +37,7 @@ import Graphics.X11.Xlib
import Graphics.X11.Xinerama (getScreenInfo)
import Graphics.X11.Xlib.Extras
import {-# SOURCE #-} Main (manageHook,numlockMask)
import {-# SOURCE #-} Main (numlockMask)
-- ---------------------------------------------------------------------
-- |
@ -67,7 +67,8 @@ manage w = whenX (fmap not $ isClient w) $ withDisplay $ \d -> do
n <- fmap (fromMaybe "") $ io $ fetchName d w
(ClassHint rn rc) <- io $ getClassHint d w
g <- manageHook w n rn rc `catchX` return id
mh <- asks (manageHook . config)
g <- mh w n rn rc `catchX` return id
windows (g . f)
-- | unmanage. A window no longer exists, remove it from the window

View File

@ -60,6 +60,7 @@ data XConfig = forall l. (LayoutClass l Window, Read (l Window)) =>
, focusedBorderColor :: !String
, terminal :: !String
, layoutHook :: !(l Window)
, manageHook :: Window -> String -> String -> String -> X (WindowSet -> WindowSet)
, workspaces :: ![String]
, defaultGaps :: ![(Int,Int,Int,Int)]
, keys :: !(M.Map (ButtonMask,KeySym) (X ()))