mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Determine numlockMask automatically, fixes #120
This commit is contained in:
parent
a2ba4d8a6c
commit
d5d8d551e6
@ -25,11 +25,11 @@ module XMonad.Config (defaultConfig) where
|
||||
-- Useful imports
|
||||
--
|
||||
import XMonad.Core as XMonad hiding
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||
,handleEventHook)
|
||||
import qualified XMonad.Core as XMonad
|
||||
(workspaces,manageHook,numlockMask,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||
,handleEventHook)
|
||||
|
||||
@ -64,22 +64,6 @@ workspaces = map show [1 .. 9 :: Int]
|
||||
defaultModMask :: KeyMask
|
||||
defaultModMask = mod1Mask
|
||||
|
||||
-- | The mask for the numlock key. Numlock status is "masked" from the
|
||||
-- current modifier status, so the keybindings will work with numlock on or
|
||||
-- off. You may need to change this on some systems.
|
||||
--
|
||||
-- You can find the numlock modifier by running "xmodmap" and looking for a
|
||||
-- modifier with Num_Lock bound to it:
|
||||
--
|
||||
-- > $ xmodmap | grep Num
|
||||
-- > mod2 Num_Lock (0x4d)
|
||||
--
|
||||
-- Set numlockMask = 0 if you don't have a numlock key, or want to treat
|
||||
-- numlock status separately.
|
||||
--
|
||||
numlockMask :: KeyMask
|
||||
numlockMask = mod2Mask
|
||||
|
||||
-- | Width of the window border in pixels.
|
||||
--
|
||||
borderWidth :: Dimension
|
||||
@ -256,7 +240,6 @@ defaultConfig = XConfig
|
||||
, XMonad.terminal = terminal
|
||||
, XMonad.normalBorderColor = normalBorderColor
|
||||
, XMonad.focusedBorderColor = focusedBorderColor
|
||||
, XMonad.numlockMask = numlockMask
|
||||
, XMonad.modMask = defaultModMask
|
||||
, XMonad.keys = keys
|
||||
, XMonad.logHook = logHook
|
||||
|
@ -64,12 +64,14 @@ data XState = XState
|
||||
, mapped :: !(S.Set Window) -- ^ the Set of mapped windows
|
||||
, waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents
|
||||
, dragging :: !(Maybe (Position -> Position -> X (), X ()))
|
||||
, numlockMask :: !KeyMask -- ^ The numlock modifier
|
||||
, extensibleState :: !(M.Map String (Either String StateExtension))
|
||||
-- ^ stores custom state information.
|
||||
--
|
||||
-- The module XMonad.Utils.ExtensibleState in xmonad-contrib
|
||||
-- provides additional information and a simple interface for using this.
|
||||
}
|
||||
|
||||
-- | XConf, the (read-only) window manager configuration.
|
||||
data XConf = XConf
|
||||
{ display :: Display -- ^ the X11 display
|
||||
@ -98,7 +100,6 @@ data XConfig l = XConfig
|
||||
-- should also be run afterwards. mappend should be used for combining
|
||||
-- event hooks in most cases.
|
||||
, workspaces :: ![String] -- ^ The list of workspaces' names
|
||||
, numlockMask :: !KeyMask -- ^ The numlock modifier
|
||||
, modMask :: !KeyMask -- ^ the mod modifier
|
||||
, keys :: !(XConfig Layout -> M.Map (ButtonMask,KeySym) (X ()))
|
||||
-- ^ The key binding: a map from key presses and actions
|
||||
|
@ -121,6 +121,7 @@ xmonad initxmc = do
|
||||
|
||||
st = XState
|
||||
{ windowset = initialWinset
|
||||
, numlockMask = 0
|
||||
, mapped = S.empty
|
||||
, waitingUnmap = M.empty
|
||||
, dragging = Nothing
|
||||
@ -129,6 +130,7 @@ xmonad initxmc = do
|
||||
allocaXEvent $ \e ->
|
||||
runX cf st $ do
|
||||
|
||||
setNumlockMask
|
||||
grabKeys
|
||||
grabButtons
|
||||
|
||||
@ -218,7 +220,9 @@ handle (UnmapEvent {ev_window = w, ev_send_event = synthetic}) = whenX (isClient
|
||||
-- set keyboard mapping
|
||||
handle e@(MappingNotifyEvent {}) = do
|
||||
io $ refreshKeyboardMapping e
|
||||
when (ev_request e == mappingKeyboard) grabKeys
|
||||
when (ev_request e `elem` [mappingKeyboard, mappingModifier]) $ do
|
||||
setNumlockMask
|
||||
grabKeys
|
||||
|
||||
-- handle button release, which may finish dragging.
|
||||
handle e@(ButtonEvent {ev_event_type = t})
|
||||
@ -324,6 +328,18 @@ scan dpy rootw = do
|
||||
return $ not (wa_override_redirect wa)
|
||||
&& (wa_map_state wa == waIsViewable || ic)
|
||||
|
||||
setNumlockMask :: X ()
|
||||
setNumlockMask = do
|
||||
dpy <- asks display
|
||||
ms <- io $ getModifierMapping dpy
|
||||
xs <- sequence [ do
|
||||
ks <- io $ keycodeToKeysym dpy kc 0
|
||||
if ks == xK_Num_Lock
|
||||
then return (setBit 0 (fromIntegral m))
|
||||
else return (0 :: KeyMask)
|
||||
| (m, kcs) <- ms, kc <- kcs, kc /= 0]
|
||||
modify (\s -> s { numlockMask = foldr (.|.) 0 xs })
|
||||
|
||||
-- | Grab the keys back
|
||||
grabKeys :: X ()
|
||||
grabKeys = do
|
||||
|
@ -389,13 +389,13 @@ isClient w = withWindowSet $ return . W.member w
|
||||
-- (numlock and capslock)
|
||||
extraModifiers :: X [KeyMask]
|
||||
extraModifiers = do
|
||||
nlm <- asks (numlockMask . config)
|
||||
nlm <- gets numlockMask
|
||||
return [0, nlm, lockMask, nlm .|. lockMask ]
|
||||
|
||||
-- | Strip numlock\/capslock from a mask
|
||||
cleanMask :: KeyMask -> X KeyMask
|
||||
cleanMask km = do
|
||||
nlm <- asks (numlockMask . config)
|
||||
nlm <- gets numlockMask
|
||||
return (complement (nlm .|. lockMask) .&. km)
|
||||
|
||||
-- | Get the 'Pixel' value for a named color
|
||||
|
@ -34,21 +34,6 @@ myBorderWidth = 1
|
||||
--
|
||||
myModMask = mod1Mask
|
||||
|
||||
-- The mask for the numlock key. Numlock status is "masked" from the
|
||||
-- current modifier status, so the keybindings will work with numlock on or
|
||||
-- off. You may need to change this on some systems.
|
||||
--
|
||||
-- You can find the numlock modifier by running "xmodmap" and looking for a
|
||||
-- modifier with Num_Lock bound to it:
|
||||
--
|
||||
-- > $ xmodmap | grep Num
|
||||
-- > mod2 Num_Lock (0x4d)
|
||||
--
|
||||
-- Set numlockMask = 0 if you don't have a numlock key, or want to treat
|
||||
-- numlock status separately.
|
||||
--
|
||||
myNumlockMask = mod2Mask
|
||||
|
||||
-- The default number of workspaces (virtual screens) and their names.
|
||||
-- By default we use numeric strings, but any string may be used as a
|
||||
-- workspace name. The number of workspaces is determined by the length
|
||||
@ -272,7 +257,6 @@ defaults = defaultConfig {
|
||||
focusFollowsMouse = myFocusFollowsMouse,
|
||||
borderWidth = myBorderWidth,
|
||||
modMask = myModMask,
|
||||
numlockMask = myNumlockMask,
|
||||
workspaces = myWorkspaces,
|
||||
normalBorderColor = myNormalBorderColor,
|
||||
focusedBorderColor = myFocusedBorderColor,
|
||||
|
Loading…
x
Reference in New Issue
Block a user