{-# LANGUAGE DeriveDataTypeable #-}
module XMonad.Actions.LinkWorkspaces (
switchWS,
removeAllMatchings,
unMatch,
toggleLinkWorkspaces,
defaultMessageConf,
MessageConfig(..)
) where
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Layout.IndependentScreens(countScreens)
import qualified XMonad.Util.ExtensibleState as XS (get, put)
import XMonad.Actions.OnScreen(Focus(FocusCurrent), onScreen')
import qualified Data.Map as M
( insert, delete, Map, lookup, empty, filter )
data MessageConfig = MessageConfig { messageFunction :: (ScreenId -> [Char] -> [Char] -> [Char] -> X())
, foreground :: [Char]
, alertedForeground :: [Char]
, background :: [Char]
}
defaultMessageConf :: MessageConfig
defaultMessageConf = MessageConfig { messageFunction = noMessageFn
, background = "#000000"
, alertedForeground = "#ff7701"
, foreground = "#00ff00" }
noMessageFn :: ScreenId -> [Char] -> [Char] -> [Char] -> X()
noMessageFn _ _ _ _ = return () :: X ()
data WorkspaceMap = WorkspaceMap (M.Map WorkspaceId WorkspaceId) deriving (Read, Show, Typeable)
instance ExtensionClass WorkspaceMap
where initialValue = WorkspaceMap M.empty
extensionType = PersistentExtension
switchWS :: (WorkspaceId -> X ()) -> MessageConfig -> WorkspaceId -> X ()
switchWS f m ws = switchWS' f m ws Nothing
switchWS' :: (WorkspaceId -> X ()) -> MessageConfig -> WorkspaceId -> (Maybe ScreenId) -> X ()
switchWS' switchFn message workspace stopAtScreen = do
ws <- gets windowset
nScreens <- countScreens
let now = W.screen (W.current ws)
let next = ((now + 1) `mod` nScreens)
switchFn workspace
case stopAtScreen of
Nothing -> sTM now next (Just now)
Just sId -> if sId == next then return () else sTM now next (Just sId)
where sTM = switchToMatching (switchWS' switchFn message) message workspace
switchToMatching :: (WorkspaceId -> (Maybe ScreenId) -> X ()) -> MessageConfig -> WorkspaceId -> ScreenId
-> ScreenId -> (Maybe ScreenId) -> X ()
switchToMatching f message t now next stopAtScreen = do
WorkspaceMap matchings <- XS.get :: X WorkspaceMap
case (M.lookup t matchings) of
Nothing -> return () :: X()
Just newWorkspace -> do
onScreen' (f newWorkspace stopAtScreen) FocusCurrent next
messageFunction message now (foreground message) (background message) ("Switching to: " ++ (t ++ " and " ++ newWorkspace))
toggleMatching :: MessageConfig -> WorkspaceId -> WorkspaceId -> X ()
toggleMatching message t1 t2 = do
WorkspaceMap matchings <- XS.get :: X WorkspaceMap
case (M.lookup t1 matchings) of
Nothing -> setMatching message t1 t2 matchings
Just t -> if t == t2 then removeMatching' message t1 t2 matchings else setMatching message t1 t2 matchings
return ()
setMatching :: MessageConfig -> WorkspaceId -> WorkspaceId -> M.Map WorkspaceId WorkspaceId -> X ()
setMatching message t1 t2 matchings = do
ws <- gets windowset
let now = W.screen (W.current ws)
XS.put $ WorkspaceMap $ M.insert t1 t2 matchings
messageFunction message now (foreground message) (background message) ("Linked: " ++ (t1 ++ " " ++ t2))
removeMatching' :: MessageConfig -> WorkspaceId -> WorkspaceId -> M.Map WorkspaceId WorkspaceId -> X ()
removeMatching' message t1 t2 matchings = do
ws <- gets windowset
let now = W.screen (W.current ws)
XS.put $ WorkspaceMap $ M.delete t1 matchings
messageFunction message now (alertedForeground message) (background message) ("Unlinked: " ++ t1 ++ " " ++ t2)
removeAllMatchings :: MessageConfig -> X ()
removeAllMatchings message = do
ws <- gets windowset
let now = W.screen (W.current ws)
XS.put $ WorkspaceMap $ M.empty
messageFunction message now (alertedForeground message) (background message) "All links removed!"
unMatch :: WorkspaceId -> X ()
unMatch workspace = do
WorkspaceMap matchings <- XS.get :: X WorkspaceMap
XS.put $ WorkspaceMap $ M.delete workspace (M.filter (/= workspace) matchings)
toggleLinkWorkspaces :: MessageConfig -> X ()
toggleLinkWorkspaces message = withWindowSet $ \ws -> toggleLinkWorkspaces' (W.screen (W.current ws)) message
toggleLinkWorkspaces' :: ScreenId -> MessageConfig -> X ()
toggleLinkWorkspaces' first message = do
ws <- gets windowset
nScreens <- countScreens
let now = W.screen (W.current ws)
let next = (now + 1) `mod` nScreens
if next == first then return () else do
case (W.lookupWorkspace next ws) of
Nothing -> return ()
Just name -> toggleMatching message (W.currentTag ws) (name)
onScreen' (toggleLinkWorkspaces' first message) FocusCurrent next