mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-02 05:01:53 -07:00
Rename withWorkspace to withWindowSet.
This commit is contained in:
@@ -252,13 +252,13 @@ setButtonGrab grab w = withDisplay $ \d -> io $ do
|
|||||||
|
|
||||||
-- | Set the focus to the window on top of the stack, or root
|
-- | Set the focus to the window on top of the stack, or root
|
||||||
setTopFocus :: X ()
|
setTopFocus :: X ()
|
||||||
setTopFocus = withWorkspace $ maybe (setFocusX =<< asks theRoot) setFocusX . W.peek
|
setTopFocus = withWindowSet $ maybe (setFocusX =<< asks theRoot) setFocusX . W.peek
|
||||||
|
|
||||||
-- | Set focus explicitly to window 'w' if it is managed by us, or root.
|
-- | Set focus explicitly to window 'w' if it is managed by us, or root.
|
||||||
-- This happens if X notices we've moved the mouse (and perhaps moved
|
-- This happens if X notices we've moved the mouse (and perhaps moved
|
||||||
-- the mouse to a new screen).
|
-- the mouse to a new screen).
|
||||||
focus :: Window -> X ()
|
focus :: Window -> X ()
|
||||||
focus w = withWorkspace $ \s -> do
|
focus w = withWindowSet $ \s -> do
|
||||||
if W.member w s then modify (\st -> st { windowset = W.focusWindow w s }) >> setFocusX w -- >> refresh
|
if W.member w s then modify (\st -> st { windowset = W.focusWindow w s }) >> setFocusX w -- >> refresh
|
||||||
else whenX (isRoot w) $ setFocusX w -- we could refresh here, moving gap too.
|
else whenX (isRoot w) $ setFocusX w -- we could refresh here, moving gap too.
|
||||||
-- XXX a focus change could be caused by switching workspaces in xinerama.
|
-- XXX a focus change could be caused by switching workspaces in xinerama.
|
||||||
@@ -269,7 +269,7 @@ focus w = withWorkspace $ \s -> do
|
|||||||
|
|
||||||
-- | Call X to set the keyboard focus details.
|
-- | Call X to set the keyboard focus details.
|
||||||
setFocusX :: Window -> X ()
|
setFocusX :: Window -> X ()
|
||||||
setFocusX w = withWorkspace $ \ws -> do
|
setFocusX w = withWindowSet $ \ws -> do
|
||||||
XConf { display = dpy , normalBorder = nbc, focusedBorder = fbc } <- ask
|
XConf { display = dpy , normalBorder = nbc, focusedBorder = fbc } <- ask
|
||||||
|
|
||||||
-- clear mouse button grab and border on other windows
|
-- clear mouse button grab and border on other windows
|
||||||
@@ -391,15 +391,15 @@ layout f = do
|
|||||||
|
|
||||||
-- | Return workspace visible on screen 'sc', or 0.
|
-- | Return workspace visible on screen 'sc', or 0.
|
||||||
screenWorkspace :: ScreenId -> X WorkspaceId
|
screenWorkspace :: ScreenId -> X WorkspaceId
|
||||||
screenWorkspace sc = withWorkspace $ return . fromMaybe 0 . W.lookupWorkspace sc
|
screenWorkspace sc = withWindowSet $ return . fromMaybe 0 . W.lookupWorkspace sc
|
||||||
|
|
||||||
-- | Apply an X operation to the currently focused window, if there is one.
|
-- | Apply an X operation to the currently focused window, if there is one.
|
||||||
withFocused :: (Window -> X ()) -> X ()
|
withFocused :: (Window -> X ()) -> X ()
|
||||||
withFocused f = withWorkspace $ \w -> whenJust (W.peek w) f
|
withFocused f = withWindowSet $ \w -> whenJust (W.peek w) f
|
||||||
|
|
||||||
-- | True if window is under management by us
|
-- | True if window is under management by us
|
||||||
isClient :: Window -> X Bool
|
isClient :: Window -> X Bool
|
||||||
isClient w = withWorkspace $ return . W.member w
|
isClient w = withWindowSet $ return . W.member w
|
||||||
|
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
-- | Floating layer support
|
-- | Floating layer support
|
||||||
|
@@ -18,7 +18,7 @@
|
|||||||
module XMonad (
|
module XMonad (
|
||||||
X, WindowSet, WorkspaceId(..), ScreenId(..), XState(..), XConf(..), Layout(..),
|
X, WindowSet, WorkspaceId(..), ScreenId(..), XState(..), XConf(..), Layout(..),
|
||||||
Typeable, Message, SomeMessage(..), fromMessage,
|
Typeable, Message, SomeMessage(..), fromMessage,
|
||||||
runX, io, withDisplay, withWorkspace, isRoot, spawn, restart, trace, whenJust, whenX
|
runX, io, withDisplay, withWindowSet, isRoot, spawn, restart, trace, whenJust, whenX
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import StackSet (StackSet)
|
import StackSet (StackSet)
|
||||||
@@ -84,9 +84,9 @@ runX c st (X a) = runStateT (runReaderT a c) st >> return ()
|
|||||||
withDisplay :: (Display -> X a) -> X a
|
withDisplay :: (Display -> X a) -> X a
|
||||||
withDisplay f = asks display >>= f
|
withDisplay f = asks display >>= f
|
||||||
|
|
||||||
-- | Run a monadic action with the current workspace
|
-- | Run a monadic action with the current stack set
|
||||||
withWorkspace :: (WindowSet -> X a) -> X a
|
withWindowSet :: (WindowSet -> X a) -> X a
|
||||||
withWorkspace f = gets windowset >>= f
|
withWindowSet f = gets windowset >>= f
|
||||||
|
|
||||||
-- | True if the given window is the root window
|
-- | True if the given window is the root window
|
||||||
isRoot :: Window -> X Bool
|
isRoot :: Window -> X Bool
|
||||||
|
Reference in New Issue
Block a user