summaryrefslogtreecommitdiffstats
path: root/lib/ProcessWorkspaces.hs
blob: 8789c514da948107057264a659c60c82123eead3 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
{-# LANGUAGE DeriveDataTypeable, TypeSynonymInstances, MultiParamTypeClasses, PatternGuards #-}

module ProcessWorkspaces ( setProcessWorkspace
                         , getProcessWorkspace
                         , doAutoShift
                         , doIgnoreProcessWorkspace
                         , regroupProcess
                         , regroupWinProcess
                         , shiftIgnoreGroup
                         , shiftWinIgnoreGroup
                         , shiftGroup
                         , shiftWinGroup
                         , 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 qualified Data.Map as M

import Storage


doAutoShift :: ManageHook
doAutoShift = do
  mp <- pid
  case mp of
    Just p -> do
      mws <- liftX $ getProcessWorkspace p
      case mws of
        Just ws ->
          doShift ws
        _ -> do
          idHook
    _ ->
      idHook

doIgnoreProcessWorkspace :: ManageHook
doIgnoreProcessWorkspace = do
  mp <- pid
  when (isJust mp) $
    liftX $ setProcessWorkspace (fromJust mp) Nothing
  idHook

regroupProcess :: WorkspaceId -> X ()
regroupProcess ws = withFocused $ regroupWinProcess ws

regroupWinProcess :: WorkspaceId -> Window -> X ()
regroupWinProcess ws w = do
  mp <- runQuery pid w
  when (isJust mp) $ setProcessWorkspace (fromJust mp) (Just ws)
  shiftWinGroup ws w

shiftIgnoreGroup :: WorkspaceId -> X ()
shiftIgnoreGroup ws = withFocused $ shiftWinIgnoreGroup ws

shiftWinIgnoreGroup :: WorkspaceId -> Window -> X ()
shiftWinIgnoreGroup ws w = do
  runQuery doIgnoreProcessWorkspace w
  windows $ W.shiftWin ws w

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

processWorkspaceStorage :: (LayoutClass l a) => l a -> ModifiedLayout (Storage ProcessWorkspaceStoreData) l a
processWorkspaceStorage = storage $ ProcessWorkspaceStoreData M.empty

setProcessWorkspace :: ProcessID -> Maybe 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 = do
  ws <- getStoreData >>= return . join . fmap (\(ProcessWorkspaceStoreData map) -> M.lookup pid $ map)
  case ws of
    Nothing -> do
      wsc <- gets (W.currentTag . windowset)
      setProcessWorkspace pid (Just wsc)
      return $ Just wsc
    Just Nothing ->
      return Nothing
    Just (Just ws') ->
      return $ Just ws'


spawnOn :: Maybe WorkspaceId -> String -> X ()
spawnOn ws x = do
  pid <- spawnPID x
  setProcessWorkspace pid ws

spawnOnCurrent :: String -> X ()
spawnOnCurrent x = gets (W.currentTag . windowset) >>= \ws -> spawnOn (Just 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
    pidExists pid = io $ ((getProcessPriority pid) >> return True) `catch` (\_ -> return False)