Merge pull request #479 from slotThe/topic-history

X.A.TopicSpace: Deprecate internal history
This commit is contained in:
slotThe
2021-03-23 07:51:16 +01:00
committed by GitHub
3 changed files with 64 additions and 28 deletions

View File

@@ -70,6 +70,13 @@
Again, no change when used together with `dynamicLogString`, but other
uses of these in user configs might need to be adapted.
* `XMonad.Actions.TopicSpace`
- Deprecated the `maxTopicHistory` field, as well as the
`getLastFocusedTopics` and `setLastFocusedTopic` functions. It is
now recommended to directly use `XMonad.Hooks.WorkspaceHistory`
instead.
### New Modules
* `XMonad.Util.Hacks`
@@ -418,6 +425,9 @@
- Added `workspaceHistoryModify` to modify the workspace history with a pure
function.
- Added `workspaceHistoryHookExclude` for excluding certain
workspaces to ever enter the history.
* `XMonad.Util.DebugWindow`
- Fixed a bottom in `debugWindow` when used on windows with UTF8 encoded titles.

View File

@@ -29,7 +29,6 @@ module XMonad.Actions.TopicSpace
-- * Switching and Shifting Topics
, switchTopic
, switchTopicWith
, switchNthLastFocused
, switchNthLastFocusedByScreen
, switchNthLastFocusedExclude
@@ -42,12 +41,17 @@ module XMonad.Actions.TopicSpace
-- * Getting the Topic History
, getLastFocusedTopics
, getLastFocusedTopicsByScreen
, workspaceHistory
, workspaceHistoryByScreen
-- * Modifying the Topic History
, setLastFocusedTopic
, reverseLastFocusedTopics
-- * History hooks
, workspaceHistoryHook
, workspaceHistoryHookExclude
-- * Pretty Printing
, pprWindowSet
@@ -60,7 +64,7 @@ where
import XMonad
import qualified Data.Map as M
import qualified Data.Map.Strict as M
import qualified XMonad.Hooks.DynamicLog as DL
import qualified XMonad.StackSet as W
@@ -78,6 +82,8 @@ import XMonad.Hooks.UrgencyHook (readUrgents)
import XMonad.Hooks.WorkspaceHistory
( workspaceHistory
, workspaceHistoryByScreen
, workspaceHistoryHook
, workspaceHistoryHookExclude
, workspaceHistoryModify
)
@@ -113,6 +119,12 @@ import XMonad.Util.Run (spawnPipe)
-- * Replace the @workspaces@ field in your 'XConfig' with a list of your
-- topics names
--
-- * Optionally, if you want to use the history features, add
-- 'workspaceHistoryHook' from "XMonad.Hooks.WorkspaceHistory"
-- (re-exported by this module) or an equivalent function to your
-- @logHook@. See the documentation of
-- "XMonad.Hooks.WorkspaceHistory" for further details
--
-- Let us go through a full example together. Given the following topic names
--
-- > -- The list of all topics/workspaces of your xmonad configuration.
@@ -272,6 +284,7 @@ data TopicConfig = TopicConfig { topicDirs :: M.Map Topic Dir
-- usually 10 is a good default since we can bind all of
-- them using numeric keypad.
}
{-# DEPRECATED maxTopicHistory "This field will be removed in the future; history is now handled by XMonad.Hooks.WorkspaceHistory" #-}
instance Default TopicConfig where
def = TopicConfig { topicDirs = M.empty
@@ -284,10 +297,7 @@ instance Default TopicConfig where
-- | Return the (possibly empty) list of last focused topics.
getLastFocusedTopics :: X [Topic]
getLastFocusedTopics = workspaceHistory
-- | Like 'getLastFocusedTopics', but group the topics by their screen-id's.
getLastFocusedTopicsByScreen :: X [(ScreenId, [Topic])]
getLastFocusedTopicsByScreen = workspaceHistoryByScreen
{-# DEPRECATED getLastFocusedTopics "Use XMonad.Hooks.WorkspaceHistory.workspaceHistory (re-exported by this module) instead" #-}
-- | Given a 'TopicConfig', a topic, and a predicate to select topics that one
-- wants to keep, this function will cons the topic in front of the list of
@@ -298,6 +308,7 @@ setLastFocusedTopic tc w predicate = do
sid <- gets $ W.screen . W.current . windowset
workspaceHistoryModify $
take (maxTopicHistory tc) . nub . filter (predicate . snd) . ((sid, w) :)
{-# DEPRECATED setLastFocusedTopic "Use XMonad.Hooks.WorkspaceHistory instead" #-}
-- | Reverse the list of "last focused topics"
reverseLastFocusedTopics :: X ()
@@ -315,7 +326,7 @@ pprWindowSet tg pp = do
setLastFocusedTopic tg
(W.tag . W.workspace . W.current $ winset)
(`notElem` empty_workspaces)
lastWs <- getLastFocusedTopics
lastWs <- workspaceHistory
let depth topic = fromJust $ elemIndex topic (lastWs ++ [topic])
add_depth proj topic = proj pp . (((topic++":")++) . show) . depth $ topic
pp' = pp { ppHidden = add_depth ppHidden, ppVisible = add_depth ppVisible }
@@ -337,19 +348,13 @@ currentTopicAction tg = topicAction tg =<< gets (W.tag . W.workspace . W.current
-- | Switch to the given topic.
switchTopic :: TopicConfig -> Topic -> X ()
switchTopic = switchTopicWith (const True)
-- | Like 'switchTopic', but give a custom filtering function to
-- 'setLastFocusedTopic'.
switchTopicWith :: (Topic -> Bool) -> TopicConfig -> Topic -> X ()
switchTopicWith predicate tg topic = do
switchTopic tc topic = do
-- Switch to topic and add it to the last seen topics
windows $ W.greedyView topic
setLastFocusedTopic tg topic predicate
-- If applicable, execute the topic action
wins <- gets (W.integrate' . W.stack . W.workspace . W.current . windowset)
when (null wins) $ topicAction tg topic
when (null wins) $ topicAction tc topic
-- | Switch to the Nth last focused topic or fall back to the 'defaultTopic'.
switchNthLastFocused :: TopicConfig -> Int -> X ()
@@ -358,7 +363,7 @@ switchNthLastFocused = switchNthLastFocusedExclude []
-- | Like 'switchNthLastFocused', but also filter out certain topics.
switchNthLastFocusedExclude :: [Topic] -> TopicConfig -> Int -> X ()
switchNthLastFocusedExclude excludes tc depth = do
lastWs <- filter (`notElem` excludes) <$> getLastFocusedTopics
lastWs <- filter (`notElem` excludes) <$> workspaceHistory
switchTopic tc $ (lastWs ++ repeat (defaultTopic tc)) !! depth
-- | Like 'switchNthLastFocused', but only consider topics that used to
@@ -376,13 +381,13 @@ switchNthLastFocusedByScreen tc depth = do
. listToMaybe
. map snd
. filter ((== sid) . fst)
<$> getLastFocusedTopicsByScreen
<$> workspaceHistoryByScreen
switchTopic tc $ (sws ++ repeat (defaultTopic tc)) !! depth
-- | Shift the focused window to the Nth last focused topic, or fall back to doing nothing.
shiftNthLastFocused :: Int -> X ()
shiftNthLastFocused n = do
ws <- fmap (listToMaybe . drop n) getLastFocusedTopics
ws <- fmap (listToMaybe . drop n) workspaceHistory
whenJust ws $ windows . W.shift
-- | Return the directory associated with the current topic, or return the empty

View File

@@ -19,6 +19,7 @@ module XMonad.Hooks.WorkspaceHistory (
-- $usage
-- * Hooking
workspaceHistoryHook
, workspaceHistoryHookExclude
-- * Querying
, workspaceHistory
, workspaceHistoryByScreen
@@ -32,8 +33,8 @@ import Control.Applicative
import Prelude
import XMonad
import XMonad.StackSet hiding (filter, delete)
import Data.List
import XMonad.StackSet hiding (delete, filter, new)
import Data.List (delete, find, foldl', groupBy, nub, sortBy)
import qualified XMonad.Util.ExtensibleState as XS
-- $usage
@@ -50,9 +51,17 @@ import qualified XMonad.Util.ExtensibleState as XS
-- > , ...
-- > }
--
-- If you want to completely exclude certain workspaces from entering
-- the history, you can use 'workspaceHistoryHookExclude' instead. For
-- example, to ignore the named scratchpad workspace:
--
-- > import XMonad.Util.NamedScratchpad (scratchpadWorkspaceTag)
-- > ...
-- > , logHook = ... >> workspaceHistoryHookExclude [scratchpadWorkspaceTag] >> ...
--
-- To make use of the collected data, a query function is provided.
data WorkspaceHistory = WorkspaceHistory
newtype WorkspaceHistory = WorkspaceHistory
{ history :: [(ScreenId, WorkspaceId)] -- ^ Workspace Screens in
-- reverse-chronological order.
} deriving (Typeable, Read, Show)
@@ -66,6 +75,12 @@ instance ExtensionClass WorkspaceHistory where
workspaceHistoryHook :: X ()
workspaceHistoryHook = gets windowset >>= (XS.modify . updateLastActiveOnEachScreen)
-- | Like 'workspaceHistoryHook', but with the ability to exclude
-- certain workspaces.
workspaceHistoryHookExclude :: [WorkspaceId] -> X ()
workspaceHistoryHookExclude ws =
gets windowset >>= XS.modify . updateLastActiveOnEachScreenExclude ws
workspaceHistoryWithScreen :: X [(ScreenId, WorkspaceId)]
workspaceHistoryWithScreen = XS.gets history
@@ -86,22 +101,28 @@ workspaceHistoryTransaction :: X () -> X ()
workspaceHistoryTransaction action = do
startingHistory <- XS.gets history
action
new <- (flip updateLastActiveOnEachScreen $ WorkspaceHistory startingHistory) <$> gets windowset
new <- flip updateLastActiveOnEachScreen (WorkspaceHistory startingHistory) <$> gets windowset
XS.put new
-- | Update the last visible workspace on each monitor if needed
-- already there, or move it to the front if it is.
updateLastActiveOnEachScreen :: WindowSet -> WorkspaceHistory -> WorkspaceHistory
updateLastActiveOnEachScreen StackSet {current = cur, visible = vis} wh =
WorkspaceHistory { history = doUpdate cur $ foldl updateLastForScreen (history wh) $ vis ++ [cur] }
updateLastActiveOnEachScreen = updateLastActiveOnEachScreenExclude []
-- | Like 'updateLastActiveOnEachScreen', but with the ability to
-- exclude certain workspaces.
updateLastActiveOnEachScreenExclude :: [WorkspaceId] -> WindowSet -> WorkspaceHistory -> WorkspaceHistory
updateLastActiveOnEachScreenExclude ws StackSet {current = cur, visible = vis} wh =
WorkspaceHistory { history = doUpdate cur $ foldl' updateLastForScreen (history wh) $ vis ++ [cur] }
where
firstOnScreen sid = find ((== sid) . fst)
doUpdate Screen {workspace = Workspace { tag = wid }, screen = sid} curr =
let newEntry = (sid, wid) in newEntry:delete newEntry curr
let newEntry = (sid, wid)
in if wid `elem` ws then curr else newEntry : delete newEntry curr
updateLastForScreen curr Screen {workspace = Workspace { tag = wid }, screen = sid} =
let newEntry = (sid, wid)
alreadyCurrent = maybe False (== newEntry) $ firstOnScreen sid curr
in if alreadyCurrent then curr else newEntry:delete newEntry curr
alreadyCurrent = Just newEntry == firstOnScreen sid curr
in if alreadyCurrent || wid `elem` ws then curr else newEntry : delete newEntry curr
-- | Modify a the workspace history with a given pure function.
workspaceHistoryModify :: ([(ScreenId, WorkspaceId)] -> [(ScreenId, WorkspaceId)]) -> X ()