From 109b7e0d38bc3ab3781c78882db35e182a489e7f Mon Sep 17 00:00:00 2001
From: Spencer Janssen <sjanssen@cse.unl.edu>
Date: Thu, 1 Nov 2007 09:00:45 +0100
Subject: Delete Main.hs-boot!

darcs-hash:20071101080045-a5988-d3b50a7fe35ff4e38c90e9eb8da1f1963b3b27fd.gz
---
 EventLoop.hs  | 11 +++++++----
 Main.hs       |  5 +++--
 Main.hs-boot  |  4 ----
 Operations.hs | 14 ++++++++------
 XMonad.hs     |  1 +
 5 files changed, 19 insertions(+), 16 deletions(-)
 delete mode 100644 Main.hs-boot

diff --git a/EventLoop.hs b/EventLoop.hs
index b01036a..9866287 100644
--- a/EventLoop.hs
+++ b/EventLoop.hs
@@ -124,7 +124,8 @@ makeMain xmc = do
             handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
                 | t == keyPress = withDisplay $ \dpy -> do
                     s  <- io $ keycodeToKeysym dpy code 0
-                    userCode $ whenJust (M.lookup (cleanMask m,s) (keys xmc)) id
+                    mClean <- cleanMask m
+                    userCode $ whenJust (M.lookup (mClean, s) (keys xmc)) id
 
             -- manage a new window
             handle (MapRequestEvent    {ev_window = w}) = withDisplay $ \dpy -> do
@@ -172,7 +173,8 @@ makeMain xmc = do
                 -- If it's the root window, then it's something we
                 -- grabbed in grabButtons. Otherwise, it's click-to-focus.
                 isr <- isRoot w
-                if isr then userCode $ whenJust (M.lookup (cleanMask (ev_state e), b) $ mouseBindings xmc) ($ ev_subwindow e)
+                m <- cleanMask $ ev_state e
+                if isr then userCode $ whenJust (M.lookup (m, b) $ mouseBindings xmc) ($ ev_subwindow e)
                        else focus w
                 sendMessage e -- Always send button events.
 
@@ -252,7 +254,7 @@ grabKeys xmc = do
          kc <- io $ keysymToKeycode dpy sym
          -- "If the specified KeySym is not defined for any KeyCode,
          -- XKeysymToKeycode() returns zero."
-         when (kc /= '\0') $ mapM_ (grab kc . (mask .|.)) extraModifiers
+         when (kc /= '\0') $ mapM_ (grab kc . (mask .|.)) =<< extraModifiers
 
 -- | XXX comment me
 grabButtons :: XConfig -> X ()
@@ -261,4 +263,5 @@ grabButtons xmc = do
     let grab button mask = io $ grabButton dpy button mask rootw False buttonPressMask
                                            grabModeAsync grabModeSync none none
     io $ ungrabButton dpy anyButton anyModifier rootw
-    mapM_ (\(m,b) -> mapM_ (grab b . (m .|.)) extraModifiers) (M.keys $ mouseBindings xmc)
+    ems <- extraModifiers
+    mapM_ (\(m,b) -> mapM_ (grab b . (m .|.)) ems) (M.keys $ mouseBindings xmc)
diff --git a/Main.hs b/Main.hs
index 2531b59..e228ee4 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, manageHook)
-import qualified XMonad (workspaces, manageHook)
+import XMonad hiding (workspaces, manageHook, numlockMask)
+import qualified XMonad (workspaces, manageHook, numlockMask)
 import Layouts
 import Operations
 import qualified StackSet as W
@@ -244,6 +244,7 @@ defaultConfig = XConfig { borderWidth = 1 -- Width of the window border in pixel
                         , terminal = "xterm" -- The preferred terminal program.
                         , normalBorderColor = "#dddddd" -- Border color for unfocused windows.
                         , focusedBorderColor = "#ff0000" -- Border color for focused windows.
+                        , XMonad.numlockMask = numlockMask
                         , XMonad.keys = Main.keys
                         , XMonad.mouseBindings = Main.mouseBindings
                         -- | Perform an arbitrary action on each internal state change or X event.
diff --git a/Main.hs-boot b/Main.hs-boot
deleted file mode 100644
index ce39bce..0000000
--- a/Main.hs-boot
+++ /dev/null
@@ -1,4 +0,0 @@
-module Main where
-import Graphics.X11.Xlib (KeyMask,Window)
-import XMonad
-numlockMask :: KeyMask
diff --git a/Operations.hs b/Operations.hs
index f3fa64f..ae6d8e1 100644
--- a/Operations.hs
+++ b/Operations.hs
@@ -37,8 +37,6 @@ import Graphics.X11.Xlib
 import Graphics.X11.Xinerama (getScreenInfo)
 import Graphics.X11.Xlib.Extras
 
-import {-# SOURCE #-} Main (numlockMask)
-
 -- ---------------------------------------------------------------------
 -- |
 -- Window manager operations
@@ -367,12 +365,16 @@ isClient w = withWindowSet $ return . W.member w
 
 -- | Combinations of extra modifier masks we need to grab keys\/buttons for.
 -- (numlock and capslock)
-extraModifiers :: [KeyMask]
-extraModifiers = [0, numlockMask, lockMask, numlockMask .|. lockMask ]
+extraModifiers :: X [KeyMask]
+extraModifiers = do
+    nlm <- asks (numlockMask . config)
+    return [0, nlm, lockMask, nlm .|. lockMask ]
 
 -- | Strip numlock\/capslock from a mask
-cleanMask :: KeyMask -> KeyMask
-cleanMask = (complement (numlockMask .|. lockMask) .&.)
+cleanMask :: KeyMask -> X KeyMask
+cleanMask km = do
+    nlm <- asks (numlockMask . config)
+    return (complement (nlm .|. lockMask) .&. km)
 
 -- | Get the Pixel value for a named color
 initColor :: Display -> String -> IO Pixel
diff --git a/XMonad.hs b/XMonad.hs
index 5fac5cb..6fcf6c1 100644
--- a/XMonad.hs
+++ b/XMonad.hs
@@ -63,6 +63,7 @@ data XConfig = forall l. (LayoutClass l Window, Read (l Window)) =>
                                      , manageHook :: Window -> String -> String -> String -> X (WindowSet -> WindowSet)
                                      , workspaces :: ![String]
                                      , defaultGaps :: ![(Int,Int,Int,Int)]
+                                     , numlockMask :: KeyMask
                                      , keys :: !(M.Map (ButtonMask,KeySym) (X ()))
                                      , mouseBindings :: !(M.Map (ButtonMask, Button) (Window -> X ()))
                                      , borderWidth :: !Dimension
-- 
cgit v1.2.3