blob: 2c42413d74333d08954795d0d0113ee29e3e79dc (
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
|
{-# LANGUAGE DeriveDataTypeable #-}
----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.CurrentWorkspaceOnTop
-- Copyright : (c) Jan Vornberger 2009
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : jan.vornberger@informatik.uni-oldenburg.de
-- Stability : unstable
-- Portability : not portable
--
-- Ensures that the windows of the current workspace are always in front
-- of windows that are located on other visible screens. This becomes important
-- if you use decoration and drag windows from one screen to another. Using this
-- module, the dragged window will always be in front of other windows.
--
-----------------------------------------------------------------------------
module XMonad.Hooks.CurrentWorkspaceOnTop (
-- * Usage
-- $usage
currentWorkspaceOnTop
) where
import XMonad
import qualified XMonad.StackSet as S
import qualified XMonad.Util.ExtensibleState as XS
import Control.Monad(when)
import qualified Data.Map as M
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Hooks.CurrentWorkspaceOnTop
-- >
-- > main = xmonad $ defaultConfig {
-- > ...
-- > logHook = currentWorkspaceOnTop
-- > ...
-- > }
--
data CWOTState = CWOTS String deriving Typeable
instance ExtensionClass CWOTState where
initialValue = CWOTS ""
currentWorkspaceOnTop :: X ()
currentWorkspaceOnTop = withDisplay $ \d -> do
ws <- gets windowset
(CWOTS lastTag) <- XS.get
let curTag = S.tag . S.workspace . S.current $ ws
when (curTag /= lastTag) $ do
-- the following is more or less a reimplementation of what's happening in "XMonad.Operation"
let s = S.current ws
wsp = S.workspace s
viewrect = screenRect $ S.screenDetail s
tmpStack = (S.stack wsp) >>= S.filter (`M.notMember` S.floating ws)
(rs, ml') <- runLayout wsp { S.stack = tmpStack } viewrect
updateLayout curTag ml'
let this = S.view curTag ws
fltWins = filter (flip M.member (S.floating ws)) $ S.index this
wins = fltWins ++ (map fst rs) -- order: first all floating windows, then the order the layout returned
-- end of reimplementation
when (not . null $ wins) $ do
io $ raiseWindow d (head wins) -- raise first window of current workspace to the very top,
io $ restackWindows d wins -- then use restackWindows to let all other windows from the workspace follow
XS.put(CWOTS curTag)
|