aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2010-10-30 19:56:15 +0200
committerAdam Vogt <vogt.adam@gmail.com>2010-10-30 19:56:15 +0200
commit20b517f2954cc5eaa4211d16a75152fbb0d3db15 (patch)
tree98363ba569bce75c750dc02cf008a223e5245184
parentcc90050738cf619c165358cc4c3fa90150e205ee (diff)
downloadXMonadContrib-20b517f2954cc5eaa4211d16a75152fbb0d3db15.tar.gz
XMonadContrib-20b517f2954cc5eaa4211d16a75152fbb0d3db15.tar.xz
XMonadContrib-20b517f2954cc5eaa4211d16a75152fbb0d3db15.zip
X.L.TrackFloating docs and help nested layouts
Ignore-this: a4362384ff8baab896715226772edf62 Now TrackFloating remembers focus for the given layout when the other window is also tiled, but not fed to the given layout: this helps with X.L.IM, among others. darcs-hash:20101030175615-1499c-e205cecd50f076131e4b5b527454a0a4f79dc273.gz
-rw-r--r--XMonad/Layout/TrackFloating.hs58
1 files changed, 44 insertions, 14 deletions
diff --git a/XMonad/Layout/TrackFloating.hs b/XMonad/Layout/TrackFloating.hs
index 615141a..b30d524 100644
--- a/XMonad/Layout/TrackFloating.hs
+++ b/XMonad/Layout/TrackFloating.hs
@@ -14,23 +14,24 @@ is in use. This is particularly helpful for tiled layouts where the focus
determines what is visible.
The relevant bug is Issue 4
-<http://code.google.com/p/xmonad/issues/detail?id=4>. Explanation:
-
-Focus in the tiled layer goes to the first window in the stack (so-called
-master window) when you focus the tiled layer.
-
-See 'trackFloating' for usage.
-
+<http://code.google.com/p/xmonad/issues/detail?id=4>.
-}
module XMonad.Layout.TrackFloating
- (trackFloating,
+ (-- * Usage
+ -- $usage
+
+ -- ** For other layout modifiers
+ -- $layoutModifier
+ trackFloating,
TrackFloating,
) where
import Control.Monad
+import Data.Function
import Data.List
import Data.Maybe
import qualified Data.Map as M
+import qualified Data.Set as S
import XMonad
import XMonad.Layout.LayoutModifier
@@ -47,8 +48,12 @@ instance LayoutModifier TrackFloating Window where
modifyLayoutWithUpdate os@(TrackFloating wasF mw) ws@(W.Workspace{ W.stack = ms }) r
= do
winset <- gets windowset
- let sCur = fmap W.focus $ W.stack $ W.workspace $ W.current winset
- isF = fmap (`M.member` W.floating winset) sCur
+ let xCur = fmap W.focus xStack
+ xStack = W.stack $ W.workspace $ W.current winset
+ isF = fmap (\x -> x `M.member` W.floating winset ||
+ (let (\\\) = (S.\\) `on` (S.fromList . W.integrate')
+ in x `S.member` (xStack \\\ ms)))
+ xCur
newStack
-- focus is floating, so use the remembered focus point
| Just isF' <- isF,
@@ -62,7 +67,7 @@ instance LayoutModifier TrackFloating Window where
= ms
newState = case isF of
Just True -> mw
- Just False | Just f <- sCur -> Just f
+ Just False | Just f <- xCur -> Just f
_ -> Nothing
ran <- runLayout ws{ W.stack = newStack } r
return (ran,
@@ -70,7 +75,9 @@ instance LayoutModifier TrackFloating Window where
in guard (n /= os) >> Just n)
-{- | Apply to your layout in a config like:
+{- $usage
+
+Apply to your layout in a config like:
> main = xmonad (defaultConfig{
> layoutHook = trackFloating
@@ -78,9 +85,32 @@ instance LayoutModifier TrackFloating Window where
> ...
> })
-Interactions with some layout modifiers (ex. decorations, minimizing) are
-unknown but likely unpleasant.
+-}
+
+{- | Runs another layout with a remembered focus, provided:
+
+* the subset of windows doesn't include the focus in XState
+
+* it was previously run with a subset that included the XState focus
+
+* the remembered focus hasn't since been killed
+
-}
trackFloating :: l a -> ModifiedLayout TrackFloating l a
trackFloating layout = ModifiedLayout (TrackFloating False Nothing) layout
+{- $layoutModifier
+It also corrects focus issues for full-like layouts inside other layout
+modifiers:
+
+> import XMonad.Layout.IM
+> import XMonad.Layout.Tabbed
+> import XMonad.Layout.TrackFloating
+> import XMonad.Layout.Reflect
+
+> gimpLayout = withIM 0.11 (Role "gimp-toolbox") $ reflectHoriz
+> $ withIM 0.15 (Role "gimp-dock") (trackFloating simpleTabbed)
+
+Interactions with some layout modifiers (ex. decorations, minimizing) are
+unknown but likely unpleasant.
+-}