xmonad-contrib/XMonad/Hooks/ManageDebug.hs
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

108 lines
4.6 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.ManageDebug
-- Description : A manageHook and associated logHook for debugging ManageHooks.
-- Copyright : (c) Brandon S Allbery KF8NH, 2014
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : allbery.b@gmail.com
-- Stability : unstable
-- Portability : not portable
--
-- A @manageHook@ and associated @logHook@ for debugging 'ManageHook's.
-- Simplest usage: wrap your xmonad config in the @debugManageHook@ combinator.
-- Or use @debugManageHookOn@ for a triggerable version, specifying the
-- triggering key sequence in "XMonad.Util.EZConfig" syntax. Or use the
-- individual hooks in whatever way you see fit.
--
-----------------------------------------------------------------------------
--
--
module XMonad.Hooks.ManageDebug (debugManageHook
,debugManageHookOn
,manageDebug
,maybeManageDebug
,manageDebugLogHook
,debugNextManagedWindow
) where
import XMonad
import XMonad.Hooks.DebugStack
import XMonad.Util.DebugWindow
import XMonad.Util.EZConfig
import qualified XMonad.Util.ExtensibleState as XS
-- state for manageHook debugging to trigger logHook debugging
data MSDFinal = DoLogHook | SkipLogHook deriving Show
data MSDTrigger = MSDActivated | MSDInactive deriving Show
data ManageStackDebug = MSD MSDFinal MSDTrigger deriving Show
instance ExtensionClass ManageStackDebug where
initialValue = MSD SkipLogHook MSDInactive
-- | A combinator to add full 'ManageHook' debugging in a single operation.
debugManageHook :: XConfig l -> XConfig l
debugManageHook cf = cf {logHook = manageDebugLogHook <> logHook cf
,manageHook = manageDebug <> manageHook cf
}
-- | A combinator to add triggerable 'ManageHook' debugging in a single operation.
-- Specify a key sequence as a string in "XMonad.Util.EZConfig" syntax; press
-- this key before opening the window to get just that logged.
debugManageHookOn :: String -> XConfig l -> XConfig l
debugManageHookOn key cf = cf {logHook = manageDebugLogHook <> logHook cf
,manageHook = maybeManageDebug <> manageHook cf
}
`additionalKeysP`
[(key,debugNextManagedWindow)]
-- | Place this at the start of a 'ManageHook', or possibly other places for a
-- more limited view. It will show the current 'StackSet' state and the new
-- window, and set a flag so that @manageDebugLogHook@ will display the
-- final 'StackSet' state.
--
-- Note that the initial state shows only the current workspace; the final
-- one shows all workspaces, since your 'manageHook' might use e.g. 'doShift',
manageDebug :: ManageHook
manageDebug = do
w <- ask
liftX $ do
trace "== manageHook; current stack =="
debugStackString >>= trace
ws <- debugWindow w
trace $ "new window:\n " ++ ws
-- technically we don't care about go here, since only maybeManageDebug
-- uses it
XS.modify $ \(MSD _ go') -> MSD DoLogHook go'
idHook
-- | @manageDebug@ only if the user requested it with @debugNextManagedWindow@.
maybeManageDebug :: ManageHook
maybeManageDebug = do
go <- liftX $ do
MSD _ go' <- XS.get
-- leave it active, as we may manage multiple windows before the logHook
-- so we now deactivate it in the logHook
return go'
case go of
MSDActivated -> manageDebug
_ -> idHook
-- | If @manageDebug@ has set the debug-stack flag, show the stack.
manageDebugLogHook :: X ()
manageDebugLogHook = do
MSD log' _ <- XS.get
case log' of
DoLogHook -> do
trace "== manageHook; final stack =="
debugStackFullString >>= trace
-- see comment in maybeManageDebug
XS.put $ MSD SkipLogHook MSDInactive
_ -> idHook
-- | Request that the next window to be managed be @manageDebug@-ed. This can
-- be used anywhere an X action can, such as key bindings, mouse bindings
-- (presumably with 'const'), 'startupHook', etc.
debugNextManagedWindow :: X ()
debugNextManagedWindow = XS.modify $ \(MSD log' _) -> MSD log' MSDActivated