diff options
author | David Roundy <droundy@darcs.net> | 2008-05-14 18:28:46 +0200 |
---|---|---|
committer | David Roundy <droundy@darcs.net> | 2008-05-14 18:28:46 +0200 |
commit | 5fd882c4150a5ea509a79b3417d2314782568965 (patch) | |
tree | 941fd659714ecdda7fb79579a57837c652f8c96f | |
parent | 850b898a3ecba2ef81772335b0363b17be575eb2 (diff) | |
download | XMonadContrib-5fd882c4150a5ea509a79b3417d2314782568965.tar.gz XMonadContrib-5fd882c4150a5ea509a79b3417d2314782568965.tar.xz XMonadContrib-5fd882c4150a5ea509a79b3417d2314782568965.zip |
add BoringWindows module to make certain windows skipped when rotating focus.
darcs-hash:20080514162846-72aca-64443ce59d280f6b4b80987fa93aabb6e16d4a00.gz
-rw-r--r-- | XMonad/Config/Droundy.hs | 12 | ||||
-rw-r--r-- | XMonad/Layout/BoringWindows.hs | 66 | ||||
-rw-r--r-- | xmonad-contrib.cabal | 1 |
3 files changed, 75 insertions, 4 deletions
diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs index 824041c..f09857c 100644 --- a/XMonad/Config/Droundy.hs +++ b/XMonad/Config/Droundy.hs @@ -25,6 +25,8 @@ import XMonad.Layout.Simplest ( Simplest(Simplest) ) import XMonad.Layout.Square ( Square(Square) ) import XMonad.Layout.WindowNavigation ( Navigate(Move,Swap,Go), Direction(U,D,R,L), windowNavigation ) +import XMonad.Layout.BoringWindows ( boringWindows, markBoring, clearBoring, + focusUp, focusDown ) import XMonad.Layout.NoBorders ( smartBorders ) import XMonad.Layout.WorkspaceDir ( changeDir, workspaceDir ) import XMonad.Layout.ToggleLayouts ( toggleLayouts, ToggleLayout(ToggleLayout) ) @@ -66,9 +68,9 @@ keys x = M.fromList $ , ((modMask x .|. shiftMask, xK_space ), setLayout $ layoutHook x) -- %! Reset the layouts on the current workspace to default -- move focus up or down the window stack - , ((modMask x, xK_Tab ), windows W.focusDown) -- %! Move focus to the next window - , ((modMask x, xK_j ), windows W.focusDown) -- %! Move focus to the next window - , ((modMask x, xK_k ), windows W.focusUp ) -- %! Move focus to the previous window + , ((modMask x, xK_Tab ), focusDown) -- %! Move focus to the next window + , ((modMask x, xK_j ), focusDown) -- %! Move focus to the next window + , ((modMask x, xK_k ), focusUp ) -- %! Move focus to the previous window , ((modMask x .|. shiftMask, xK_j ), windows W.swapDown ) -- %! Swap the focused window with the next window , ((modMask x .|. shiftMask, xK_k ), windows W.swapUp ) -- %! Swap the focused window with the previous window @@ -98,6 +100,8 @@ keys x = M.fromList $ , ((0, xK_F2 ), spawn "gnome-terminal") -- %! Launch gnome-terminal , ((0, xK_F3 ), shellPrompt myXPConfig) -- %! Launch program , ((0, xK_F11 ), spawn "ksnapshot") -- %! Take snapshot + , ((modMask x .|. shiftMask, xK_b ), markBoring) + , ((controlMask .|. modMask x .|. shiftMask, xK_b ), clearBoring) , ((modMask x .|. shiftMask, xK_x ), changeDir myXPConfig) , ((modMask x .|. shiftMask, xK_BackSpace), removeWorkspace) , ((modMask x .|. shiftMask, xK_v ), selectWorkspace myXPConfig) @@ -120,7 +124,7 @@ config = defaultConfig { borderWidth = 1 -- Width of the window border in pixels. , XMonad.workspaces = ["mutt","iceweasel"] , layoutHook = ewmhDesktopsLayout $ showWName $ workspaceDir "~" $ - smartBorders $ windowNavigation $ + boringWindows $ smartBorders $ windowNavigation $ toggleLayouts Full $ avoidStruts $ named "tabbed" mytab ||| named "xclock" (mytab ****//* combineTwo Square mytab mytab) ||| diff --git a/XMonad/Layout/BoringWindows.hs b/XMonad/Layout/BoringWindows.hs new file mode 100644 index 0000000..d66aa73 --- /dev/null +++ b/XMonad/Layout/BoringWindows.hs @@ -0,0 +1,66 @@ +{-# OPTIONS_GHC -fglasgow-exts #-} -- For deriving Data/Typeable + +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Layout.BoringWindows +-- Copyright : (c) 2008 David Roundy <droundy@darcs.net> +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : David Roundy <droundy@darcs.net> +-- Stability : unstable +-- Portability : unportable +-- +-- BoringWindows is an extension to allow windows to be marked boring +-- +----------------------------------------------------------------------------- + +module XMonad.Layout.BoringWindows ( + -- * Usage + -- $usage + boringWindows, + markBoring, clearBoring, + focusUp, focusDown + ) where + +import XMonad hiding (Point) +import qualified XMonad.StackSet as W +import XMonad.Layout.LayoutModifier +import XMonad.Util.Invisible + +data BoringMessage = FocusUp | FocusDown | IsBoring Window | ClearBoring + deriving ( Read, Show, Typeable ) +instance Message BoringMessage + +markBoring = withFocused (sendMessage . IsBoring) +clearBoring = sendMessage ClearBoring +focusUp = sendMessage FocusUp +focusDown = sendMessage FocusDown + +data BoringWindows a = BoringWindows (Invisible [] a) deriving ( Show, Read, Typeable ) + +boringWindows :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a +boringWindows = ModifiedLayout (BoringWindows (I [])) + +instance LayoutModifier BoringWindows Window where + handleMessOrMaybeModifyIt (BoringWindows (I bs)) m + | Just (IsBoring b) <- fromMessage m = return $ Just $ Left $ BoringWindows (I (b:bs)) + | Just ClearBoring <- fromMessage m = return $ Just $ Left $ BoringWindows (I []) + | Just FocusUp <- fromMessage m = do windows $ W.modify' $ focusUp' + return Nothing + | Just FocusDown <- fromMessage m = + do windows $ W.modify' (reverseStack . focusUp' . reverseStack) + return Nothing + where focusUp' (W.Stack t ls rs) + | (a,l:ls') <- skipBoring ls = W.Stack l ls' (a++t:rs) + | otherwise = case skipBoring (reverse (t:rs)++ls) of + (a,x:xs) -> W.Stack x xs a + _ -> W.Stack t ls rs + skipBoring [] = ([],[]) + skipBoring (x:xs) | x `elem` bs = case skipBoring xs of + (a,b) -> (x:a,b) + | otherwise = ([],x:xs) + handleMessOrMaybeModifyIt _ _ = return Nothing + +-- | reverse a stack: up becomes down and down becomes up. +reverseStack :: W.Stack a -> W.Stack a +reverseStack (W.Stack t ls rs) = W.Stack t rs ls diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal index 16706fd..0a1ba79 100644 --- a/xmonad-contrib.cabal +++ b/xmonad-contrib.cabal @@ -115,6 +115,7 @@ library XMonad.Hooks.UrgencyHook XMonad.Hooks.XPropManage XMonad.Layout.Accordion + XMonad.Layout.BoringWindows XMonad.Layout.Circle XMonad.Layout.Combo XMonad.Layout.Decoration |