mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
updated documentation of Operations.
Added missing documentation for type alias `D`. Moved misplaced documentation. Edited to a consistent style that will play well with Haddock.
This commit is contained in:
parent
f89df98f40
commit
52a5e7ca8c
@ -10,7 +10,7 @@
|
|||||||
-- Stability : unstable
|
-- Stability : unstable
|
||||||
-- Portability : not portable, mtl, posix
|
-- Portability : not portable, mtl, posix
|
||||||
--
|
--
|
||||||
-- Operations.
|
-- Operations. A module for functions that don't cleanly fit anywhere else.
|
||||||
--
|
--
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
@ -42,9 +42,10 @@ import Graphics.X11.Xinerama (getScreenInfo)
|
|||||||
import Graphics.X11.Xlib.Extras
|
import Graphics.X11.Xlib.Extras
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- |
|
|
||||||
-- Window manager operations
|
-- Window manager operations
|
||||||
-- manage. Add a new window to be managed in the current workspace.
|
|
||||||
|
-- |
|
||||||
|
-- Add a new window to be managed in the current workspace.
|
||||||
-- Bring it into focus.
|
-- Bring it into focus.
|
||||||
--
|
--
|
||||||
-- Whether the window is already managed, or not, it is mapped, has its
|
-- Whether the window is already managed, or not, it is mapped, has its
|
||||||
@ -71,7 +72,7 @@ manage w = whenX (not <$> isClient w) $ withDisplay $ \d -> do
|
|||||||
g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
|
g <- appEndo <$> userCodeDef (Endo id) (runQuery mh w)
|
||||||
windows (g . f)
|
windows (g . f)
|
||||||
|
|
||||||
-- | unmanage. A window no longer exists, remove it from the window
|
-- | A window no longer exists; remove it from the window
|
||||||
-- list, on whatever workspace it is.
|
-- list, on whatever workspace it is.
|
||||||
--
|
--
|
||||||
unmanage :: Window -> X ()
|
unmanage :: Window -> X ()
|
||||||
@ -102,7 +103,7 @@ kill = withFocused killWindow
|
|||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Managing windows
|
-- Managing windows
|
||||||
|
|
||||||
-- | windows. Modify the current window list with a pure function, and refresh
|
-- | Modify the current window list with a pure function, and refresh
|
||||||
windows :: (WindowSet -> WindowSet) -> X ()
|
windows :: (WindowSet -> WindowSet) -> X ()
|
||||||
windows f = do
|
windows f = do
|
||||||
XState { windowset = old } <- get
|
XState { windowset = old } <- get
|
||||||
@ -190,8 +191,10 @@ windowBracket p action = withWindowSet $ \old -> do
|
|||||||
windows $ \_ -> new
|
windows $ \_ -> new
|
||||||
return a
|
return a
|
||||||
|
|
||||||
-- | A version of @windowBracket@ that discards the return value, and handles an
|
-- | Perform an @X@ action. If it returns @Any True@, unwind the
|
||||||
-- @X@ action reporting its need for refresh via @Any@.
|
-- changes to the @WindowSet@ and replay them using @windows@. This is
|
||||||
|
-- a version of @windowBracket@ that discards the return value and
|
||||||
|
-- handles an @X@ action that reports its need for refresh via @Any@.
|
||||||
windowBracket_ :: X Any -> X ()
|
windowBracket_ :: X Any -> X ()
|
||||||
windowBracket_ = void . windowBracket getAny
|
windowBracket_ = void . windowBracket getAny
|
||||||
|
|
||||||
@ -201,14 +204,14 @@ scaleRationalRect (Rectangle sx sy sw sh) (W.RationalRect rx ry rw rh)
|
|||||||
= Rectangle (sx + scale sw rx) (sy + scale sh ry) (scale sw rw) (scale sh rh)
|
= Rectangle (sx + scale sw rx) (sy + scale sh ry) (scale sw rw) (scale sh rh)
|
||||||
where scale s r = floor (toRational s * r)
|
where scale s r = floor (toRational s * r)
|
||||||
|
|
||||||
-- | setWMState. set the WM_STATE property
|
-- | Set a window's WM_STATE property.
|
||||||
setWMState :: Window -> Int -> X ()
|
setWMState :: Window -> Int -> X ()
|
||||||
setWMState w v = withDisplay $ \dpy -> do
|
setWMState w v = withDisplay $ \dpy -> do
|
||||||
a <- atom_WM_STATE
|
a <- atom_WM_STATE
|
||||||
io $ changeProperty32 dpy w a a propModeReplace [fromIntegral v, fromIntegral none]
|
io $ changeProperty32 dpy w a a propModeReplace [fromIntegral v, fromIntegral none]
|
||||||
|
|
||||||
-- | Set the border color using the window's color map, if possible,
|
-- | Set the border color using the window's color map, if possible;
|
||||||
-- otherwise fallback to the color in @Pixel@.
|
-- otherwise fall back to the color in @Pixel@.
|
||||||
setWindowBorderWithFallback :: Display -> Window -> String -> Pixel -> X ()
|
setWindowBorderWithFallback :: Display -> Window -> String -> Pixel -> X ()
|
||||||
setWindowBorderWithFallback dpy w color basic = io $
|
setWindowBorderWithFallback dpy w color basic = io $
|
||||||
C.handle fallback $ do
|
C.handle fallback $ do
|
||||||
@ -220,7 +223,7 @@ setWindowBorderWithFallback dpy w color basic = io $
|
|||||||
fallback e = do hPrint stderr e >> hFlush stderr
|
fallback e = do hPrint stderr e >> hFlush stderr
|
||||||
setWindowBorder dpy w basic
|
setWindowBorder dpy w basic
|
||||||
|
|
||||||
-- | hide. Hide a window by unmapping it, and setting Iconified.
|
-- | Hide a window by unmapping it and setting Iconified.
|
||||||
hide :: Window -> X ()
|
hide :: Window -> X ()
|
||||||
hide w = whenX (gets (S.member w . mapped)) $ withDisplay $ \d -> do
|
hide w = whenX (gets (S.member w . mapped)) $ withDisplay $ \d -> do
|
||||||
cMask <- asks $ clientMask . config
|
cMask <- asks $ clientMask . config
|
||||||
@ -233,15 +236,15 @@ hide w = whenX (gets (S.member w . mapped)) $ withDisplay $ \d -> do
|
|||||||
modify (\s -> s { waitingUnmap = M.insertWith (+) w 1 (waitingUnmap s)
|
modify (\s -> s { waitingUnmap = M.insertWith (+) w 1 (waitingUnmap s)
|
||||||
, mapped = S.delete w (mapped s) })
|
, mapped = S.delete w (mapped s) })
|
||||||
|
|
||||||
-- | reveal. Show a window by mapping it and setting Normal
|
-- | Show a window by mapping it and setting Normal.
|
||||||
-- this is harmless if the window was already visible
|
-- This is harmless if the window was already visible.
|
||||||
reveal :: Window -> X ()
|
reveal :: Window -> X ()
|
||||||
reveal w = withDisplay $ \d -> do
|
reveal w = withDisplay $ \d -> do
|
||||||
setWMState w normalState
|
setWMState w normalState
|
||||||
io $ mapWindow d w
|
io $ mapWindow d w
|
||||||
whenX (isClient w) $ modify (\s -> s { mapped = S.insert w (mapped s) })
|
whenX (isClient w) $ modify (\s -> s { mapped = S.insert w (mapped s) })
|
||||||
|
|
||||||
-- | Set some properties when we initially gain control of a window
|
-- | Set some properties when we initially gain control of a window.
|
||||||
setInitialProperties :: Window -> X ()
|
setInitialProperties :: Window -> X ()
|
||||||
setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
|
setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
|
||||||
setWMState w iconicState
|
setWMState w iconicState
|
||||||
@ -252,7 +255,7 @@ setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
|
|||||||
-- required by the border setting in 'windows'
|
-- required by the border setting in 'windows'
|
||||||
io $ setWindowBorder d w nb
|
io $ setWindowBorder d w nb
|
||||||
|
|
||||||
-- | refresh. Render the currently visible workspaces, as determined by
|
-- | Render the currently visible workspaces, as determined by
|
||||||
-- the 'StackSet'. Also, set focus to the focused window.
|
-- the 'StackSet'. Also, set focus to the focused window.
|
||||||
--
|
--
|
||||||
-- This is our 'view' operation (MVC), in that it pretty prints our model
|
-- This is our 'view' operation (MVC), in that it pretty prints our model
|
||||||
@ -261,7 +264,7 @@ setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
|
|||||||
refresh :: X ()
|
refresh :: X ()
|
||||||
refresh = windows id
|
refresh = windows id
|
||||||
|
|
||||||
-- | clearEvents. Remove all events of a given type from the event queue.
|
-- | Remove all events of a given type from the event queue.
|
||||||
clearEvents :: EventMask -> X ()
|
clearEvents :: EventMask -> X ()
|
||||||
clearEvents mask = withDisplay $ \d -> io $ do
|
clearEvents mask = withDisplay $ \d -> io $ do
|
||||||
sync d False
|
sync d False
|
||||||
@ -269,8 +272,8 @@ clearEvents mask = withDisplay $ \d -> io $ do
|
|||||||
more <- checkMaskEvent d mask p
|
more <- checkMaskEvent d mask p
|
||||||
when more again -- beautiful
|
when more again -- beautiful
|
||||||
|
|
||||||
-- | tileWindow. Moves and resizes w such that it fits inside the given
|
-- | Move and resize @w@ such that it fits inside the given rectangle,
|
||||||
-- rectangle, including its border.
|
-- including its border.
|
||||||
tileWindow :: Window -> Rectangle -> X ()
|
tileWindow :: Window -> Rectangle -> X ()
|
||||||
tileWindow w r = withDisplay $ \d -> withWindowAttributes d w $ \wa -> do
|
tileWindow w r = withDisplay $ \d -> withWindowAttributes d w $ \wa -> do
|
||||||
-- give all windows at least 1x1 pixels
|
-- give all windows at least 1x1 pixels
|
||||||
@ -297,13 +300,13 @@ containedIn r1@(Rectangle x1 y1 w1 h1) r2@(Rectangle x2 y2 w2 h2)
|
|||||||
nubScreens :: [Rectangle] -> [Rectangle]
|
nubScreens :: [Rectangle] -> [Rectangle]
|
||||||
nubScreens xs = nub . filter (\x -> not $ any (x `containedIn`) xs) $ xs
|
nubScreens xs = nub . filter (\x -> not $ any (x `containedIn`) xs) $ xs
|
||||||
|
|
||||||
-- | Cleans the list of screens according to the rules documented for
|
-- | Clean the list of screens according to the rules documented for
|
||||||
-- nubScreens.
|
-- nubScreens.
|
||||||
getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle]
|
getCleanedScreenInfo :: MonadIO m => Display -> m [Rectangle]
|
||||||
getCleanedScreenInfo = io . fmap nubScreens . getScreenInfo
|
getCleanedScreenInfo = io . fmap nubScreens . getScreenInfo
|
||||||
|
|
||||||
-- | rescreen. The screen configuration may have changed (due to
|
-- | The screen configuration may have changed (due to -- xrandr),
|
||||||
-- xrandr), update the state and refresh the screen, and reset the gap.
|
-- update the state and refresh the screen, and reset the gap.
|
||||||
rescreen :: X ()
|
rescreen :: X ()
|
||||||
rescreen = do
|
rescreen = do
|
||||||
xinesc <- withDisplay getCleanedScreenInfo
|
xinesc <- withDisplay getCleanedScreenInfo
|
||||||
@ -317,7 +320,7 @@ rescreen = do
|
|||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
|
|
||||||
-- | setButtonGrab. Tell whether or not to intercept clicks on a given window
|
-- | Tell whether or not to intercept clicks on a given window
|
||||||
setButtonGrab :: Bool -> Window -> X ()
|
setButtonGrab :: Bool -> Window -> X ()
|
||||||
setButtonGrab grab w = do
|
setButtonGrab grab w = do
|
||||||
pointerMode <- asks $ \c -> if clickJustFocuses (config c)
|
pointerMode <- asks $ \c -> if clickJustFocuses (config c)
|
||||||
@ -415,12 +418,12 @@ sendMessageWithNoRefresh a w =
|
|||||||
handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
|
handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
|
||||||
updateLayout (W.tag w)
|
updateLayout (W.tag w)
|
||||||
|
|
||||||
-- | Update the layout field of a workspace
|
-- | Update the layout field of a workspace.
|
||||||
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
|
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
|
||||||
updateLayout i ml = whenJust ml $ \l ->
|
updateLayout i ml = whenJust ml $ \l ->
|
||||||
runOnWorkspaces $ \ww -> return $ if W.tag ww == i then ww { W.layout = l} else ww
|
runOnWorkspaces $ \ww -> return $ if W.tag ww == i then ww { W.layout = l} else ww
|
||||||
|
|
||||||
-- | Set the layout of the currently viewed workspace
|
-- | Set the layout of the currently viewed workspace.
|
||||||
setLayout :: Layout Window -> X ()
|
setLayout :: Layout Window -> X ()
|
||||||
setLayout l = do
|
setLayout l = do
|
||||||
ss@(W.StackSet { W.current = c@(W.Screen { W.workspace = ws })}) <- gets windowset
|
ss@(W.StackSet { W.current = c@(W.Screen { W.workspace = ws })}) <- gets windowset
|
||||||
@ -430,7 +433,7 @@ setLayout l = do
|
|||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
-- Utilities
|
-- Utilities
|
||||||
|
|
||||||
-- | Return workspace visible on screen 'sc', or 'Nothing'.
|
-- | Return workspace visible on screen @sc@, or 'Nothing'.
|
||||||
screenWorkspace :: ScreenId -> X (Maybe WorkspaceId)
|
screenWorkspace :: ScreenId -> X (Maybe WorkspaceId)
|
||||||
screenWorkspace sc = withWindowSet $ return . W.lookupWorkspace sc
|
screenWorkspace sc = withWindowSet $ return . W.lookupWorkspace sc
|
||||||
|
|
||||||
@ -438,7 +441,7 @@ screenWorkspace sc = withWindowSet $ return . W.lookupWorkspace sc
|
|||||||
withFocused :: (Window -> X ()) -> X ()
|
withFocused :: (Window -> X ()) -> X ()
|
||||||
withFocused f = withWindowSet $ \w -> whenJust (W.peek w) f
|
withFocused f = withWindowSet $ \w -> whenJust (W.peek w) f
|
||||||
|
|
||||||
-- | 'True' if window is under management by us
|
-- | Is the window is under management by xmonad?
|
||||||
isClient :: Window -> X Bool
|
isClient :: Window -> X Bool
|
||||||
isClient w = withWindowSet $ return . W.member w
|
isClient w = withWindowSet $ return . W.member w
|
||||||
|
|
||||||
@ -449,13 +452,13 @@ extraModifiers = do
|
|||||||
nlm <- gets numberlockMask
|
nlm <- gets numberlockMask
|
||||||
return [0, nlm, lockMask, nlm .|. lockMask ]
|
return [0, nlm, lockMask, nlm .|. lockMask ]
|
||||||
|
|
||||||
-- | Strip numlock\/capslock from a mask
|
-- | Strip numlock\/capslock from a mask.
|
||||||
cleanMask :: KeyMask -> X KeyMask
|
cleanMask :: KeyMask -> X KeyMask
|
||||||
cleanMask km = do
|
cleanMask km = do
|
||||||
nlm <- gets numberlockMask
|
nlm <- gets numberlockMask
|
||||||
return (complement (nlm .|. lockMask) .&. km)
|
return (complement (nlm .|. lockMask) .&. km)
|
||||||
|
|
||||||
-- | Get the 'Pixel' value for a named color
|
-- | Get the 'Pixel' value for a named color.
|
||||||
initColor :: Display -> String -> IO (Maybe Pixel)
|
initColor :: Display -> String -> IO (Maybe Pixel)
|
||||||
initColor dpy c = C.handle (\(C.SomeException _) -> return Nothing) $
|
initColor dpy c = C.handle (\(C.SomeException _) -> return Nothing) $
|
||||||
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||||
@ -521,8 +524,8 @@ readStateFile xmc = do
|
|||||||
readStrict :: Handle -> IO String
|
readStrict :: Handle -> IO String
|
||||||
readStrict h = hGetContents h >>= \s -> length s `seq` return s
|
readStrict h = hGetContents h >>= \s -> length s `seq` return s
|
||||||
|
|
||||||
-- | @restart name resume@. Attempt to restart xmonad by executing the program
|
-- | @restart name resume@ attempts to restart xmonad by executing the program
|
||||||
-- @name@. If @resume@ is 'True', restart with the current window state.
|
-- @name@. If @resume@ is 'True', restart with the current window state.
|
||||||
-- When executing another window manager, @resume@ should be 'False'.
|
-- When executing another window manager, @resume@ should be 'False'.
|
||||||
restart :: String -> Bool -> X ()
|
restart :: String -> Bool -> X ()
|
||||||
restart prog resume = do
|
restart prog resume = do
|
||||||
@ -532,10 +535,10 @@ restart prog resume = do
|
|||||||
catchIO (executeFile prog True [] Nothing)
|
catchIO (executeFile prog True [] Nothing)
|
||||||
|
|
||||||
------------------------------------------------------------------------
|
------------------------------------------------------------------------
|
||||||
-- | Floating layer support
|
-- Floating layer support
|
||||||
|
|
||||||
-- | Given a window, find the screen it is located on, and compute
|
-- | Given a window, find the screen it is located on, and compute
|
||||||
-- the geometry of that window wrt. that screen.
|
-- the geometry of that window WRT that screen.
|
||||||
floatLocation :: Window -> X (ScreenId, W.RationalRect)
|
floatLocation :: Window -> X (ScreenId, W.RationalRect)
|
||||||
floatLocation w =
|
floatLocation w =
|
||||||
catchX go $ do
|
catchX go $ do
|
||||||
@ -619,7 +622,7 @@ mouseDrag f done = do
|
|||||||
clearEvents pointerMotionMask
|
clearEvents pointerMotionMask
|
||||||
return z
|
return z
|
||||||
|
|
||||||
-- | drag the window under the cursor with the mouse while it is dragged
|
-- | Drag the window under the cursor with the mouse while it is dragged.
|
||||||
mouseMoveWindow :: Window -> X ()
|
mouseMoveWindow :: Window -> X ()
|
||||||
mouseMoveWindow w = whenX (isClient w) $ withDisplay $ \d -> do
|
mouseMoveWindow w = whenX (isClient w) $ withDisplay $ \d -> do
|
||||||
wa <- io $ getWindowAttributes d w
|
wa <- io $ getWindowAttributes d w
|
||||||
@ -633,7 +636,7 @@ mouseMoveWindow w = whenX (isClient w) $ withDisplay $ \d -> do
|
|||||||
)
|
)
|
||||||
(float w)
|
(float w)
|
||||||
|
|
||||||
-- | resize the window under the cursor with the mouse while it is dragged
|
-- | Resize the window under the cursor with the mouse while it is dragged.
|
||||||
mouseResizeWindow :: Window -> X ()
|
mouseResizeWindow :: Window -> X ()
|
||||||
mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
|
mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
|
||||||
wa <- io $ getWindowAttributes d w
|
wa <- io $ getWindowAttributes d w
|
||||||
@ -648,8 +651,9 @@ mouseResizeWindow w = whenX (isClient w) $ withDisplay $ \d -> do
|
|||||||
(float w)
|
(float w)
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- | Support for window size hints
|
-- Support for window size hints
|
||||||
|
|
||||||
|
-- | An alias for a (width, height) pair
|
||||||
type D = (Dimension, Dimension)
|
type D = (Dimension, Dimension)
|
||||||
|
|
||||||
-- | Given a window, build an adjuster function that will reduce the given
|
-- | Given a window, build an adjuster function that will reduce the given
|
||||||
@ -677,7 +681,7 @@ applySizeHintsContents :: Integral a => SizeHints -> (a, a) -> D
|
|||||||
applySizeHintsContents sh (w, h) =
|
applySizeHintsContents sh (w, h) =
|
||||||
applySizeHints' sh (fromIntegral $ max 1 w, fromIntegral $ max 1 h)
|
applySizeHints' sh (fromIntegral $ max 1 w, fromIntegral $ max 1 h)
|
||||||
|
|
||||||
-- | XXX comment me
|
-- | Use X11 size hints to scale a pair of dimensions.
|
||||||
applySizeHints' :: SizeHints -> D -> D
|
applySizeHints' :: SizeHints -> D -> D
|
||||||
applySizeHints' sh =
|
applySizeHints' sh =
|
||||||
maybe id applyMaxSizeHint (sh_max_size sh)
|
maybe id applyMaxSizeHint (sh_max_size sh)
|
||||||
|
Loading…
x
Reference in New Issue
Block a user