-----------------------------------------------------------------------------
-- |
-- 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 Int -> MSDFinal -> ShowS
[MSDFinal] -> ShowS
MSDFinal -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MSDFinal] -> ShowS
$cshowList :: [MSDFinal] -> ShowS
show :: MSDFinal -> String
$cshow :: MSDFinal -> String
showsPrec :: Int -> MSDFinal -> ShowS
$cshowsPrec :: Int -> MSDFinal -> ShowS
Show
data MSDTrigger = MSDActivated | MSDInactive deriving Int -> MSDTrigger -> ShowS
[MSDTrigger] -> ShowS
MSDTrigger -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MSDTrigger] -> ShowS
$cshowList :: [MSDTrigger] -> ShowS
show :: MSDTrigger -> String
$cshow :: MSDTrigger -> String
showsPrec :: Int -> MSDTrigger -> ShowS
$cshowsPrec :: Int -> MSDTrigger -> ShowS
Show
data ManageStackDebug = MSD MSDFinal MSDTrigger deriving Int -> ManageStackDebug -> ShowS
[ManageStackDebug] -> ShowS
ManageStackDebug -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ManageStackDebug] -> ShowS
$cshowList :: [ManageStackDebug] -> ShowS
show :: ManageStackDebug -> String
$cshow :: ManageStackDebug -> String
showsPrec :: Int -> ManageStackDebug -> ShowS
$cshowsPrec :: Int -> ManageStackDebug -> ShowS
Show
instance ExtensionClass ManageStackDebug where
  initialValue :: ManageStackDebug
initialValue = MSDFinal -> MSDTrigger -> ManageStackDebug
MSD MSDFinal
SkipLogHook MSDTrigger
MSDInactive

-- | A combinator to add full 'ManageHook' debugging in a single operation.
debugManageHook :: XConfig l -> XConfig l
debugManageHook :: forall (l :: * -> *). XConfig l -> XConfig l
debugManageHook XConfig l
cf = XConfig l
cf {logHook :: X ()
logHook    = X ()
manageDebugLogHook forall a. Semigroup a => a -> a -> a
<> forall (l :: * -> *). XConfig l -> X ()
logHook    XConfig l
cf
                        ,manageHook :: Query (Endo WindowSet)
manageHook = Query (Endo WindowSet)
manageDebug        forall a. Semigroup a => a -> a -> a
<> forall (l :: * -> *). XConfig l -> Query (Endo WindowSet)
manageHook XConfig l
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 :: forall (l :: * -> *). String -> XConfig l -> XConfig l
debugManageHookOn String
key XConfig l
cf = XConfig l
cf {logHook :: X ()
logHook    = X ()
manageDebugLogHook forall a. Semigroup a => a -> a -> a
<> forall (l :: * -> *). XConfig l -> X ()
logHook    XConfig l
cf
                              ,manageHook :: Query (Endo WindowSet)
manageHook = Query (Endo WindowSet)
maybeManageDebug   forall a. Semigroup a => a -> a -> a
<> forall (l :: * -> *). XConfig l -> Query (Endo WindowSet)
manageHook XConfig l
cf
                              }
                           forall (l :: * -> *). XConfig l -> [(String, X ())] -> XConfig l
`additionalKeysP`
                           [(String
key,X ()
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 :: Query (Endo WindowSet)
manageDebug = do
  Window
w <- forall r (m :: * -> *). MonadReader r m => m r
ask
  forall a. X a -> Query a
liftX forall a b. (a -> b) -> a -> b
$ do
    forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"== manageHook; current stack =="
    X String
debugStackString forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadIO m => String -> m ()
trace
    String
ws <- Window -> X String
debugWindow Window
w
    forall (m :: * -> *). MonadIO m => String -> m ()
trace forall a b. (a -> b) -> a -> b
$ String
"new window:\n  " forall a. [a] -> [a] -> [a]
++ String
ws
    -- technically we don't care about go here, since only maybeManageDebug
    -- uses it
    forall a (m :: * -> *).
(ExtensionClass a, XLike m) =>
(a -> a) -> m ()
XS.modify forall a b. (a -> b) -> a -> b
$ \(MSD MSDFinal
_ MSDTrigger
go') -> MSDFinal -> MSDTrigger -> ManageStackDebug
MSD MSDFinal
DoLogHook MSDTrigger
go'
  forall m. Monoid m => m
idHook

-- | @manageDebug@ only if the user requested it with @debugNextManagedWindow@.
maybeManageDebug :: ManageHook
maybeManageDebug :: Query (Endo WindowSet)
maybeManageDebug = do
  MSDTrigger
go <- forall a. X a -> Query a
liftX forall a b. (a -> b) -> a -> b
$ do
    MSD MSDFinal
_ MSDTrigger
go' <- forall a (m :: * -> *). (ExtensionClass a, XLike m) => m a
XS.get
    -- leave it active, as we may manage multiple windows before the logHook
    -- so we now deactivate it in the logHook
    forall (m :: * -> *) a. Monad m => a -> m a
return MSDTrigger
go'
  case MSDTrigger
go of
    MSDTrigger
MSDActivated -> Query (Endo WindowSet)
manageDebug
    MSDTrigger
_            -> forall m. Monoid m => m
idHook

-- | If @manageDebug@ has set the debug-stack flag, show the stack.
manageDebugLogHook :: X ()
manageDebugLogHook :: X ()
manageDebugLogHook = do
                       MSD MSDFinal
log' MSDTrigger
_ <- forall a (m :: * -> *). (ExtensionClass a, XLike m) => m a
XS.get
                       case MSDFinal
log' of
                         MSDFinal
DoLogHook -> do
                                  forall (m :: * -> *). MonadIO m => String -> m ()
trace String
"== manageHook; final stack =="
                                  X String
debugStackFullString forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadIO m => String -> m ()
trace
                                  -- see comment in maybeManageDebug
                                  forall a (m :: * -> *). (ExtensionClass a, XLike m) => a -> m ()
XS.put forall a b. (a -> b) -> a -> b
$ MSDFinal -> MSDTrigger -> ManageStackDebug
MSD MSDFinal
SkipLogHook MSDTrigger
MSDInactive
                         MSDFinal
_         -> forall m. Monoid m => m
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 :: X ()
debugNextManagedWindow = forall a (m :: * -> *).
(ExtensionClass a, XLike m) =>
(a -> a) -> m ()
XS.modify forall a b. (a -> b) -> a -> b
$ \(MSD MSDFinal
log' MSDTrigger
_) -> MSDFinal -> MSDTrigger -> ManageStackDebug
MSD MSDFinal
log' MSDTrigger
MSDActivated