aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/TrackFloating.hs
blob: 615141a6a05d43b5595b383a417574fd95789a86 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
{-# LANGUAGE MultiParamTypeClasses, PatternGuards, TypeSynonymInstances #-}
{- |

Module      :  XMonad.Layout.TrackFloating
Copyright   :  (c) 2010 Adam Vogt
License     :  BSD-style (see xmonad/LICENSE)

Maintainer  :  vogt.adam@gmail.com
Stability   :  unstable
Portability :  unportable

Layout modifier that tracks focus in the tiled layer while the floating layer
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.

-}
module XMonad.Layout.TrackFloating
    (trackFloating,
     TrackFloating,
    ) where

import Control.Monad
import Data.List
import Data.Maybe
import qualified Data.Map as M

import XMonad
import XMonad.Layout.LayoutModifier
import qualified XMonad.StackSet as W


data TrackFloating a = TrackFloating
    { _wasFloating :: Bool,
      _tiledFocus :: Maybe Window }
    deriving (Read,Show,Eq)


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
            newStack
              -- focus is floating, so use the remembered focus point
              | Just isF' <- isF,
                isF' || wasF,
                Just w <- mw,
                Just s <- ms,
                Just ns <- find ((==) w . W.focus)
                    $ zipWith const (iterate W.focusDown' s) (W.integrate s)
                = Just ns
              | otherwise
                = ms
            newState = case isF of
              Just True -> mw
              Just False | Just f <- sCur -> Just f
              _ -> Nothing
        ran <- runLayout ws{ W.stack = newStack } r
        return (ran,
                let n = TrackFloating (fromMaybe False isF) newState
                in guard (n /= os) >> Just n)


{- | Apply to your layout in a config like:

> main = xmonad (defaultConfig{
>                   layoutHook = trackFloating
>                       (noBorders Full ||| Tall 1 0.3 0.5),
>                   ...
>               })

Interactions with some layout modifiers (ex. decorations, minimizing) are
unknown but likely unpleasant.
-}
trackFloating ::  l a -> ModifiedLayout TrackFloating l a
trackFloating layout = ModifiedLayout (TrackFloating False Nothing) layout