aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Config/Droundy.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-12-01 14:29:10 +0100
committerDavid Roundy <droundy@darcs.net>2007-12-01 14:29:10 +0100
commit169f3ace9e8ee77e2797d1691054c5660dc75b3f (patch)
tree949b590a4b1219a96937bb752ec9e1ab537133eb /XMonad/Config/Droundy.hs
parent006474f5ef3ae446606be3308f3efdc56c9d5ae1 (diff)
downloadXMonadContrib-169f3ace9e8ee77e2797d1691054c5660dc75b3f.tar.gz
XMonadContrib-169f3ace9e8ee77e2797d1691054c5660dc75b3f.tar.xz
XMonadContrib-169f3ace9e8ee77e2797d1691054c5660dc75b3f.zip
add to Droundy a non-working urgency hook and enable avoidStruts.
darcs-hash:20071201132910-72aca-07e111e0721b34cfc038b59fa4d55622df05ae06.gz
Diffstat (limited to '')
-rw-r--r--XMonad/Config/Droundy.hs30
1 files changed, 25 insertions, 5 deletions
diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs
index 8ce000d..24de457 100644
--- a/XMonad/Config/Droundy.hs
+++ b/XMonad/Config/Droundy.hs
@@ -8,13 +8,13 @@
module XMonad.Config.Droundy ( config, mytab ) where
---
--- Useful imports
---
+import Control.Monad.State ( modify )
+
import XMonad hiding (keys, config)
import qualified XMonad (keys)
import XMonad.Config ( defaultConfig )
+import XMonad.Core ( windowset )
import XMonad.Layouts hiding ( (|||) )
import XMonad.Operations
import qualified XMonad.StackSet as W
@@ -45,6 +45,9 @@ import XMonad.Actions.CopyWindow
import XMonad.Actions.DynamicWorkspaces
import XMonad.Actions.RotView
+import XMonad.Hooks.ManageDocks
+import XMonad.Hooks.UrgencyHook
+
myXPConfig :: XPConfig
myXPConfig = defaultXPConfig {font="-*-lucida-medium-r-*-*-14-*-*-*-*-*-*-*"
,height=22}
@@ -127,11 +130,11 @@ keys x = M.fromList $
++
zip (zip (repeat (modMask x .|. shiftMask)) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
-config = defaultConfig
+config = withUrgencyHook FocusUrgencyHook $ defaultConfig
{ borderWidth = 1 -- Width of the window border in pixels.
, XMonad.workspaces = ["1:mutt","2:iceweasel"]
, layoutHook = workspaceDir "~" $ windowNavigation $
- toggleLayouts (noBorders Full) $ -- avoidStruts $
+ toggleLayouts (noBorders Full) $ avoidStruts $
Named "tabbed" (noBorders mytab) |||
Named "xclock" (mytab ****//* combineTwo Square mytab mytab) |||
Named "widescreen" ((mytab *||* mytab)
@@ -167,3 +170,20 @@ dropFromTail t s | drop (length s - length t) s == t = Just $ take (length s - l
dropFromHead :: String -> String -> Maybe String
dropFromHead h s | take (length h) s == h = Just $ drop (length h) s
| otherwise = Nothing
+
+data FocusUrgencyHook = FocusUrgencyHook deriving (Read, Show)
+
+instance UrgencyHook FocusUrgencyHook Window where
+ urgencyHook _ w = modify copyAndFocus
+ where copyAndFocus s
+ | Just w == W.peek (windowset s) = s
+ | has w $ W.stack $ W.workspace $ W.current $ windowset s =
+ s { windowset = until ((Just w ==) . W.peek)
+ W.focusUp $ windowset s }
+ | otherwise =
+ let t = W.tag $ W.workspace $ W.current $ windowset s
+ in s { windowset = until ((Just w ==) . W.peek)
+ W.focusUp $ copyWindow w t $ windowset s }
+ has _ Nothing = False
+ has x (Just (W.Stack t l rr)) = x `elem` (t : l ++ rr)
+