xmonad-contrib-0.11.2: Third party extensions for xmonad

Portabilityunportable
Stabilityunstable
MaintainerNicolas Pouillard <nicolas.pouillard@gmail.com>
Safe HaskellNone

XMonad.Actions.TopicSpace

Contents

Description

Turns your workspaces into a more topic oriented system.

Synopsis

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.

Usage

Here is an example of configuration using TopicSpace:

 -- The list of all topics/workspaces of your xmonad configuration.
 -- The order is important, new topics must be inserted
 -- at the end of the list if you want hot-restarting
 -- to work.
 myTopics :: [Topic]
 myTopics =
   [ "dashboard" -- the first one
   , "admin", "build", "cleaning", "conf", "darcs", "haskell", "irc"
   , "mail", "movie", "music", "talk", "text", "tools", "web", "xmonad"
   , "yi", "documents", "twitter", "pdf"
   ]

 myTopicConfig :: TopicConfig
 myTopicConfig = defaultTopicConfig
   { topicDirs = M.fromList $
       [ ("conf", "w/conf")
       , ("dashboard", "Desktop")
       , ("yi", "w/dev-haskell/yi")
       , ("darcs", "w/dev-haskell/darcs")
       , ("haskell", "w/dev-haskell")
       , ("xmonad", "w/dev-haskell/xmonad")
       , ("tools", "w/tools")
       , ("movie", "Movies")
       , ("talk", "w/talks")
       , ("music", "Music")
       , ("documents", "w/documents")
       , ("pdf", "w/documents")
       ]
   , defaultTopicAction = const $ spawnShell >*> 3
   , defaultTopic = "dashboard"
   , topicActions = M.fromList $
       [ ("conf",       spawnShell >> spawnShellIn "wd/ertai/private")
       , ("darcs",      spawnShell >*> 3)
       , ("yi",         spawnShell >*> 3)
       , ("haskell",    spawnShell >*> 2 >>
                        spawnShellIn "wd/dev-haskell/ghc")
       , ("xmonad",     spawnShellIn "wd/x11-wm/xmonad" >>
                        spawnShellIn "wd/x11-wm/xmonad/contrib" >>
                        spawnShellIn "wd/x11-wm/xmonad/utils" >>
                        spawnShellIn ".xmonad" >>
                        spawnShellIn ".xmonad")
       , ("mail",       mailAction)
       , ("irc",        ssh somewhere)
       , ("admin",      ssh somewhere >>
                        ssh nowhere)
       , ("dashboard",  spawnShell)
       , ("twitter",    spawnShell)
       , ("web",        spawn browserCmd)
       , ("movie",      spawnShell)
       , ("documents",  spawnShell >*> 2 >>
                        spawnShellIn "Documents" >*> 2)
       , ("pdf",        spawn pdfViewerCmd)
       ]
   }

 -- extend your keybindings
 myKeys conf@XConfig{modMask=modm} =
   [ ((modm              , xK_n     ), spawnShell) -- %! Launch terminal
   , ((modm              , xK_a     ), currentTopicAction myTopicConfig)
   , ((modm              , xK_g     ), promptedGoto)
   , ((modm .|. shiftMask, xK_g     ), promptedShift)
   {- more  keys ... -}
   ]
   ++
   [ ((modm, k), switchNthLastFocused myTopicConfig i)
   | (i, k) <- zip [1..] workspaceKeys]

 spawnShell :: X ()
 spawnShell = currentTopicDir myTopicConfig >>= spawnShellIn

 spawnShellIn :: Dir -> X ()
 spawnShellIn dir = spawn $ "urxvt '(cd ''" ++ dir ++ "'' && " ++ myShell ++ " )'"

 goto :: Topic -> X ()
 goto = switchTopic myTopicConfig

 promptedGoto :: X ()
 promptedGoto = workspacePrompt myXPConfig goto

 promptedShift :: X ()
 promptedShift = workspacePrompt myXPConfig $ windows . W.shift

 myConfig = do
     checkTopicConfig myTopics myTopicConfig
     myLogHook <- makeMyLogHook
     return $ defaultConfig
          { borderWidth = 1 -- Width of the window border in pixels.
          , workspaces = myTopics
          , layoutHook = myModifiers myLayout
          , manageHook = myManageHook
          , logHook = myLogHook
          , handleEventHook = myHandleEventHook
          , terminal = myTerminal -- The preferred terminal program.
          , normalBorderColor = "#3f3c6d"
          , focusedBorderColor = "#4f66ff"
          , XMonad.modMask = mod1Mask
          , keys = myKeys
          , mouseBindings = myMouseBindings
          }

 main :: IO ()
 main = xmonad =<< myConfig

type Topic = WorkspaceIdSource

Topic is just an alias for WorkspaceId

type Dir = FilePathSource

Dir is just an alias for FilePath but should points to a directory.

data TopicConfig Source

Here is the topic space configuration area.

Constructors

TopicConfig 

Fields

topicDirs :: Map Topic Dir

This mapping associate a directory to each topic.

topicActions :: Map Topic (X ())

This mapping associate an action to trigger when switching to a given topic which workspace is empty.

defaultTopicAction :: Topic -> X ()

This is the default topic action.

defaultTopic :: Topic

This is the default topic.

maxTopicHistory :: Int

This setups the maximum depth of topic history, usually 10 is a good default since we can bind all of them using numeric keypad.

getLastFocusedTopics :: X [String]Source

Returns the list of last focused workspaces the empty list otherwise.

setLastFocusedTopic :: Topic -> (Topic -> Bool) -> X ()Source

Given a TopicConfig, the last focused topic, and a predicate that will select topics that one want to keep, this function will set the property of last focused topics.

pprWindowSet :: TopicConfig -> PP -> X StringSource

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 highlighting topics with urgent windows.

topicActionWithPrompt :: XPConfig -> TopicConfig -> X ()Source

Given a prompt configuration and a topic configuration, triggers the action associated with the topic given in prompt.

topicAction :: TopicConfig -> Topic -> X ()Source

Given a configuration and a topic, triggers the action associated with the given topic.

currentTopicAction :: TopicConfig -> X ()Source

Trigger the action associated with the current topic.

switchTopic :: TopicConfig -> Topic -> X ()Source

Switch to the given topic.

switchNthLastFocused :: TopicConfig -> Int -> X ()Source

Switch to the Nth last focused topic or failback to the defaultTopic.

shiftNthLastFocused :: Int -> X ()Source

Shift the focused window to the Nth last focused topic, or fallback to doing nothing.

currentTopicDir :: TopicConfig -> X StringSource

Returns the directory associated with current topic returns the empty string otherwise.

checkTopicConfig :: [Topic] -> TopicConfig -> IO ()Source

Check the given topic configuration for duplicates topics or undefined topics.

(>*>) :: Monad m => m a -> Int -> m ()Source

An alias for flip replicateM_