Allow spawning processes bound to workspaces
This commit is contained in:
parent
894e8b41d3
commit
cd08ed8a00
3 changed files with 159 additions and 18 deletions
89
lib/ProcessWorkspaces.hs
Normal file
89
lib/ProcessWorkspaces.hs
Normal file
|
@ -0,0 +1,89 @@
|
|||
{-# 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 Prelude hiding ( catch )
|
||||
import Control.OldException (catch)
|
||||
import Control.Monad
|
||||
import Data.Maybe
|
||||
import Data.Monoid
|
||||
import qualified Data.Map as M
|
||||
|
||||
import Storage
|
||||
|
||||
|
||||
moveWindowHook :: ManageHook
|
||||
moveWindowHook = do
|
||||
mp <- pid
|
||||
io $ appendFile "/tmp/test" $ "Pid: " ++ show mp ++ "\n"
|
||||
case mp of
|
||||
Just p -> do
|
||||
mws <- liftX $ getProcessWorkspace p
|
||||
io $ appendFile "/tmp/test" $ "WS: " ++ show mws ++ "\n"
|
||||
case mws of
|
||||
Just ws -> do
|
||||
io $ appendFile "/tmp/test" $ show ws ++ "\n"
|
||||
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
|
||||
io $ appendFile "/tmp/test" $ "Added " ++ show (pid, ws) ++ "\n"
|
||||
ProcessWorkspaceStoreData map <- liftM (fromMaybe $ ProcessWorkspaceStoreData M.empty) $ getStoreData
|
||||
map' <- filterPIDMap $ M.insert pid ws map
|
||||
setStoreData $ ProcessWorkspaceStoreData map'
|
||||
io (appendFile "/tmp/test" $ show map' ++ "\n")
|
||||
|
||||
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
|
||||
|
||||
|
||||
catchX' :: X a -> X a -> X a
|
||||
catchX' job errcase = do
|
||||
st <- get
|
||||
c <- ask
|
||||
(a, s') <- io $ runX c st job `catch` \_ -> runX c st errcase
|
||||
put s'
|
||||
return a
|
||||
|
||||
filterPIDMap :: M.Map ProcessID a -> X (M.Map ProcessID a)
|
||||
filterPIDMap = liftM M.fromAscList . filterM (pidExists . fst) . M.toAscList
|
||||
where
|
||||
pidExists :: ProcessID -> X Bool
|
||||
pidExists pid = catchX' (io (getProcessPriority pid) >> return True) (return False)
|
65
lib/Storage.hs
Normal file
65
lib/Storage.hs
Normal file
|
@ -0,0 +1,65 @@
|
|||
{-# LANGUAGE DeriveDataTypeable, ExistentialQuantification, TypeSynonymInstances, MultiParamTypeClasses, ScopedTypeVariables, FlexibleInstances, PatternGuards #-}
|
||||
|
||||
module Storage ( StoreData
|
||||
, Storage
|
||||
, storage
|
||||
, getStoreData
|
||||
, setStoreData
|
||||
, updateStoreData
|
||||
) where
|
||||
|
||||
import XMonad
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Layout.LayoutModifier (LayoutModifier(..), ModifiedLayout(..))
|
||||
|
||||
import Control.Applicative ((<$>))
|
||||
import Control.Monad
|
||||
|
||||
import Data.IORef
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe
|
||||
import Data.Typeable
|
||||
|
||||
|
||||
class (Typeable d, Show d, Read d) => StoreData d
|
||||
|
||||
|
||||
data (StoreData d) => StorageMessage d = GetStoreData (IORef (Maybe d)) | SetStoreData d
|
||||
deriving Typeable
|
||||
instance (StoreData d) => Message (StorageMessage d)
|
||||
|
||||
|
||||
data (StoreData d) => Storage d a = Storage d deriving (Show, Read)
|
||||
|
||||
instance (StoreData d) => LayoutModifier (Storage d) a where
|
||||
modifierDescription _ = "Storage"
|
||||
|
||||
handleMess (Storage d) m
|
||||
| Just (GetStoreData ref :: StorageMessage d) <- fromMessage m = do
|
||||
io $ writeIORef ref $ Just d
|
||||
return $ Nothing
|
||||
|
||||
| Just (SetStoreData d' :: StorageMessage d) <- fromMessage m = do
|
||||
return $ Just $ Storage d'
|
||||
|
||||
handleMess _ _ = return Nothing
|
||||
|
||||
|
||||
storage :: (LayoutClass l a, StoreData d) => d -> l a -> ModifiedLayout (Storage d) l a
|
||||
storage def = ModifiedLayout $ Storage def
|
||||
|
||||
|
||||
getStoreData :: StoreData d => X (Maybe d)
|
||||
getStoreData = do
|
||||
ref <- io . newIORef $ Nothing
|
||||
broadcastMessage $ GetStoreData ref
|
||||
io . readIORef $ ref
|
||||
|
||||
|
||||
setStoreData :: StoreData d => d -> X ()
|
||||
setStoreData = broadcastMessage . SetStoreData
|
||||
|
||||
updateStoreData :: StoreData d => (d -> d) -> X ()
|
||||
updateStoreData f = do
|
||||
d <- getStoreData
|
||||
when (isJust d) $ setStoreData . f $ fromJust d
|
Reference in a new issue