Skip to content

Commit

Permalink
introduce single active scratchpad hook
Browse files Browse the repository at this point in the history
  • Loading branch information
philib committed Oct 22, 2023
1 parent 8c0ca8b commit d811643
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 0 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,10 @@
ordered lexicographically, as before. Currently focused window will
always be the topmost, meaning the last in the list.

* `XMonad.Util.NamedScratchpad`

- Added a logHook to allow only one active scratchpad per workspace.

### New Modules

* `XMonad.Layout.CenterMainFluid`
Expand Down
35 changes: 35 additions & 0 deletions XMonad/Util/NamedScratchpad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ module XMonad.Util.NamedScratchpad (
allNamedScratchpadAction,
namedScratchpadManageHook,
nsHideOnFocusLoss,
nsSingleScratchpadPerWorkspace,

-- * Dynamic Scratchpads
-- $dynamic-scratchpads
Expand Down Expand Up @@ -298,6 +299,40 @@ nsHideOnFocusLoss scratches = withWindowSet $ \winSet -> do
whenX (isNSP lastFocus scratches) $
shiftToNSP (W.workspaces winSet) ($ lastFocus)

-- | A @logHook@ to have only one active scratchpad on a workspace. This can be
-- useful when working with multiple floating scratchpads which would otherwise be stacked. Note that this also requires you
-- to use the 'XMonad.Hooks.RefocusLast.refocusLastLogHook'.
--
-- ==== __Example__
--
-- > import XMonad.Hooks.RefocusLast (refocusLastLogHook)
-- > import XMonad.Util.NamedScratchpad
-- >
-- > main = xmonad $ def
-- > { logHook = refocusLastLogHook
-- > >> nsHideOnNewScratchpad myScratchpads
-- > -- enable hiding for all of @myScratchpads@
-- > }
nsSingleScratchpadPerWorkspace :: NamedScratchpads -> X ()
nsSingleScratchpadPerWorkspace scratches = withWindowSet $ \winSet -> do
let cur = W.currentTag winSet
let allWindowsOnCurrentWorkspace = W.index winSet
withRecentsIn cur () $ \lastFocus curFocus -> do
allScratchesOnCurrentWS <- filterM (`isNSP` scratches) allWindowsOnCurrentWorkspace
let allScratchesButCurrent = filter (/= curFocus) allScratchesOnCurrentWS
hideScratch = \s -> shiftToNSP (W.workspaces winSet) ($ s)

let isWorthy =
-- Check for the window being on the current workspace; if there
-- is no history (i.e., curFocus ≡ lastFocus), don't do anything
-- because the potential scratchpad is definitely focused.
lastFocus `elem` W.index winSet && lastFocus /= curFocus
-- Don't do anything on the NSP workspace, lest the world explodes.
&& cur /= scratchpadWorkspaceTag
when isWorthy $
whenX (isNSP curFocus scratches) $
for_ allScratchesButCurrent hideScratch

-- | Execute some action on a named scratchpad.
--
-- This function /almost always/ ignores its third argument; see Note
Expand Down

0 comments on commit d811643

Please sign in to comment.