Add getLastFocusedTopicsByScreen, switchNthLastFocusedByScreen

This commit is contained in:
slotThe 2020-11-21 16:22:58 +01:00
parent ce5aae5403
commit 8822d2ff51

View File

@ -18,22 +18,40 @@ module XMonad.Actions.TopicSpace
-- * Usage -- * Usage
-- $usage -- $usage
-- * Types for Building Topics
Topic Topic
, Dir , Dir
, TopicConfig(..) , TopicConfig(..)
-- * Default Topic Config
, def , def
, getLastFocusedTopics
, setLastFocusedTopic -- * Switching and Shifting Topics
, reverseLastFocusedTopics
, pprWindowSet
, topicActionWithPrompt
, topicAction
, currentTopicAction
, switchTopic , switchTopic
, switchTopicWith , switchTopicWith
, switchNthLastFocused , switchNthLastFocused
, switchNthLastFocusedByScreen
, switchNthLastFocusedExclude , switchNthLastFocusedExclude
, shiftNthLastFocused , shiftNthLastFocused
-- * Topic Actions
, topicActionWithPrompt
, topicAction
, currentTopicAction
-- * Getting the Topic History
, getLastFocusedTopics
, getLastFocusedTopicsByScreen
-- * Modifying the Topic History
, setLastFocusedTopic
, reverseLastFocusedTopics
-- * Pretty Printing
, pprWindowSet
-- * Utility
, currentTopicDir , currentTopicDir
, checkTopicConfig , checkTopicConfig
, (>*>) , (>*>)
@ -42,20 +60,19 @@ where
import XMonad import XMonad
import Data.List
import Data.Maybe (fromMaybe, isNothing, listToMaybe, fromJust)
import Data.Ord
import qualified Data.Map as M import qualified Data.Map as M
import Control.Applicative (liftA2) import qualified XMonad.Hooks.DynamicLog as DL
import Control.Monad (when,unless,replicateM_)
import System.IO
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.Prompt import Control.Applicative (liftA2)
import XMonad.Prompt.Workspace import Control.Monad (replicateM_, unless, when)
import Data.List ((\\), elemIndex, nub, sort, sortOn)
import Data.Maybe (fromJust, fromMaybe, isNothing, listToMaybe)
import System.IO (hClose, hPutStr)
import XMonad.Prompt (XPConfig)
import XMonad.Prompt.Workspace (workspacePrompt)
import qualified XMonad.Hooks.DynamicLog as DL
import XMonad.Hooks.DynamicLog (PP(ppHidden, ppVisible)) import XMonad.Hooks.DynamicLog (PP(ppHidden, ppVisible))
import XMonad.Hooks.UrgencyHook (readUrgents) import XMonad.Hooks.UrgencyHook (readUrgents)
import XMonad.Hooks.WorkspaceHistory import XMonad.Hooks.WorkspaceHistory
@ -237,23 +254,23 @@ infix >*>
-- | 'Topic' is just an alias for 'WorkspaceId' -- | 'Topic' is just an alias for 'WorkspaceId'
type Topic = WorkspaceId type Topic = WorkspaceId
-- | 'Dir' is just an alias for 'FilePath' but should point to a directory. -- | 'Dir' is just an alias for 'FilePath', but should point to a directory.
type Dir = FilePath type Dir = FilePath
-- | Here is the topic space configuration area. -- | Here is the topic space configuration area.
data TopicConfig = TopicConfig { topicDirs :: M.Map Topic Dir data TopicConfig = TopicConfig { topicDirs :: M.Map Topic Dir
-- ^ This mapping associate a directory to each topic. -- ^ This mapping associates a directory to each topic.
, topicActions :: M.Map Topic (X ()) , topicActions :: M.Map Topic (X ())
-- ^ This mapping associate an action to trigger when -- ^ This mapping associates an action to trigger when
-- switching to a given topic which workspace is empty. -- switching to a given topic which workspace is empty.
, defaultTopicAction :: Topic -> X () , defaultTopicAction :: Topic -> X ()
-- ^ This is the default topic action. -- ^ This is the default topic action.
, defaultTopic :: Topic , defaultTopic :: Topic
-- ^ This is the default (= fallback) topic. -- ^ This is the default (= fallback) topic.
, maxTopicHistory :: Int , maxTopicHistory :: Int
-- ^ This setups the maximum depth of topic history, usually -- ^ This specifies the maximum depth of the topic history;
-- 10 is a good default since we can bind all of them using -- usually 10 is a good default since we can bind all of
-- numeric keypad. -- them using numeric keypad.
} }
instance Default TopicConfig where instance Default TopicConfig where
@ -265,9 +282,13 @@ instance Default TopicConfig where
} }
-- | Return the (possibly empty) list of last focused topics. -- | Return the (possibly empty) list of last focused topics.
getLastFocusedTopics :: X [WorkspaceId] getLastFocusedTopics :: X [Topic]
getLastFocusedTopics = workspaceHistory getLastFocusedTopics = workspaceHistory
-- | Like 'getLastFocusedTopics', but group the topics by their screen-id's.
getLastFocusedTopicsByScreen :: X [(ScreenId, [Topic])]
getLastFocusedTopicsByScreen = workspaceHistoryByScreen
-- | Given a 'TopicConfig', a topic, and a predicate to select topics that one -- | 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 -- wants to keep, this function will cons the topic in front of the list of
-- last focused topics and filter it according to the predicate. Note that we -- last focused topics and filter it according to the predicate. Note that we
@ -340,6 +361,24 @@ switchNthLastFocusedExclude excludes tc depth = do
lastWs <- filter (`notElem` excludes) <$> getLastFocusedTopics lastWs <- filter (`notElem` excludes) <$> getLastFocusedTopics
switchTopic tc $ (lastWs ++ repeat (defaultTopic tc)) !! depth switchTopic tc $ (lastWs ++ repeat (defaultTopic tc)) !! depth
-- | Like 'switchNthLastFocused', but only consider topics that used to
-- be on the current screen.
--
-- For example, the following function allows one to toggle between the
-- currently focused and the last used topic, while treating different
-- screens completely independently from one another.
--
-- > toggleTopicScreen = switchNthLastFocusedByScreen myTopicConfig 1
switchNthLastFocusedByScreen :: TopicConfig -> Int -> X ()
switchNthLastFocusedByScreen tc depth = do
sid <- gets $ W.screen . W.current . windowset
sws <- fromMaybe []
. listToMaybe
. map snd
. filter ((== sid) . fst)
<$> getLastFocusedTopicsByScreen
switchTopic tc $ (sws ++ repeat (defaultTopic tc)) !! depth
-- | Shift the focused window to the Nth last focused topic, or fall back to doing nothing. -- | Shift the focused window to the Nth last focused topic, or fall back to doing nothing.
shiftNthLastFocused :: Int -> X () shiftNthLastFocused :: Int -> X ()
shiftNthLastFocused n = do shiftNthLastFocused n = do
@ -348,7 +387,7 @@ shiftNthLastFocused n = do
-- | Return the directory associated with the current topic, or return the empty -- | Return the directory associated with the current topic, or return the empty
-- string if the topic could not be found. -- string if the topic could not be found.
currentTopicDir :: TopicConfig -> X String currentTopicDir :: TopicConfig -> X FilePath
currentTopicDir tg = do currentTopicDir tg = do
topic <- gets (W.tag . W.workspace . W.current . windowset) topic <- gets (W.tag . W.workspace . W.current . windowset)
return . fromMaybe "" . M.lookup topic $ topicDirs tg return . fromMaybe "" . M.lookup topic $ topicDirs tg