Skip to content

Commit 673de11

Browse files
authored
Merge pull request #768 from liskin/fullscreen-hooks
Add (un)fullscreen hooks and float-restoring toggleFullFloat action
2 parents 815a595 + 02bd9eb commit 673de11

File tree

4 files changed

+170
-4
lines changed

4 files changed

+170
-4
lines changed

CHANGES.md

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,14 @@
106106
- A new module replicating the functionality of
107107
`XMonad.Hooks.DynamicProperty`, but with more discoverable names.
108108

109+
* `XMonad.Actions.ToggleFullFloat`:
110+
111+
- Fullscreen (float) a window while remembering its original state.
112+
There's both an action to be bound to a key, and hooks that plug into
113+
`XMonad.Hooks.EwmhDesktops`.
114+
109115
### Bug Fixes and Minor Changes
116+
110117
* `XMonad.Util.Loggers`
111118

112119
- Added `logClassname`, `logClassnames`, `logClassnames'`,
@@ -201,6 +208,11 @@
201208
some status bars (see this
202209
[polybar issue](https://github.com/polybar/polybar/issues/2603)).
203210

211+
- Added `setEwmhFullscreenHooks` to override the default fullfloat/sink
212+
behaviour of `_NET_WM_STATE_FULLSCREEN` requests. See also
213+
`XMonad.Actions.ToggleFullFloat` for a float-restoring implementation of
214+
fullscreening.
215+
204216
* `XMonad.Hooks.StatusBar`
205217

206218
- Added `startAllStatusBars` to start the configured status bars.

XMonad/Actions/ToggleFullFloat.hs

Lines changed: 122 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,122 @@
1+
-- |
2+
-- Module : XMonad.Actions.ToggleFullFloat
3+
-- Description : Fullscreen (float) a window while remembering its original state.
4+
-- Copyright : (c) 2022 Tomáš Janoušek <[email protected]>
5+
-- License : BSD3
6+
-- Maintainer : Tomáš Janoušek <[email protected]>
7+
--
8+
module XMonad.Actions.ToggleFullFloat (
9+
-- * Usage
10+
-- $usage
11+
toggleFullFloatEwmhFullscreen,
12+
toggleFullFloat,
13+
fullFloat,
14+
unFullFloat,
15+
gcToggleFullFloat,
16+
) where
17+
18+
import qualified Data.Map.Strict as M
19+
20+
import XMonad
21+
import XMonad.Prelude
22+
import XMonad.Hooks.EwmhDesktops (setEwmhFullscreenHooks)
23+
import XMonad.Hooks.ManageHelpers
24+
import qualified XMonad.StackSet as W
25+
import qualified XMonad.Util.ExtensibleState as XS
26+
27+
-- ---------------------------------------------------------------------
28+
-- $usage
29+
--
30+
-- The main use-case is to make 'ewmhFullscreen' (re)store the size and
31+
-- position of floating windows instead of just unconditionally sinking them
32+
-- into the floating layer. To enable this, you'll need this in your
33+
-- @xmonad.hs@:
34+
--
35+
-- > import XMonad
36+
-- > import XMonad.Actions.ToggleFullFloat
37+
-- > import XMonad.Hooks.EwmhDesktops
38+
-- >
39+
-- > main = xmonad $ … . toggleFullFloatEwmhFullscreen . ewmhFullscreen . ewmh . … $ def{…}
40+
--
41+
-- Additionally, this "smart" fullscreening can be bound to a key and invoked
42+
-- manually whenever one needs a larger window temporarily:
43+
--
44+
-- > , ((modMask .|. shiftMask, xK_t), withFocused toggleFullFloat)
45+
46+
newtype ToggleFullFloat = ToggleFullFloat{ fromToggleFullFloat :: M.Map Window (Maybe W.RationalRect) }
47+
deriving (Show, Read)
48+
49+
instance ExtensionClass ToggleFullFloat where
50+
extensionType = PersistentExtension
51+
initialValue = ToggleFullFloat mempty
52+
53+
-- | Full-float a window, remembering its state (tiled/floating and
54+
-- position/size).
55+
fullFloat :: Window -> X ()
56+
fullFloat = windows . appEndo <=< runQuery doFullFloatSave
57+
58+
-- | Restore window to its remembered state.
59+
unFullFloat :: Window -> X ()
60+
unFullFloat = windows . appEndo <=< runQuery doFullFloatRestore
61+
62+
-- | Full-float a window, if it's not already full-floating. Otherwise,
63+
-- restore its original state.
64+
toggleFullFloat :: Window -> X ()
65+
toggleFullFloat w = ifM (isFullFloat w) (unFullFloat w) (fullFloat w)
66+
67+
isFullFloat :: Window -> X Bool
68+
isFullFloat w = gets $ (Just fullRect ==) . M.lookup w . W.floating . windowset
69+
where
70+
fullRect = W.RationalRect 0 0 1 1
71+
72+
doFullFloatSave :: ManageHook
73+
doFullFloatSave = do
74+
w <- ask
75+
liftX $ do
76+
f <- gets $ M.lookup w . W.floating . windowset
77+
-- @M.insertWith const@ = don't overwrite stored original state
78+
XS.modify' $ ToggleFullFloat . M.insertWith const w f . fromToggleFullFloat
79+
doFullFloat
80+
81+
doFullFloatRestore :: ManageHook
82+
doFullFloatRestore = do
83+
w <- ask
84+
mf <- liftX $ do
85+
mf <- XS.gets $ M.lookup w . fromToggleFullFloat
86+
XS.modify' $ ToggleFullFloat . M.delete w . fromToggleFullFloat
87+
pure mf
88+
doF $ case mf of
89+
Just (Just f) -> W.float w f -- was floating before
90+
Just Nothing -> W.sink w -- was tiled before
91+
Nothing -> W.sink w -- fallback when not found in ToggleFullFloat
92+
93+
-- | Install ToggleFullFloat garbage collection hooks.
94+
--
95+
-- Note: This is included in 'toggleFullFloatEwmhFullscreen', only needed if
96+
-- using the 'toggleFullFloat' separately from the EWMH hook.
97+
gcToggleFullFloat :: XConfig a -> XConfig a
98+
gcToggleFullFloat c = c { startupHook = startupHook c <> gcToggleFullFloatStartupHook
99+
, handleEventHook = handleEventHook c <> gcToggleFullFloatEventHook }
100+
101+
-- | ToggleFullFloat garbage collection: drop windows when they're destroyed.
102+
gcToggleFullFloatEventHook :: Event -> X All
103+
gcToggleFullFloatEventHook DestroyWindowEvent{ev_window = w} = do
104+
XS.modify' $ ToggleFullFloat . M.delete w . fromToggleFullFloat
105+
mempty
106+
gcToggleFullFloatEventHook _ = mempty
107+
108+
-- | ToggleFullFloat garbage collection: restrict to existing windows at
109+
-- startup.
110+
gcToggleFullFloatStartupHook :: X ()
111+
gcToggleFullFloatStartupHook = withWindowSet $ \ws ->
112+
XS.modify' $ ToggleFullFloat . M.filterWithKey (\w _ -> w `W.member` ws) . fromToggleFullFloat
113+
114+
-- | Hook this module into 'XMonad.Hooks.EwmhDesktops.ewmhFullscreen'. This
115+
-- makes windows restore their original state (size and position if floating)
116+
-- instead of unconditionally sinking into the tiling layer.
117+
--
118+
-- ('gcToggleFullFloat' is included here.)
119+
toggleFullFloatEwmhFullscreen :: XConfig a -> XConfig a
120+
toggleFullFloatEwmhFullscreen =
121+
setEwmhFullscreenHooks doFullFloatSave doFullFloatRestore .
122+
gcToggleFullFloat

XMonad/Hooks/EwmhDesktops.hs

Lines changed: 35 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,10 @@ module XMonad.Hooks.EwmhDesktops (
4040
-- $customActivate
4141
setEwmhActivateHook,
4242

43+
-- ** Fullscreen
44+
-- $customFullscreen
45+
setEwmhFullscreenHooks,
46+
4347
-- ** @_NET_DESKTOP_VIEWPORT@
4448
-- $customManageDesktopViewport
4549
disableEwmhManageDesktopViewport,
@@ -106,6 +110,8 @@ data EwmhDesktopsConfig =
106110
-- ^ configurable workspace rename (see 'XMonad.Hooks.StatusBar.PP.ppRename')
107111
, activateHook :: ManageHook
108112
-- ^ configurable handling of window activation requests
113+
, fullscreenHooks :: (ManageHook, ManageHook)
114+
-- ^ configurable handling of fullscreen state requests
109115
, manageDesktopViewport :: Bool
110116
-- ^ manage @_NET_DESKTOP_VIEWPORT@?
111117
}
@@ -115,6 +121,7 @@ instance Default EwmhDesktopsConfig where
115121
{ workspaceSort = getSortByIndex
116122
, workspaceRename = pure pure
117123
, activateHook = doFocus
124+
, fullscreenHooks = (doFullFloat, doSink)
118125
, manageDesktopViewport = True
119126
}
120127

@@ -235,6 +242,25 @@ setEwmhWorkspaceRename f = XC.modifyDef $ \c -> c{ workspaceRename = f }
235242
setEwmhActivateHook :: ManageHook -> XConfig l -> XConfig l
236243
setEwmhActivateHook h = XC.modifyDef $ \c -> c{ activateHook = h }
237244

245+
246+
-- $customFullscreen
247+
-- When a client sends a @_NET_WM_STATE@ request to add/remove/toggle the
248+
-- @_NET_WM_STATE_FULLSCREEN@ state, 'ewmhFullscreen' uses a pair of hooks to
249+
-- make the window fullscreen and revert its state. The default hooks are
250+
-- stateless: windows are fullscreened by turning them into fullscreen floats,
251+
-- and reverted by sinking them into the tiling layer. This behaviour can be
252+
-- configured by supplying a pair of 'ManageHook's to 'setEwmhFullscreenHooks'.
253+
--
254+
-- See "XMonad.Actions.ToggleFullFloat" for a pair of hooks that store the
255+
-- original state of floating windows.
256+
257+
-- | Set (replace) the hooks invoked when clients ask to add/remove the
258+
-- $_NET_WM_STATE_FULLSCREEN@ state. The defaults are 'doFullFloat' and
259+
-- 'doSink'.
260+
setEwmhFullscreenHooks :: ManageHook -> ManageHook -> XConfig l -> XConfig l
261+
setEwmhFullscreenHooks f uf = XC.modifyDef $ \c -> c{ fullscreenHooks = (f, uf) }
262+
263+
238264
-- $customManageDesktopViewport
239265
-- Setting @_NET_DESKTOP_VIEWPORT@ is typically desired but can lead to a
240266
-- confusing workspace list in polybar, where this information is used to
@@ -472,7 +498,12 @@ fullscreenStartup = setFullscreenSupported
472498
-- Note this is not included in 'ewmh'.
473499
{-# DEPRECATED fullscreenEventHook "Use ewmhFullscreen instead." #-}
474500
fullscreenEventHook :: Event -> X All
475-
fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
501+
fullscreenEventHook = XC.withDef . fullscreenEventHook'
502+
503+
fullscreenEventHook' :: Event -> EwmhDesktopsConfig -> X All
504+
fullscreenEventHook'
505+
ClientMessageEvent{ev_event_display = dpy, ev_window = win, ev_message_type = typ, ev_data = action:dats}
506+
EwmhDesktopsConfig{fullscreenHooks = (fullscreenHook, unFullscreenHook)} = do
476507
managed <- isClient win
477508
wmstate <- getAtom "_NET_WM_STATE"
478509
fullsc <- getAtom "_NET_WM_STATE_FULLSCREEN"
@@ -489,14 +520,14 @@ fullscreenEventHook (ClientMessageEvent _ _ _ dpy win typ (action:dats)) = do
489520
when (managed && typ == wmstate && fi fullsc `elem` dats) $ do
490521
when (action == add || (action == toggle && not isFull)) $ do
491522
chWstate (fi fullsc:)
492-
windows $ W.float win $ W.RationalRect 0 0 1 1
523+
windows . appEndo =<< runQuery fullscreenHook win
493524
when (action == remove || (action == toggle && isFull)) $ do
494525
chWstate $ delete (fi fullsc)
495-
windows $ W.sink win
526+
windows . appEndo =<< runQuery unFullscreenHook win
496527

497528
return $ All True
498529

499-
fullscreenEventHook _ = return $ All True
530+
fullscreenEventHook' _ _ = return $ All True
500531

501532
setNumberOfDesktops :: (Integral a) => a -> X ()
502533
setNumberOfDesktops n = withDisplay $ \dpy -> do

xmonad-contrib.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -147,6 +147,7 @@ library
147147
XMonad.Actions.SwapWorkspaces
148148
XMonad.Actions.TagWindows
149149
XMonad.Actions.TiledWindowDragging
150+
XMonad.Actions.ToggleFullFloat
150151
XMonad.Actions.TopicSpace
151152
XMonad.Actions.TreeSelect
152153
XMonad.Actions.UpdateFocus

0 commit comments

Comments
 (0)