aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2009-05-03 04:03:03 +0200
committerAdam Vogt <vogt.adam@gmail.com>2009-05-03 04:03:03 +0200
commit9aad112502bbf81ef02e361f77b0d73c374e37e4 (patch)
tree1a9669a0b51898b14e904a8862360c317912e26f /XMonad/Hooks
parent8700b67ae680c67c60bbdc1b3213903e9b6628de (diff)
downloadXMonadContrib-9aad112502bbf81ef02e361f77b0d73c374e37e4.tar.gz
XMonadContrib-9aad112502bbf81ef02e361f77b0d73c374e37e4.tar.xz
XMonadContrib-9aad112502bbf81ef02e361f77b0d73c374e37e4.zip
Add H.InsertPosition: add new windows to different positions in a workspace
Ignore-this: 7e7d5fa5b42698799cabe600159a75f7 darcs-hash:20090503020303-1499c-03bd01137979cfbbe6aaebe4981c03c5597818ab.gz
Diffstat (limited to 'XMonad/Hooks')
-rw-r--r--XMonad/Hooks/InsertPosition.hs74
1 files changed, 74 insertions, 0 deletions
diff --git a/XMonad/Hooks/InsertPosition.hs b/XMonad/Hooks/InsertPosition.hs
new file mode 100644
index 0000000..54c2a6d
--- /dev/null
+++ b/XMonad/Hooks/InsertPosition.hs
@@ -0,0 +1,74 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Hooks.InsertPosition
+-- Copyright : (c) 2009 Adam Vogt
+-- License : BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer : vogt.adam@gmail.com
+-- Stability : unstable
+-- Portability : portable
+--
+-- Configure where new windows should be added and which window should be
+-- focused.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Hooks.InsertPosition (
+ -- * Usage
+ -- $usage
+ insertPosition
+ ,Focus(..), Position(..)
+ ) where
+
+import XMonad(ManageHook, MonadReader(ask))
+import qualified XMonad.StackSet as W
+import Control.Applicative((<$>))
+import Data.Maybe(fromMaybe)
+import Data.List(find)
+import Data.Monoid(Endo(Endo))
+
+-- $usage
+-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Hooks.InsertPosition
+-- > xmonad defaultConfig { manageHook = insertPosition Master Newer <+> myManageHook }
+--
+-- You should you put the manageHooks that use 'doShift' to take effect
+-- /before/ 'insertPosition', so that the window order will be consistent.
+-- Because ManageHooks compose from right to left (like function composition
+-- '.'), this means that 'insertPosition' should be the leftmost ManageHook.
+
+data Position = Master | End | Above | Below
+data Focus = Newer | Older
+
+-- | insertPosition. A manage hook for placing new windows. XMonad's default is
+-- the same as using: @insertPosition Above Newer@.
+insertPosition :: Position -> Focus -> ManageHook
+insertPosition pos foc = Endo . g <$> ask
+ where
+ g w = viewingWs w (updateFocus w . ins w . W.delete w)
+ ins w = (\f ws -> fromMaybe id (W.focusWindow <$> W.peek ws) $ f ws) $
+ case pos of
+ Master -> W.insertUp w . W.focusMaster
+ End -> insertDown w . W.modify' focusLast'
+ Above -> W.insertUp w
+ Below -> insertDown w
+ updateFocus =
+ case foc of
+ Older -> const id
+ Newer -> W.focusWindow
+
+-- | Modify the StackSet when the workspace containing w is focused
+viewingWs :: (Eq a, Eq s, Eq i, Show i) =>a-> (W.StackSet i l a s sd -> W.StackSet i l a s sd)-> W.StackSet i l a s sd-> W.StackSet i l a s sd
+viewingWs w f = do
+ i <- W.tag . W.workspace . W.current
+ ws <- find (elem w . W.integrate' . W.stack) . W.workspaces
+ maybe id (fmap (W.view i . f) . W.view . W.tag) ws
+
+-- | 'insertDown' and 'focusLast' belong in XMonad.StackSet?
+insertDown :: (Eq a) => a -> W.StackSet i l a s sd -> W.StackSet i l a s sd
+insertDown w = W.swapDown . W.insertUp w
+
+focusLast' :: W.Stack a -> W.Stack a
+focusLast' st = let ws = W.integrate st
+ in W.Stack (last ws) (tail $ reverse ws) []