summaryrefslogtreecommitdiffstats
path: root/lib/ProcessWorkspaces.hs
blob: 69ab48ddc26038857d6eba08ecbe2408dadaa06c (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
{-# 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)