diff --git a/CHANGES.md b/CHANGES.md index 7da89b54..392d82ba 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -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 diff --git a/XMonad/Layout/MultiToggle.hs b/XMonad/Layout/MultiToggle.hs index 94857463..61ae2270 100644 --- a/XMonad/Layout/MultiToggle.hs +++ b/XMonad/Layout/MultiToggle.hs @@ -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