xmonad-contrib/XMonad/Layout/WorkspaceDir.hs
Tony Zorman 3d65a6bf72 Refer to the tutorial instead of X.D.Extending more often
Essentially, whenever the tutorial actually has decent material on the
subject matter.  The replacement is roughly done as follows:

  - logHook → tutorial
  - keybindings → tutorial, as this is thoroughly covered
  - manageHook → tutorial + X.D.Extending, as the manageHook stuff the
    tutorial talks about is a little bit of an afterthought.
  - X.D.Extending (on its own) → tutorial + X.D.Extending
  - layoutHook → tutorial + X.D.Extending, as the tutorial, while
    talking about layouts, doesn't necessarily have a huge focus there.
  - mouse bindings → leave this alone, as the tutorial does not at all
    talk about them.
2022-10-21 09:17:43 +02:00

98 lines
3.6 KiB
Haskell

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, PatternGuards #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.WorkspaceDir
-- Description : A layout modifier to set the current directory in a workspace.
-- Copyright : (c) 2007 David Roundy <droundy@darcs.net>
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : none
-- 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.
--
-- Note this extension requires the 'directory' package to be installed.
--
-----------------------------------------------------------------------------
module XMonad.Layout.WorkspaceDir (
-- * Usage
-- $usage
workspaceDir,
changeDir,
WorkspaceDir,
Chdir(Chdir),
) where
import System.Directory ( setCurrentDirectory, getCurrentDirectory )
import XMonad.Prelude ( when )
import XMonad hiding ( focus )
import XMonad.Prompt ( XPConfig )
import XMonad.Prompt.Directory ( directoryPrompt )
import XMonad.Layout.LayoutModifier
import XMonad.StackSet ( tag, currentTag )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.WorkspaceDir
--
-- Then edit your @layoutHook@ by adding the Workspace layout modifier
-- to some layout:
--
-- > myLayout = workspaceDir "~" (Tall 1 (3/100) (1/2)) ||| Full ||| etc..
-- > main = xmonad def { layoutHook = myLayout }
--
-- For more detailed instructions on editing the layoutHook see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial> and
-- "XMonad.Doc.Extending#Editing_the_layout_hook".
--
-- WorkspaceDir provides also a prompt. To use it you need to import
-- "XMonad.Prompt" and add something like this to your key bindings:
--
-- > , ((modm .|. shiftMask, xK_x ), changeDir def)
--
-- If you prefer a prompt with case-insensitive completion:
--
-- > , ((modm .|. shiftMask, xK_x ),
-- changeDir def {complCaseSensitivity = CaseInSensitive})
--
-- For detailed instruction on editing the key binding see:
--
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
newtype Chdir = Chdir String
instance Message Chdir
newtype WorkspaceDir a = WorkspaceDir String deriving ( Read, Show )
instance LayoutModifier WorkspaceDir Window where
modifyLayout (WorkspaceDir d) w r = do tc <- gets (currentTag.windowset)
when (tc == tag w) $ scd d
runLayout w r
handleMess (WorkspaceDir _) m
| Just (Chdir wd) <- fromMessage m = do wd' <- cleanDir wd
return $ Just $ WorkspaceDir wd'
| otherwise = return Nothing
workspaceDir :: LayoutClass l a => String -> l a
-> ModifiedLayout WorkspaceDir l a
workspaceDir s = ModifiedLayout (WorkspaceDir s)
cleanDir :: String -> X String
cleanDir x = scd x >> io getCurrentDirectory
scd :: String -> X ()
scd x = catchIO $ setCurrentDirectory x
changeDir :: XPConfig -> X ()
changeDir c = directoryPrompt c "Set working directory: " (sendMessage . Chdir)