From 9b93fc161e659b7d3d478e1b5a9a711a31968967 Mon Sep 17 00:00:00 2001 From: Spencer Janssen Date: Thu, 1 Nov 2007 08:53:08 +0100 Subject: Remove manageHook from Main.hs-boot darcs-hash:20071101075308-a5988-26cbe1f6f89a90f2e81b34f76c7e56030e5c2c11.gz --- Main.hs | 5 +++-- Main.hs-boot | 1 - Operations.hs | 5 +++-- XMonad.hs | 1 + 4 files changed, 7 insertions(+), 5 deletions(-) diff --git a/Main.hs b/Main.hs index b249431..2531b59 100644 --- a/Main.hs +++ b/Main.hs @@ -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 diff --git a/Main.hs-boot b/Main.hs-boot index 47821a9..ce39bce 100644 --- a/Main.hs-boot +++ b/Main.hs-boot @@ -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) diff --git a/Operations.hs b/Operations.hs index d2b6844..f3fa64f 100644 --- a/Operations.hs +++ b/Operations.hs @@ -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 diff --git a/XMonad.hs b/XMonad.hs index e21b726..5fac5cb 100644 --- a/XMonad.hs +++ b/XMonad.hs @@ -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 ())) -- cgit v1.2.3