Copyright | (c) Nicolas Pouillard |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Nicolas Pouillard <nicolas.pouillard@gmail.com> |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Turns your workspaces into a more topic oriented system.
Synopsis
- type Topic = WorkspaceId
- type Dir = FilePath
- data TopicConfig = TopicConfig {
- topicDirs :: Map Topic Dir
- topicActions :: Map Topic (X ())
- defaultTopicAction :: Topic -> X ()
- defaultTopic :: Topic
- maxTopicHistory :: Int
- data TopicItem = TI {}
- topicNames :: [TopicItem] -> [Topic]
- tiActions :: [TopicItem] -> Map Topic (X ())
- tiDirs :: [TopicItem] -> Map Topic Dir
- noAction :: Topic -> Dir -> TopicItem
- inHome :: Topic -> X () -> TopicItem
- switchTopic :: TopicConfig -> Topic -> X ()
- switchNthLastFocused :: TopicConfig -> Int -> X ()
- switchNthLastFocusedByScreen :: TopicConfig -> Int -> X ()
- switchNthLastFocusedExclude :: [Topic] -> TopicConfig -> Int -> X ()
- shiftNthLastFocused :: Int -> X ()
- topicActionWithPrompt :: XPConfig -> TopicConfig -> X ()
- topicAction :: TopicConfig -> Topic -> X ()
- currentTopicAction :: TopicConfig -> X ()
- getLastFocusedTopics :: X [Topic]
- workspaceHistory :: X [WorkspaceId]
- workspaceHistoryByScreen :: X [(ScreenId, [WorkspaceId])]
- setLastFocusedTopic :: TopicConfig -> Topic -> (Topic -> Bool) -> X ()
- reverseLastFocusedTopics :: X ()
- workspaceHistoryHook :: X ()
- workspaceHistoryHookExclude :: [WorkspaceId] -> X ()
- pprWindowSet :: TopicConfig -> PP -> X String
- currentTopicDir :: TopicConfig -> X FilePath
- checkTopicConfig :: [Topic] -> TopicConfig -> IO ()
- (>*>) :: Monad m => m a -> Int -> m ()
Overview
This module allows to organize your workspaces on a precise topic basis. So
instead of having a workspace called work
you can setup one workspace per
task. Here we call these workspaces, topics. The great thing with
topics is that one can attach a directory that makes sense to each
particular topic. One can also attach an action which will be triggered
when switching to a topic that does not have any windows in it. So you can
attach your mail client to the mail topic, some terminals in the right
directory to the xmonad topic... This package also provides a nice way to
display your topics in an historical way using a custom pprWindowSet
function. You can also easily switch to recent topics using this history
of last focused topics.
A blog post highlighting some features of this module can be found here.
Usage
You can use this module with the following in your xmonad.hs
:
import qualified Data.Map.Strict as M import qualified XMonad.StackSet as W import XMonad.Actions.TopicSpace import XMonad.Util.EZConfig -- for the keybindings import XMonad.Prompt.Workspace -- if you want to use the prompt
You will then have to
- Define a new
TopicConfig
viaTopicItem
s - Add the appropriate keybindings
- Replace the
workspaces
field in yourXConfig
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 yourlogHook
. See the documentation of XMonad.Hooks.WorkspaceHistory for further details
Let us go through a full example together.
A TopicItem
consists of three things: the name of the topic, its
root directory, and the action associated to it—to be executed if the
topic is empty or the action is forced via a keybinding.
We start by specifying our chosen topics as a list of such
TopicItem
s:
topicItems :: [TopicItem] topicItems = [ inHome "1:WEB" (spawn "firefox") , noAction "2" "." , noAction "3:VID" "videos" , TI "4:VPN" "openvpn" (spawn "urxvt -e randomVPN.sh") , inHome "5:IM" (spawn "signal" *> spawn "telegram") , inHome "6:IRC" (spawn "urxvt -e weechat") , TI "dts" ".dotfiles" spawnShell , TI "xm-con" "hs/xm-con" (spawnShell *> spawnShellIn "hs/xm") ]
Then we just need to put together our topic config:
myTopicConfig :: TopicConfig myTopicConfig = def { topicDirs = tiDirs topicItems , topicActions = tiActions topicItems , defaultTopicAction = const (pure ()) -- by default, do nothing , defaultTopic = "1:WEB" -- fallback }
Above, we have used the spawnShell
and spawnShellIn
helper
functions; here they are:
spawnShell :: X () spawnShell = currentTopicDir myTopicConfig >>= spawnShellIn spawnShellIn :: Dir -> X () spawnShellIn dir = spawn $ "alacritty --working-directory " ++ dir
Next, we define some other other useful helper functions. It is
rather common to have a lot of topics—much more than available keys!
In a situation like that, it's very convenient to switch topics with
a prompt; the following use of workspacePrompt
does exactly that.
goto :: Topic -> X () goto = switchTopic myTopicConfig promptedGoto :: X () promptedGoto = workspacePrompt def goto promptedShift :: X () promptedShift = workspacePrompt def $ windows . W.shift -- Toggle between the two most recently used topics, but keep -- screens separate. This needs @workspaceHistoryHook@. toggleTopic :: X () toggleTopic = switchNthLastFocusedByScreen myTopicConfig 1
Hopefully you've gotten a general feeling of how to define these kind of small helper functions using what's provided in this module.
Adding the appropriate keybindings works as it normally would. Here, we'll use XMonad.Util.EZConfig syntax:
myKeys :: [(String, X ())] myKeys = [ ("M-n" , spawnShell) , ("M-a" , currentTopicAction myTopicConfig) , ("M-g" , promptedGoto) , ("M-S-g" , promptedShift) , ("M-S-<Space>", toggleTopic) ] ++ -- The following does two things: -- 1. Switch topics (no modifier) -- 2. Move focused window to topic N (shift modifier) [ ("M-" ++ m ++ k, f i) | (i, k) <- zip (topicNames topicItems) (map show [1 .. 9 :: Int]) , (f, m) <- [(goto, ""), (windows . W.shift, "S-")] ]
This makes M-1
to M-9
switch to the first nine topics that we
have specified in topicItems
.
You can also switch to the nine last-used topics instead:
[ ("M-" ++ show i, switchNthLastFocused myTopicConfig i) | i <- [1 .. 9] ]
We can now put the whole configuration together with the following:
main :: IO () main = xmonad $ def { workspaces = topicNames topicItems } `additionalKeysP` myKeys
Types for Building Topics
type Topic = WorkspaceId Source #
Topic
is just an alias for WorkspaceId
data TopicConfig Source #
Here is the topic space configuration area.
TopicConfig | |
|
Instances
Default TopicConfig Source # | |
Defined in XMonad.Actions.TopicSpace def :: TopicConfig # |
Convenience type for specifying topics.
Managing TopicItem
s
tiActions :: [TopicItem] -> Map Topic (X ()) Source #
From a list of TopicItem
s, build a map that can be supplied as
the topicActions
.
noAction :: Topic -> Dir -> TopicItem Source #
Associate a directory with the topic, but don't spawn anything.
Switching and Shifting Topics
switchTopic :: TopicConfig -> Topic -> X () Source #
Switch to the given topic.
switchNthLastFocused :: TopicConfig -> Int -> X () Source #
Switch to the Nth last focused topic or fall back to the defaultTopic
.
switchNthLastFocusedByScreen :: TopicConfig -> Int -> X () Source #
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
switchNthLastFocusedExclude :: [Topic] -> TopicConfig -> Int -> X () Source #
Like switchNthLastFocused
, but also filter out certain topics.
shiftNthLastFocused :: Int -> X () Source #
Shift the focused window to the Nth last focused topic, or fall back to doing nothing.
Topic Actions
topicActionWithPrompt :: XPConfig -> TopicConfig -> X () Source #
Given a prompt configuration and a topic configuration, trigger the action associated with the topic given in prompt.
topicAction :: TopicConfig -> Topic -> X () Source #
Given a configuration and a topic, trigger the action associated with the given topic.
currentTopicAction :: TopicConfig -> X () Source #
Trigger the action associated with the current topic.
Getting the Topic History
getLastFocusedTopics :: X [Topic] Source #
Deprecated: Use XMonad.Hooks.WorkspaceHistory.workspaceHistory (re-exported by this module) instead
Return the (possibly empty) list of last focused topics.
workspaceHistory :: X [WorkspaceId] Source #
A list of workspace tags in the order they have been viewed, with the most recent first. No duplicates are present, but not all workspaces are guaranteed to appear, and there may be workspaces that no longer exist.
workspaceHistoryByScreen :: X [(ScreenId, [WorkspaceId])] Source #
Modifying the Topic History
setLastFocusedTopic :: TopicConfig -> Topic -> (Topic -> Bool) -> X () Source #
Deprecated: Use XMonad.Hooks.WorkspaceHistory 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
last focused topics and filter it according to the predicate. Note that we
prune the list in case that its length exceeds maxTopicHistory
.
reverseLastFocusedTopics :: X () Source #
Reverse the list of "last focused topics"
History hooks
workspaceHistoryHook :: X () Source #
A logHook
that keeps track of the order in which workspaces have
been viewed.
workspaceHistoryHookExclude :: [WorkspaceId] -> X () Source #
Like workspaceHistoryHook
, but with the ability to exclude
certain workspaces.
Pretty Printing
pprWindowSet :: TopicConfig -> PP -> X String Source #
This function is a variant of pprWindowSet
which takes a topic
configuration and a pretty-printing record PP
. It will show the list of
topics sorted historically and highlight topics with urgent windows.
Utility
currentTopicDir :: TopicConfig -> X FilePath Source #
Return the directory associated with the current topic, or return the empty string if the topic could not be found.
checkTopicConfig :: [Topic] -> TopicConfig -> IO () Source #
Check the given topic configuration for duplicate or undefined topics.