mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-18 19:10:21 -07:00
X.L.StateFull's `FocusTracking` and the eponymous `TrackFloating` were redundant, hence the former was slated for deprecation. However, the latter and its host module are somewhat poorly named; the layout modifier has little relation to floats. As such, it's renamed and rehosted, becoming the eponymous `FocusTracking`. The redundant offerings in the original modules are redefined in terms of the new module where possible, and deprecated. See: #418; comments on #253, #783.
86 lines
2.7 KiB
Haskell
86 lines
2.7 KiB
Haskell
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-}
|
|
{- |
|
|
|
|
Module : XMonad.Layout.FocusTracking
|
|
Description : Track focus in the tiled layer.
|
|
Copyright : (c) 2010 & 2013 Adam Vogt
|
|
2011 Willem Vanlint
|
|
2018 & 2022 L.S.Leary
|
|
License : BSD-style (see xmonad/LICENSE)
|
|
|
|
Maintainer : @LSLeary (on github)
|
|
Stability : unstable
|
|
Portability : unportable
|
|
|
|
FocusTracking simply holds onto the last true focus it was given and continues
|
|
to use it as the focus for the transformed layout until it sees another. It can
|
|
be used to improve the behaviour of a child layout that has not been given the
|
|
focused window, or equivalently, that of the layout itself when a float has
|
|
focus.
|
|
|
|
Relevant issues:
|
|
|
|
* <http://code.google.com/p/xmonad/issues/detail?id=4>
|
|
* <http://code.google.com/p/xmonad/issues/detail?id=306>
|
|
|
|
--------------------------------------------------------------------------------
|
|
-}
|
|
module XMonad.Layout.FocusTracking
|
|
( -- * Usage
|
|
-- $usage
|
|
FocusTracking(..)
|
|
, focusTracking
|
|
) where
|
|
|
|
import XMonad.Prelude
|
|
import XMonad
|
|
import XMonad.Layout.LayoutModifier
|
|
import XMonad.Util.Stack (findZ)
|
|
import qualified XMonad.StackSet as W
|
|
|
|
-- $usage
|
|
--
|
|
-- To use the module, first import it:
|
|
--
|
|
-- > import XMonad.Layout.FocusTracking
|
|
--
|
|
-- Then, a focus-dependent layout can be made to fall back on the last focus it
|
|
-- saw, for example:
|
|
--
|
|
-- > main = xmonad def
|
|
-- > { layoutHook = someParentLayoutWith aChild (focusTracking anotherChild)
|
|
-- > , ...
|
|
-- > }
|
|
--
|
|
-- Or in a simpler case:
|
|
--
|
|
-- > main = xmonad def
|
|
-- > { layoutHook = myTiledLayout ||| focusTracking Full
|
|
-- > , ...
|
|
-- > }
|
|
--
|
|
|
|
-- | A 'LayoutModifier' that remembers the last focus it saw.
|
|
newtype FocusTracking a = FocusTracking (Maybe Window)
|
|
deriving (Read, Show)
|
|
|
|
instance LayoutModifier FocusTracking Window where
|
|
modifyLayoutWithUpdate (FocusTracking mw) ws@W.Workspace{ W.stack = ms } r
|
|
= do
|
|
xCur <- gets (W.peek . W.view (W.tag ws) . windowset)
|
|
let isF = xCur /= (W.focus <$> ms)
|
|
-- use the remembered focus point when true focus differs from
|
|
-- what this (sub)layout is given, which happens e.g. when true
|
|
-- focus is in floating layer or when another sublayout has focus
|
|
newStack | isF = (mw >>= \w -> findZ (w==) ms) <|> ms
|
|
| otherwise = ms
|
|
newState | isF = mw
|
|
| otherwise = xCur
|
|
ran <- runLayout ws{ W.stack = newStack } r
|
|
return (ran, guard (newState /= mw) $> FocusTracking newState)
|
|
|
|
-- | Transform a layout into one that remembers and uses the last focus it saw.
|
|
focusTracking :: l a -> ModifiedLayout FocusTracking l a
|
|
focusTracking = ModifiedLayout (FocusTracking Nothing)
|
|
|