[xmonad] Re: Issue 347 in xmonad: Feature request: Adding new Topics as you go

codesite-noreply at google.com codesite-noreply at google.com
Fri May 21 02:55:18 EDT 2010


Comment #3 on issue 347 by quesel: Feature request: Adding new Topics as  
you go
http://code.google.com/p/xmonad/issues/detail?id=347

Ok I have found a partial solution. Maybe one could extend it using this  
eval function.
For the moment I'm able to spawn new topics which spawn a new shell on the  
fly using
X.A.DynamicWorkspaces and the following set of functions:

-- Constructor for a prompt
data Prom = Prom String
instance XPrompt Prom where
     showXPrompt (Prom x) = x

-- Input a name and create a new workspace with that name
newWS :: X ()
newWS = withWindowSet $ \w -> do
     let wss = W.workspaces w
     mkXPrompt pr myXPConfig (mkComplFunFromList (map W.tag wss))  
newWSWithName
     where pr = Prom "Workspace name: "

-- Create a new workspace with a given name
newWSWithName :: String -> X ()
newWSWithName name = withWindowSet $ \w -> do
   let wss = W.workspaces w
       dname = defname name
       cws = map W.tag $ filter (\ws -> (dname `isPrefixOf` W.tag ws ||  
dname == W.tag
ws) && isJust (W.stack ws)) wss
       num = head $ [0..] \\ catMaybes (map (readMaybe . drop 4) cws)
       usednames = map W.tag wss
       new = dname ++ if (dname `elem` cws) then show num else ""
   when (new `notElem` usednames) $ addWorkspace new
   windows $ W.view new
   spawnShell -- TODO replace this by the freshly entered topic action
  where readMaybe s = case reads s of
                        [(r,_)] -> Just r
                        _       -> Nothing
        defname "" = "temp"
        defname s  = s

-- | Switch to the given topic non greedy.
switchTopicNonGreedy :: TopicConfig -> Topic -> X ()
switchTopicNonGreedy tg topic = removeEmptyWorkspaceAfterExcept myTopicNames
(switchTopicNonGreedy' tg topic)

switchTopicNonGreedy' :: TopicConfig -> Topic -> X ()
switchTopicNonGreedy' tg topic = do
   windows $ W.view topic
   wins <- gets (W.integrate' . W.stack . W.workspace . W.current .  
windowset)
   when (null wins) $ topicAction tg topic

-- | Switch to the Nth last focused topic non greedy or failback to  
the 'defaultTopic'.
switchNthLastFocusedNonGreedy ::TopicConfig -> Int -> X ()
switchNthLastFocusedNonGreedy tg depth = do
   lastWs <- getLastFocusedTopics
   switchTopicNonGreedy tg $ (lastWs ++ repeat (defaultTopic tg)) !! depth

wsgrid = withWindowSet $ \w -> do
     let wss = W.workspaces w
         usednames = map W.tag $  wss
         newnames = filter (\w -> (show w `notElem` (map show  
myTopicNames))) usednames
     gridselect gsConfig (map (\x -> (x,x)) (myTopicNames ++ newnames))

promptedGoto = wsgrid >>= flip whenJust (switchTopicNonGreedy myTopicConfig)


So almost what I wanted to achieve. Maybe this is useful for you as well.



More information about the xmonad mailing list