xmonad-contrib-0.18.0.9: Community-maintained extensions for xmonad
Copyright(c) Mislav Zanic
LicenseBSD3-style (see LICENSE)
MaintainerMislav Zanic <mislavzanic3@gmail.com>
Stabilityexperimental
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Actions.Profiles

Description

 
Synopsis

Overview

This module allows you to group your workspaces into Profiles based on certain similarities. The idea is to expand upon the philosophy set by XMonad.Actions.TopicSpace which states that you can look at a topic/workspace as a single unit of work instead of multiple related units of work. This comes in handy if you have lots of workspaces with windows open and need only to work with a few of them at a time. With Profiles, you can focus on those few workspaces that require your attention by not displaying, or allowing you to switch to the rest of the workspaces. The best example is having a profile for development and a profile for leisure activities.

Usage

To use Profiles you need to add it to your XMonad configuration and configure your profiles.

First you'll need to handle the imports.

import XMonad.Actions.Profiles 
import XMonad.Util.EZConfig -- for keybindings
import qualified XMonad.StackSet as W
import qualified XMonad.Actions.DynamicWorkspaceOrder as DO -- for workspace navigation

Next you'll need to define your profiles.

myStartingProfile :: ProfileId
myStartingProfile = "Work"

myProfiles :: [Profile]
myProfiles =
 [ Profile { profileId = "Home"
           , profileWS = [ "www"
                         , "rss"
                         , "vid"
                         , "vms"
                         , "writing"
                         , "notes"
                         ]
           }
 , Profile { profileId = "Work"
           , profileWS = [ "www"
                         , "slack"
                         , "dev"
                         , "k8s"
                         , "notes"
                         ]
           }
 ]

So, while using Home Profile, you'll only be able to see, navigate to and do actions with ["www", "rss", "vid", "vms", "writing", "notes"] workspaces.

You may also need to define some keybindings. Since M-1 .. M-9 are sensible keybindings for switching workspaces, you'll need to use bindOn to have different keybindings per profile. Here, we'll use XMonad.Util.EZConfig syntax:

myKeys :: [(String, X())]
myKeys = 
  [ ("M-p",  switchProfilePrompt   xpConfig)
  , ("M-g",  switchProfileWSPrompt xpConfig)
  , ("M1-j", DO.moveTo Next wsFilter)
  , ("M1-k", DO.moveTo Prev wsFilter)
  ]
  <>
  [ ("M-" ++ m ++ k, bindOn $ map (\x -> (fst x, f $ snd x)) i)
  | (i, k) <- map (\(x:xs) -> (map fst (x:xs), snd x)) $ sortGroupBy snd tupleList
  , (f, m) <- [(mby $ windows . W.greedyView, ""), (mby $ windows . W.shift, "S-")]
  ]
  where
    mby f wid = if wid == "" then return () else f wid
    sortGroupBy f = groupBy (\ x y -> f x == f y) . sortBy (\x y -> compare (f x) (f y))
    tupleList = concatMap (\p -> zip (map (\wid -> (profileId p, wid)) (profileWS p <> repeat "")) (map show [1..9 :: Int])) myProfiles

After that, you'll need to hook Profiles into your XMonad config:

main = xmonad $ addProfiles def { profiles        = myProfiles
                                , startingProfile = myStartingProfile
                                }
              $ def `additionalKeysP` myKeys

Types

data Profile Source #

Profile representation.

Constructors

Profile 

Fields

data ProfileConfig Source #

User config for profiles.

Constructors

ProfileConfig 

Fields

Instances

Instances details
Default ProfileConfig Source # 
Instance details

Defined in XMonad.Actions.Profiles

Methods

def :: ProfileConfig #

Hooks

addProfiles :: ProfileConfig -> XConfig a -> XConfig a Source #

Hook profiles into XMonad. This function adds a startup hook that sets up ProfileState. Also adds an afterRescreenHook for viewing correct workspaces when adding new screens.

addProfilesWithHistory :: ProfileConfig -> XConfig a -> XConfig a Source #

Hooks profiles into XMonad and enables Profile history logging.

Switching profiles

switchToProfile :: ProfileId -> X () Source #

Switch to a profile.

Workspace navigation and keybindings

wsFilter :: WSType Source #

For cycling through workspaces associated with the current.

bindOn :: [(String, X ())] -> X () Source #

Create keybindings per profile.

Loggers and pretty printers

excludeWSPP :: PP -> X PP Source #

Pretty printer for a bar. Prints workspace ids of current profile.

profileLogger :: (String -> String) -> (String -> String) -> Logger Source #

Loggs currentProfile and all profiles with hidden workspaces (workspaces that aren't shown on a screen but have windows).

Prompts

switchProfilePrompt :: XPConfig -> X () Source #

Prompt for switching profiles.

addWSToProfilePrompt :: XPConfig -> X () Source #

Prompt for adding a workspace id to a profile.

removeWSFromProfilePrompt :: XPConfig -> X () Source #

Prompt for removing a workspace from a profile.

switchProfileWSPrompt :: XPConfig -> X () Source #

Prompt for switching workspaces.

shiftProfileWSPrompt :: XPConfig -> X () Source #

Prompt for shifting windows to a different workspace.

Utilities

currentProfile :: X ProfileId Source #

Returns current profile.

profileIds :: X [ProfileId] Source #

Returns ids of all profiles.

previousProfile :: X (Maybe ProfileId) Source #

Returns previous profile.

profileHistory :: X (Map ProfileId [(ScreenId, WorkspaceId)]) Source #

Returns the history of viewed workspaces per profile.

allProfileWindows :: XWindowMap Source #

XWindowMap of all windows contained in a profile.

profileWorkspaces :: ProfileId -> X [WorkspaceId] Source #

Returns the workspace ids associated with a profile id.