From bf33a8c33c2bf83076cd6d520560e047b0456ac1 Mon Sep 17 00:00:00 2001 From: Jan Vornberger Date: Sun, 29 Nov 2009 01:45:06 +0100 Subject: Module to ensure that a dragged window always stays in front of all other windows Ignore-this: a8a389198ccc28a66686561d4d17e91b darcs-hash:20091129004506-594c5-4266465b2a3105e45f1ff9838d9e98dd14390106.gz --- XMonad/Hooks/CurrentWorkspaceOnTop.hs | 62 +++++++++++++++++++++++++++++++++++ 1 file changed, 62 insertions(+) create mode 100644 XMonad/Hooks/CurrentWorkspaceOnTop.hs (limited to 'XMonad') diff --git a/XMonad/Hooks/CurrentWorkspaceOnTop.hs b/XMonad/Hooks/CurrentWorkspaceOnTop.hs new file mode 100644 index 0000000..638a963 --- /dev/null +++ b/XMonad/Hooks/CurrentWorkspaceOnTop.hs @@ -0,0 +1,62 @@ +{-# 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) + +-- $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 + let s = S.current ws + wsp = S.workspace s + viewrect = screenRect $ S.screenDetail s + tmpStack = S.stack . S.workspace $ s + (rs, _) <- runLayout wsp { S.stack = tmpStack } viewrect + let wins = map fst rs + 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) -- cgit v1.2.3