mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
X.L.MultiToggle: Add function to query toggle state
This commit is contained in:
parent
a03d58cf6a
commit
3e83068e0a
@ -697,6 +697,11 @@
|
|||||||
pointer to match the focused window). Together these can be used to
|
pointer to match the focused window). Together these can be used to
|
||||||
ensure focus stays in sync with mouse.
|
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
|
## 0.16
|
||||||
|
|
||||||
### Breaking Changes
|
### Breaking Changes
|
||||||
|
@ -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,
|
single,
|
||||||
mkToggle,
|
mkToggle,
|
||||||
mkToggle1,
|
mkToggle1,
|
||||||
|
isToggleActive,
|
||||||
|
|
||||||
HList,
|
HList,
|
||||||
HCons,
|
HCons,
|
||||||
@ -37,6 +38,7 @@ import XMonad.Prelude hiding (find)
|
|||||||
import XMonad.StackSet (Workspace(..))
|
import XMonad.StackSet (Workspace(..))
|
||||||
|
|
||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
|
import Data.IORef
|
||||||
import Data.Typeable
|
import Data.Typeable
|
||||||
|
|
||||||
-- $usage
|
-- $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
|
currIndex = if cur then Nothing else i
|
||||||
}
|
}
|
||||||
where cur = i == currIndex mt
|
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
|
| otherwise
|
||||||
= case currLayout mt of
|
= case currLayout mt of
|
||||||
EL l det -> fmap (\x -> mt { currLayout = EL x det }) <$>
|
EL l det -> fmap (\x -> mt { currLayout = EL x det }) <$>
|
||||||
handleMessage l m
|
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
|
||||||
|
Loading…
x
Reference in New Issue
Block a user