Adam Plaice ca866229f6 Fix most remaining broken inter-module docs links
The links were broken due to:

1. Incorrect quotes (' instead of " for module links and occasionally
vice-versa).

2. Changes in the name of the "target" module not reflected in the
"source" docs.

3. Typos to begin with.

4. Use of `<foo>` in the docs is rendered as just `foo` with a link to
`/foo`.

5. Similarly for `"Foo"` if it starts with a capital letter (and hence
could be a module).

6. Markup inside `@` code blocks still being applied.

e.g. `@M-<arrow-keys>@` is rendered as `M-arrow-keys` with a spurious
hyperlink from arrow-keys to `/arrow-keys`, which is confusing.

Three links from XMonad.Util.Run have been removed outright, since
they're no longer examples of the usage of 'runProcessWithInput'.
WmiiActions has been gone since 2008, while XMonad.Prompt.Directory
and XMonad.Layout.WorkspaceDir haven't been using
'runProcessWithInput' since 2020 and 2012, respectively.

In some cases the `<foo>` were surrounded with @, especially in the
case of key definitions, for consistency.  (This wasn't done
everywhere, because it looks ugly in the source.)

MoreManageHelpers has never been in xmonad-contrib.  ManageHelpers
seems to fill the expected role.

In the case of the module description for X.H.ManageDebug the quotes
were simply removed because none of the likely options to make the
link work were successful.
2022-11-01 19:35:55 +01:00

157 lines
6.5 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.FloatKeys
-- Description : Move and resize floating windows.
-- Copyright : (c) Karsten Schoelzel <kuser@gmx.de>
-- License : BSD
--
-- Maintainer : Karsten Schoelzel <kuser@gmx.de>
-- Stability : stable
-- Portability : unportable
--
-- Move and resize floating windows.
-----------------------------------------------------------------------------
module XMonad.Actions.FloatKeys (
-- * Usage
-- $usage
keysMoveWindow,
keysMoveWindowTo,
keysResizeWindow,
keysAbsResizeWindow,
directionMoveWindow,
directionResizeWindow,
Direction2D(..),
P, G, ChangeDim
) where
import XMonad
import XMonad.Prelude (fi)
import XMonad.Util.Types
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Actions.FloatKeys
--
-- Then add appropriate key bindings, for example:
--
-- > , ((modm, xK_d ), withFocused (keysResizeWindow (-10,-10) (1,1)))
-- > , ((modm, xK_s ), withFocused (keysResizeWindow (10,10) (1,1)))
-- > , ((modm .|. shiftMask, xK_d ), withFocused (keysAbsResizeWindow (-10,-10) (1024,752)))
-- > , ((modm .|. shiftMask, xK_s ), withFocused (keysAbsResizeWindow (10,10) (1024,752)))
-- > , ((modm, xK_a ), withFocused (keysMoveWindowTo (512,384) (1%2,1%2)))
--
-- Using "XMonad.Util.EZConfig" syntax, we can easily build keybindings
-- where @M-\<arrow-keys\>@ moves the currently focused window and
-- @M-S-\<arrow-keys\>@ resizes it using 'directionMoveWindow' and
-- 'directionResizeWindow':
--
-- > [ ("M-" <> m <> k, withFocused $ f i)
-- > | (i, k) <- zip [U, D, R, L] ["<Up>", "<Down>", "<Right>", "<Left>"]
-- > , (f, m) <- [(directionMoveWindow 10, ""), (directionResizeWindow 10, "S-")]
-- > ]
--
-- For detailed instructions on editing your key bindings, see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
-- | @directionMoveWindow delta dir win@ moves the window @win@ by
-- @delta@ pixels in direction @dir@.
directionMoveWindow :: Int -> Direction2D -> Window -> X ()
directionMoveWindow delta dir win = case dir of
U -> keysMoveWindow (0, -delta) win
D -> keysMoveWindow (0, delta) win
R -> keysMoveWindow (delta, 0) win
L -> keysMoveWindow (-delta, 0) win
-- | @directionResizeWindow delta dir win@ resizes the window @win@ by
-- @delta@ pixels in direction @dir@.
directionResizeWindow :: Int -> Direction2D -> Window -> X ()
directionResizeWindow delta dir win = case dir of
U -> keysResizeWindow (0, -delta) (0, 0) win
D -> keysResizeWindow (0, delta) (0, 0) win
R -> keysResizeWindow (delta, 0) (0, 0) win
L -> keysResizeWindow (-delta, 0) (0, 0) win
-- | @keysMoveWindow (dx, dy)@ moves the window by @dx@ pixels to the
-- right and @dy@ pixels down.
keysMoveWindow :: ChangeDim -> Window -> X ()
keysMoveWindow (dx,dy) w = whenX (isClient w) $ withDisplay $ \d ->
withWindowAttributes d w $ \wa -> do
io $ moveWindow d w (fi (fi (wa_x wa) + dx))
(fi (fi (wa_y wa) + dy))
float w
-- | @keysMoveWindowTo (x, y) (gx, gy)@ moves the window relative
-- point @(gx, gy)@ to the point @(x,y)@, where @(gx,gy)@ gives a
-- position relative to the window border, i.e. @gx = 0@ is the left
-- border, @gx = 1@ is the right border, @gy = 0@ is the top border, and
-- @gy = 1@ the bottom border.
--
-- For example, on a 1024x768 screen:
--
-- > keysMoveWindowTo (512,384) (1%2, 1%2) -- center the window on screen
-- > keysMoveWindowTo (1024,0) (1, 0) -- put window in the top right corner
keysMoveWindowTo :: P -> G -> Window -> X ()
keysMoveWindowTo (x,y) (gx, gy) w = whenX (isClient w) $ withDisplay $ \d ->
withWindowAttributes d w $ \wa -> do
io $ moveWindow d w (x - round (gx * fi (wa_width wa)))
(y - round (gy * fi (wa_height wa)))
float w
type G = (Rational, Rational)
type P = (Position, Position)
type ChangeDim = (Int, Int)
-- | @keysResizeWindow (dx, dy) (gx, gy)@ changes the width by @dx@
-- and the height by @dy@, leaving the window-relative point @(gx,
-- gy)@ fixed.
--
-- For example:
--
-- > keysResizeWindow (10, 0) (0, 0) -- make the window 10 pixels larger to the right
-- > keysResizeWindow (10, 0) (0, 1%2) -- does the same, unless sizeHints are applied
-- > keysResizeWindow (10, 10) (1%2, 1%2) -- add 5 pixels on each side
-- > keysResizeWindow (-10, -10) (0, 1) -- shrink the window in direction of the bottom-left corner
keysResizeWindow :: ChangeDim -> G -> Window -> X ()
keysResizeWindow = keysMoveResize keysResizeWindow'
-- | @keysAbsResizeWindow (dx, dy) (ax, ay)@ changes the width by @dx@
-- and the height by @dy@, leaving the screen absolute point @(ax,
-- ay)@ fixed.
--
-- For example:
--
-- > keysAbsResizeWindow (10, 10) (0, 0) -- enlarge the window; if it is not in the top-left corner it will also be moved down and to the right.
keysAbsResizeWindow :: ChangeDim -> D -> Window -> X ()
keysAbsResizeWindow = keysMoveResize keysAbsResizeWindow'
keysAbsResizeWindow' :: SizeHints -> P -> D -> ChangeDim -> D -> (P,D)
keysAbsResizeWindow' sh (x,y) (w,h) (dx,dy) (ax, ay) = ((round nx, round ny), (nw, nh))
where
-- The width and height of a window are positive and thus
-- converting to 'Dimension' should be safe.
(nw, nh) = applySizeHintsContents sh (fi w + dx, fi h + dy)
nx :: Rational
nx = fi (ax * w + nw * (fi x - ax)) / fi w
ny :: Rational
ny = fi (ay * h + nh * (fi y - ay)) / fi h
keysResizeWindow' :: SizeHints -> P -> D -> ChangeDim -> G -> (P,D)
keysResizeWindow' sh (x,y) (w,h) (dx,dy) (gx, gy) = ((nx, ny), (nw, nh))
where
(nw, nh) = applySizeHintsContents sh (fi w + dx, fi h + dy)
nx = round $ fi x + gx * fi w - gx * fi nw
ny = round $ fi y + gy * fi h - gy * fi nh
keysMoveResize :: (SizeHints -> P -> D -> a -> b -> (P,D)) -> a -> b -> Window -> X ()
keysMoveResize f move resize w = whenX (isClient w) $ withDisplay $ \d ->
withWindowAttributes d w $ \wa -> do
sh <- io $ getWMNormalHints d w
let wa_dim = (fi $ wa_width wa, fi $ wa_height wa)
wa_pos = (fi $ wa_x wa, fi $ wa_y wa)
(wn_pos, wn_dim) = f sh wa_pos wa_dim move resize
io $ resizeWindow d w `uncurry` wn_dim
io $ moveWindow d w `uncurry` wn_pos
float w