aboutsummaryrefslogtreecommitdiffstats
path: root/WorkspaceDir.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-06-11 17:40:41 +0200
committerDavid Roundy <droundy@darcs.net>2007-06-11 17:40:41 +0200
commit2854dd0b15a46135f2396a3ce886b0b2dbad9aab (patch)
tree6c64a1e4887a9affd7765fd9a3ede8a9bef9c75b /WorkspaceDir.hs
parent78afd7a9c7349652d5000f44f51804b1cacc46c8 (diff)
downloadXMonadContrib-2854dd0b15a46135f2396a3ce886b0b2dbad9aab.tar.gz
XMonadContrib-2854dd0b15a46135f2396a3ce886b0b2dbad9aab.tar.xz
XMonadContrib-2854dd0b15a46135f2396a3ce886b0b2dbad9aab.zip
add WorkspaceDir, which sets the current directory in a workspace.
Actually, it sets the current directory in a layout, since there's no way I know of to attach a behavior to a workspace. This means that any terminals (or other programs) pulled up in that workspace (with that layout) will execute in that working directory. Sort of handy, I think. darcs-hash:20070611154041-72aca-86d2e97e073eae656407df497ab4e1236762c92b.gz
Diffstat (limited to 'WorkspaceDir.hs')
-rw-r--r--WorkspaceDir.hs35
1 files changed, 35 insertions, 0 deletions
diff --git a/WorkspaceDir.hs b/WorkspaceDir.hs
new file mode 100644
index 0000000..a109f64
--- /dev/null
+++ b/WorkspaceDir.hs
@@ -0,0 +1,35 @@
+module XMonadContrib.WorkspaceDir ( workspaceDir, changeDir ) where
+
+-- to use:
+
+-- import XMonadContrib.WorkspaceDir
+
+-- defaultLayouts = map (workspaceDir "~") [ tiled, ... ]
+
+-- In keybindings:
+-- , ((modMask .|. shiftMask, xK_x ), changeDir ["~","/tmp"])
+
+import System.Directory ( setCurrentDirectory, getCurrentDirectory )
+import Data.List ( nub )
+
+import XMonad
+import Operations ( sendMessage )
+import XMonadContrib.Dmenu ( dmenu, runProcessWithInput )
+
+data Chdir = Chdir String deriving ( Typeable )
+instance Message Chdir
+
+workspaceDir :: String -> Layout -> Layout
+workspaceDir wd l = l { doLayout = \r x -> scd wd >> doLayout l r x
+ , modifyLayout = ml }
+ where ml m | Just (Chdir wd') <- fromMessage m = return $ Just (workspaceDir wd' l)
+ | otherwise = fmap (workspaceDir wd) `fmap` modifyLayout l m
+
+scd :: String -> X ()
+scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` \_ -> return x)
+ safeIO $ setCurrentDirectory x'
+
+changeDir :: [String] -> X ()
+changeDir dirs = do thisd <- io getCurrentDirectory
+ dir <- dmenu (nub (thisd:dirs))
+ sendMessage (Chdir dir)