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

Status: New Owner: ---- New issue 347 by quesel: Feature request: Adding new Topics as you go http://code.google.com/p/xmonad/issues/detail?id=347 Hi, it would be a nice feature if one would be able to add new topics on the fly. I have a static config containing lots of topics, but sometimes I have a task that requires a new topic and I dont want to add it to my config but just add it temporarily. Therefore, it would be nice, if there was a way to easily combine X.A.TopicSpaces with X.A.DynamicWorkspaces and X.Prompt. Something like a keybind that pops-up two prompts, one for the topic name and one for the action and then creates this new topic, and one for deleting topics... Best Regards, Jan -- You received this message because you are listed in the owner or CC fields of this issue, or because you starred this issue. You may adjust your issue notification preferences at: http://code.google.com/hosting/settings

Updates: Status: Accepted Labels: Type-Enhancement Component-Contrib Comment #1 on issue 347 by byorgey: Feature request: Adding new Topics as you go http://code.google.com/p/xmonad/issues/detail?id=347 Of course, it will not work to just type in any expression to be executed, since Haskell doesn't have an 'eval' function (for good reason), but we should be able to use the XMonad.Actions.Commands module somehow. This is a feature I'd like as well, so I'll plan to implement it eventually if no one else does it first. -- You received this message because you are listed in the owner or CC fields of this issue, or because you starred this issue. You may adjust your issue notification preferences at: http://code.google.com/hosting/settings

Comment #2 on issue 347 by daniel.wagner: Feature request: Adding new Topics as you go http://code.google.com/p/xmonad/issues/detail?id=347
Haskell doesn't have an 'eval' function
Well, xmonad-extras does have XMonad.Actions.Eval and XMonad.Prompt.Eval, so if 'eval' would be helpful in implementing this, you might want to check those out. -- You received this message because you are listed in the owner or CC fields of this issue, or because you starred this issue. You may adjust your issue notification preferences at: http://code.google.com/hosting/settings

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.

Comment #4 on issue 347 by loupgaroublond: Feature request: Adding new Topics as you go http://code.google.com/p/xmonad/issues/detail?id=347 'lo, I've worked out a similar solution, let me show you some code: -- Workspaces _spaces = M.fromList $ [ ("schutbord", "~") , ("browsen", "~") , ("praten", "~") , ("muziek", "~/Muziek") , ("berichten", "~/Mail") , ("agenda", "~/Documenten/Day Planner") , ("ldap", "~") , ("flim", "~") , ("terminals", "~") ] _workspaces = [ "schutbord"] _topicConfig = TS.TopicConfig { TS.topicDirs = _spaces , TS.topicActions = _topicActions , TS.defaultTopicAction = (const $ return ()) , TS.defaultTopic = "schutbord" , TS.maxTopicHistory = 10 } _topicActions = M.fromList $ [ ("schutbord", replicateM_ 2 runColourTerminal) , ("terminals", replicateM_ 2 runColourTerminal) , ("browsen", runBrowser) , ("praten", runChat) , ("berichten", runMail) , ("muziek", runMixer >> runMusicPlayer) , ("transmission", runTorrent) , ("agenda", runEditor) , ("flim", runFilm) ] goto :: TS.Topic -> X () goto t = newWorkspace t >> TS.switchTopic _topicConfig t shift = windows . W.shift newWorkspace :: WorkspaceId -> X () newWorkspace w = do exists <- widExist w if (not exists) then DW.addHiddenWorkspace w else return () newWorkspaceDir :: WorkspaceId -> X () newWorkspaceDir w = do exists <- widExist w if (not exists) then do DW.addHiddenWorkspace w goto w WD.changeDir P.defaultXPConfig else return () widExist :: WorkspaceId -> X Bool widExist wid = do xs <- get return $ widExists wid ( windowset xs ) widExists :: WorkspaceId -> W.StackSet WorkspaceId l a s sd -> Bool widExists wid ws = wid `elem` map W.tag (W.workspaces ws) I also have these key bindings (with ezconfig) , ("M-S-n", PI.inputPrompt P.defaultXPConfig "New Workspace:" PI.?+ newWorkspaceDir) , ("M-S-<Backspace>", WithAll.killAll >> DW.removeWorkspace) , ("M-S-r", DW.renameWorkspace P.defaultXPConfig) [ -- Applications ("M-t", goto "terminals") , ("M-S-t", runColourTerminal) , ("M-v M-t", pasteTerminal) , ("M-v M-d", manTerminal) , ("M-i", goto "browsen") , ("M-S-i", runBrowser) , ("M-v M-i", pasteBrowser) , ("M-p", runCmdLine) , ("M-x", WD.changeDir P.defaultXPConfig) , ("M-e", goto "muziek") -- , ("M-o", runMixer) , ("M-h", runFileManager) , ("M-s", goto "praten") , ("M-m", goto "berichten") , ("M-S-m", runMail) , ("M-u", goto "agenda") , ("M-0", goto "schutbord") , ("M-w", goto "flim")
participants (1)
-
codesite-noreply@google.com