X.L.MultiToggle: Add function to query toggle state

This commit is contained in:
Ivan Malison 2021-08-11 22:45:54 -06:00 committed by Tomas Janousek
parent a03d58cf6a
commit 3e83068e0a
2 changed files with 27 additions and 1 deletions

View File

@ -697,6 +697,11 @@
pointer to match the focused window). Together these can be used to
ensure focus stays in sync with mouse.
- `XMonad.Layout.MultiToggle`
- Added `isToggleActive` for querying the toggle state of transformers.
Useful to show the state in a status bar.
## 0.16
### Breaking Changes

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ExistentialQuantification, Rank2Types, FunctionalDependencies, FlexibleInstances, FlexibleContexts, PatternGuards #-}
{-# LANGUAGE ExistentialQuantification, Rank2Types, FunctionalDependencies, FlexibleInstances, FlexibleContexts, PatternGuards, ScopedTypeVariables #-}
-----------------------------------------------------------------------------
-- |
@ -25,6 +25,7 @@ module XMonad.Layout.MultiToggle (
single,
mkToggle,
mkToggle1,
isToggleActive,
HList,
HCons,
@ -37,6 +38,7 @@ import XMonad.Prelude hiding (find)
import XMonad.StackSet (Workspace(..))
import Control.Arrow
import Data.IORef
import Data.Typeable
-- $usage
@ -206,7 +208,26 @@ instance (Typeable a, Show ts, Typeable ts, HList ts a, LayoutClass l a) => Layo
currIndex = if cur then Nothing else i
}
where cur = i == currIndex mt
| Just (MultiToggleActiveQueryMessage t ref :: MultiToggleActiveQueryMessage a) <- fromMessage m
, i@(Just _) <- find (transformers mt) t
= Nothing <$ io (writeIORef ref (Just (i == currIndex mt)))
| otherwise
= case currLayout mt of
EL l det -> fmap (\x -> mt { currLayout = EL x det }) <$>
handleMessage l m
data MultiToggleActiveQueryMessage a = forall t. (Transformer t a) =>
MultiToggleActiveQueryMessage t (IORef (Maybe Bool))
instance (Typeable a) => Message (MultiToggleActiveQueryMessage a)
-- | Query the state of a 'Transformer' on a given workspace.
--
-- To query the current workspace, use something like this:
--
-- > withWindowSet (isToggleActive t . W.workspace . W.current)
isToggleActive :: Transformer t Window => t -> WindowSpace -> X (Maybe Bool)
isToggleActive t w = do
ref <- io $ newIORef Nothing
sendMessageWithNoRefresh (MultiToggleActiveQueryMessage t ref) w
io $ readIORef ref