aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/WorkspaceDir.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
commit4866f2e367dfcf22a9591231ba40948826a1b438 (patch)
tree7a245caee3f146826b267d773b7eaa80386a818e /XMonad/Layout/WorkspaceDir.hs
parent47589e1913fb9530481caedb543978a30d4323ea (diff)
downloadXMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.gz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.xz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.zip
Hierarchify
darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz
Diffstat (limited to 'XMonad/Layout/WorkspaceDir.hs')
-rw-r--r--XMonad/Layout/WorkspaceDir.hs78
1 files changed, 78 insertions, 0 deletions
diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs
new file mode 100644
index 0000000..e5f15ce
--- /dev/null
+++ b/XMonad/Layout/WorkspaceDir.hs
@@ -0,0 +1,78 @@
+{-# OPTIONS_GHC -fglasgow-exts #-} -- For deriving Data/Typeable
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.WorkspaceDir
+-- Copyright : (c) 2007 David Roundy <droundy@darcs.net>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : David Roundy <droundy@darcs.net>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- WorkspaceDir is an extension to set 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.
+--
+-- Requires the 'directory' package
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.WorkspaceDir (
+ -- * Usage
+ -- $usage
+ workspaceDir,
+ changeDir
+ ) where
+
+import System.Directory ( setCurrentDirectory )
+
+import XMonad
+import XMonad.Operations ( sendMessage )
+import XMonad.Util.Run ( runProcessWithInput )
+import XMonad.Prompt ( XPConfig )
+import XMonad.Prompt.Directory ( directoryPrompt )
+import XMonad.Layout.LayoutModifier
+
+-- $usage
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonad.Layout.WorkspaceDir
+-- >
+-- > layouts = map (workspaceDir "~") [ tiled, ... ]
+--
+-- In keybindings:
+--
+-- > , ((modMask .|. shiftMask, xK_x ), changeDir defaultXPConfig)
+
+-- %import XMonad.Layout.WorkspaceDir
+-- %keybind , ((modMask .|. shiftMask, xK_x ), changeDir defaultXPConfig)
+-- %layout -- prepend 'map (workspaceDir "~")' to layouts definition above,
+-- %layout -- just before the list, like the following (don't uncomment next line):
+-- %layout -- layouts = map (workspaceDir "~") [ tiled, ... ]
+
+
+data Chdir = Chdir String deriving ( Typeable )
+instance Message Chdir
+
+data WorkspaceDir a = WorkspaceDir String deriving ( Read, Show )
+
+instance LayoutModifier WorkspaceDir a where
+ hook (WorkspaceDir s) = scd s
+ handleMess (WorkspaceDir _) m = return $ do Chdir wd <- fromMessage m
+ Just (WorkspaceDir wd)
+
+workspaceDir :: LayoutClass l a => String -> l a
+ -> ModifiedLayout WorkspaceDir l a
+workspaceDir s = ModifiedLayout (WorkspaceDir s)
+
+scd :: String -> X ()
+scd x = do x' <- io (runProcessWithInput "bash" [] ("echo -n " ++ x) `catch` \_ -> return x)
+ catchIO $ setCurrentDirectory x'
+
+changeDir :: XPConfig -> X ()
+changeDir c = directoryPrompt c "Set working directory: " (sendMessage . Chdir)