mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 00:20:22 -07:00
Delete Main.hs-boot!
This commit is contained in:
parent
b0b43050f4
commit
22aacf9bf6
11
EventLoop.hs
11
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)
|
||||
|
5
Main.hs
5
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.
|
||||
|
@ -1,4 +0,0 @@
|
||||
module Main where
|
||||
import Graphics.X11.Xlib (KeyMask,Window)
|
||||
import XMonad
|
||||
numlockMask :: KeyMask
|
@ -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
|
||||
|
@ -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
|
||||
|
Loading…
x
Reference in New Issue
Block a user