Allow moving whole processes to other workspaces
This commit is contained in:
parent
0b80dad888
commit
016dc1e4b7
3 changed files with 27 additions and 6 deletions
|
@ -4,6 +4,8 @@ module ProcessWorkspaces ( setProcessWorkspace
|
|||
, getProcessWorkspace
|
||||
, doAutoShift
|
||||
, doIgnoreProcessWorkspace
|
||||
, shiftGroup
|
||||
, shiftWinGroup
|
||||
, processWorkspaceStorage
|
||||
, spawnOn
|
||||
, spawnOnCurrent
|
||||
|
@ -21,7 +23,6 @@ import System.Posix.Types (ProcessID)
|
|||
|
||||
import Control.Monad
|
||||
import Data.Maybe
|
||||
import Data.Monoid
|
||||
import qualified Data.Map as M
|
||||
|
||||
import Storage
|
||||
|
@ -48,6 +49,26 @@ doIgnoreProcessWorkspace = do
|
|||
liftX $ setProcessWorkspace (fromJust mp) Nothing
|
||||
idHook
|
||||
|
||||
shiftGroup :: WorkspaceId -> X ()
|
||||
shiftGroup ws = withFocused $ shiftWinGroup ws
|
||||
|
||||
shiftWinGroup :: WorkspaceId -> Window -> X ()
|
||||
shiftWinGroup ws w = do
|
||||
mp <- runQuery pid w
|
||||
case mp of
|
||||
Just p -> do
|
||||
mws <- getProcessWorkspace p
|
||||
case mws of
|
||||
Just pws -> do
|
||||
setProcessWorkspace p (Just ws)
|
||||
wins <- withWindowSet $ return . W.allWindows
|
||||
windows =<< foldM (\f w' -> runQuery pid w' >>= \mp' -> return $ if (mp' == Just p) then W.shiftWin ws w' . f else f) id wins
|
||||
_ ->
|
||||
windows $ W.shiftWin ws w
|
||||
_ ->
|
||||
windows $ W.shiftWin ws w
|
||||
|
||||
|
||||
data ProcessWorkspaceStoreData = ProcessWorkspaceStoreData (M.Map ProcessID (Maybe WorkspaceId))
|
||||
deriving (Typeable, Show, Read)
|
||||
instance StoreData ProcessWorkspaceStoreData
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
{-# LANGUAGE DeriveDataTypeable, ExistentialQuantification, TypeSynonymInstances, MultiParamTypeClasses, ScopedTypeVariables, FlexibleInstances, PatternGuards #-}
|
||||
{-# LANGUAGE DeriveDataTypeable, ExistentialQuantification, TypeSynonymInstances, MultiParamTypeClasses, FlexibleInstances, PatternGuards #-}
|
||||
|
||||
module Storage ( StoreData
|
||||
, Storage
|
||||
|
@ -16,7 +16,6 @@ import Control.Applicative ((<$>))
|
|||
import Control.Monad
|
||||
|
||||
import Data.IORef
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe
|
||||
import Data.Typeable
|
||||
|
||||
|
@ -35,11 +34,11 @@ instance (StoreData d) => LayoutModifier (Storage d) a where
|
|||
modifierDescription _ = "Storage"
|
||||
|
||||
handleMess (Storage d) m
|
||||
| Just (GetStoreData ref :: StorageMessage d) <- fromMessage m = do
|
||||
| Just (GetStoreData ref) <- fromMessage m = do
|
||||
io $ writeIORef ref $ Just d
|
||||
return $ Nothing
|
||||
|
||||
| Just (SetStoreData d' :: StorageMessage d) <- fromMessage m = do
|
||||
| Just (SetStoreData d') <- fromMessage m = do
|
||||
return $ Just $ Storage d'
|
||||
|
||||
handleMess _ _ = return Nothing
|
||||
|
|
|
@ -45,6 +45,7 @@ main = xmonad $ gnomeConfig
|
|||
, ("M-<F1>", viewOrWarp 0)
|
||||
, ("M-<F2>", viewOrWarp 1)
|
||||
, ("M-<F3>", viewOrWarp 2)
|
||||
, ("M-b", banishScreen LowerRight)
|
||||
, ("M-p", spawnOnCurrent "exe=`dmenu_path | /home/neoraider/bin/dmemu -b` && eval \"exec $exe\"")
|
||||
]
|
||||
`additionalMouseBindings`
|
||||
|
@ -92,7 +93,7 @@ myManageHook = composeAll
|
|||
, stringProperty "WM_ICON_NAME" =? "ZeroGS" -?> doFloat
|
||||
, isFullscreen -?> doFullscreen
|
||||
]
|
||||
, doAutoShift
|
||||
--, doAutoShift
|
||||
, manageHook gnomeConfig
|
||||
]
|
||||
|
||||
|
|
Reference in a new issue