mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 20:21:51 -07:00
watch only for tiled windows in X.L.IfMax
This commit is contained in:
@@ -14,7 +14,7 @@
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
|
||||
|
||||
module XMonad.Layout.IfMax
|
||||
( -- * Usage
|
||||
@@ -24,6 +24,9 @@ module XMonad.Layout.IfMax
|
||||
) where
|
||||
|
||||
import Control.Applicative((<$>))
|
||||
import Control.Arrow
|
||||
import qualified Data.List as L
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe
|
||||
|
||||
import XMonad
|
||||
@@ -48,25 +51,25 @@ import qualified XMonad.StackSet as W
|
||||
data IfMax l1 l2 w = IfMax Int (l1 w) (l2 w)
|
||||
deriving (Read, Show)
|
||||
|
||||
instance (LayoutClass l1 a, LayoutClass l2 a) => LayoutClass (IfMax l1 l2) a where
|
||||
instance (LayoutClass l1 Window, LayoutClass l2 Window) => LayoutClass (IfMax l1 l2) Window where
|
||||
|
||||
runLayout (W.Workspace _ (IfMax n l1 l2) s) rect = arrange (W.integrate' s)
|
||||
runLayout (W.Workspace _ (IfMax n l1 l2) s) rect = withWindowSet $ \ws -> arrange (W.integrate' s) (M.keys . W.floating $ ws)
|
||||
where
|
||||
arrange [] = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage ReleaseResources)
|
||||
l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage ReleaseResources)
|
||||
return ([], Just $ IfMax n l1' l2')
|
||||
arrange ws | length ws <= n = do
|
||||
arrange [] _ = do l1' <- maybe l1 id `fmap` handleMessage l1 (SomeMessage ReleaseResources)
|
||||
l2' <- maybe l2 id `fmap` handleMessage l2 (SomeMessage ReleaseResources)
|
||||
return ([], Just $ IfMax n l1' l2')
|
||||
arrange ws fw | length (ws L.\\ fw) <= n = do
|
||||
(wrs, ml1') <- runLayout (W.Workspace "" l1 s) rect
|
||||
let l1' = fromMaybe l1 ml1'
|
||||
return (wrs, Just $ IfMax n l1' l2)
|
||||
| otherwise = do
|
||||
| otherwise = do
|
||||
(wrs, ml2') <- runLayout (W.Workspace "" l2 s) rect
|
||||
let l2' = fromMaybe l2 ml2'
|
||||
return (wrs, Just $ IfMax n l1 l2')
|
||||
|
||||
handleMessage (IfMax n l1 l2) m = do
|
||||
len <- gets (length . W.integrate' . W.stack . W.workspace . W.current . windowset)
|
||||
if len <= n
|
||||
(allWindows, floatingWindows) <- gets ((W.integrate' . W.stack . W.workspace . W.current &&& M.keys . W.floating) . windowset)
|
||||
if length (allWindows L.\\ floatingWindows) <= n
|
||||
then do
|
||||
l1' <- handleMessage l1 m
|
||||
return $ flip (IfMax n) l2 <$> l1'
|
||||
|
Reference in New Issue
Block a user