2011-02-25 19:44:32 +01:00
|
|
|
{-# LANGUAGE DeriveDataTypeable, TypeSynonymInstances, MultiParamTypeClasses, PatternGuards #-}
|
|
|
|
|
|
|
|
module ProcessWorkspaces ( setProcessWorkspace
|
|
|
|
, getProcessWorkspace
|
|
|
|
, moveWindowHook
|
|
|
|
, processWorkspaceStorage
|
|
|
|
, spawnOn
|
|
|
|
, spawnOnCurrent
|
|
|
|
) where
|
|
|
|
|
|
|
|
import XMonad hiding (moveWindow)
|
|
|
|
import qualified XMonad.StackSet as W
|
|
|
|
|
|
|
|
import XMonad.Layout.LayoutModifier (LayoutModifier(..), ModifiedLayout(..))
|
|
|
|
import XMonad.Hooks.ManageHelpers (pid)
|
|
|
|
import Graphics.X11.Types (Window)
|
|
|
|
|
|
|
|
import System.Posix.Process (getProcessPriority)
|
|
|
|
import System.Posix.Types (ProcessID)
|
|
|
|
|
|
|
|
import Control.Monad
|
|
|
|
import Data.Maybe
|
|
|
|
import Data.Monoid
|
|
|
|
import qualified Data.Map as M
|
|
|
|
|
|
|
|
import Storage
|
|
|
|
|
|
|
|
|
|
|
|
moveWindowHook :: ManageHook
|
|
|
|
moveWindowHook = do
|
|
|
|
mp <- pid
|
|
|
|
case mp of
|
|
|
|
Just p -> do
|
|
|
|
mws <- liftX $ getProcessWorkspace p
|
|
|
|
case mws of
|
2011-02-25 21:11:04 +01:00
|
|
|
Just ws ->
|
2011-02-25 19:44:32 +01:00
|
|
|
doShift ws
|
|
|
|
_ ->
|
|
|
|
idHook
|
|
|
|
_ ->
|
|
|
|
idHook
|
|
|
|
|
|
|
|
|
|
|
|
data ProcessWorkspaceStoreData = ProcessWorkspaceStoreData (M.Map ProcessID WorkspaceId)
|
|
|
|
deriving (Typeable, Show, Read)
|
|
|
|
instance StoreData ProcessWorkspaceStoreData
|
|
|
|
|
|
|
|
processWorkspaceStorage :: (LayoutClass l a) => l a -> ModifiedLayout (Storage ProcessWorkspaceStoreData) l a
|
|
|
|
processWorkspaceStorage = storage $ ProcessWorkspaceStoreData M.empty
|
|
|
|
|
|
|
|
setProcessWorkspace :: ProcessID -> WorkspaceId -> X ()
|
|
|
|
setProcessWorkspace pid ws = do
|
|
|
|
ProcessWorkspaceStoreData map <- liftM (fromMaybe $ ProcessWorkspaceStoreData M.empty) $ getStoreData
|
|
|
|
map' <- filterPIDMap $ M.insert pid ws map
|
|
|
|
setStoreData $ ProcessWorkspaceStoreData map'
|
|
|
|
|
|
|
|
getProcessWorkspace :: ProcessID -> X (Maybe WorkspaceId)
|
|
|
|
getProcessWorkspace pid = getStoreData >>= return . join . fmap (\(ProcessWorkspaceStoreData map) -> M.lookup pid map)
|
|
|
|
|
|
|
|
|
|
|
|
spawnOn :: WorkspaceId -> String -> X ()
|
|
|
|
spawnOn ws x = do
|
|
|
|
pid <- spawnPID x
|
|
|
|
setProcessWorkspace pid ws
|
|
|
|
|
|
|
|
spawnOnCurrent :: String -> X ()
|
|
|
|
spawnOnCurrent x = gets (W.currentTag . windowset) >>= \ws -> spawnOn ws x
|
|
|
|
|
|
|
|
|
|
|
|
filterPIDMap :: M.Map ProcessID a -> X (M.Map ProcessID a)
|
|
|
|
filterPIDMap = liftM M.fromAscList . filterM (pidExists . fst) . M.toAscList
|
|
|
|
where
|
|
|
|
pidExists :: ProcessID -> X Bool
|
2011-02-25 21:11:04 +01:00
|
|
|
pidExists pid = io $ ((getProcessPriority pid) >> return True) `catch` (\_ -> return False)
|