mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
Rewrite minimization-related modules
* Use global state instead of per-layout - so now window is minimized on all workspaces (EWMH requires that windows with _NET_WM_STATE_HIDDEN set should be minimized on any workspace but previously they were not) * Use `windows` instead of `modify`. That should fix bugs related to actions that should be done by `windows` and not done by `modify` (fixes #46) * Mark module X.H.RestoreMinimized as deprecated
This commit is contained in:
parent
a226ca62c7
commit
c99606bbdd
12
CHANGES.md
12
CHANGES.md
@ -22,6 +22,16 @@
|
||||
Also, you can use regular 'ManageHook' combinators for changing window
|
||||
activation behavior.
|
||||
|
||||
* `XMonad.Layout.Minimize`
|
||||
|
||||
Though the interface it offers is quite similar, this module has been
|
||||
almost completely rewritten. The new `XMonad.Actions.Minimize` contains
|
||||
several functions that allow interaction with minimization window state.
|
||||
If you are using this module, you must upgrade your configuration to import
|
||||
`X.A.Minimize` and use `maximizeWindow` and `withLastMinimized` instead of
|
||||
sending messages to `Minimized` layout. `XMonad.Hooks.RestoreMinimized` has
|
||||
been completely deprecated, and its functions have no effect.
|
||||
|
||||
### New Modules
|
||||
|
||||
* `XMonad.Hooks.Focus`
|
||||
@ -75,7 +85,7 @@
|
||||
* `XMonad.Hooks.ManageHelpers`
|
||||
|
||||
Make type of ManageHook combinators more general.
|
||||
|
||||
|
||||
* `XMonad.Prompt.Window`
|
||||
|
||||
- New function: `windowMultiPrompt` for using `mkXPromptWithModes`
|
||||
|
132
XMonad/Actions/Minimize.hs
Normal file
132
XMonad/Actions/Minimize.hs
Normal file
@ -0,0 +1,132 @@
|
||||
----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Actions.Minimize
|
||||
-- Copyright : (c) Bogdan Sinitsyn (2016)
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
-- Maintainer : Bogdan Sinitsyn <bogdan.sinitsyn@gmail.com>
|
||||
-- Stability : unstable
|
||||
-- Portability : not portable
|
||||
--
|
||||
-- Adds actions for minimizing and maximizing windows
|
||||
--
|
||||
-- This module should be used with "XMonad.Layout.Minimize". Add 'minimize' to your
|
||||
-- layout modifiers as described in "XMonad.Layout.Minimized" and use actions from
|
||||
-- this module
|
||||
--
|
||||
-- Possible keybindings:
|
||||
--
|
||||
-- > , ((modm, xK_m ), withFocused minimizeWindow)
|
||||
-- > , ((modm .|. shiftMask, xK_m ), withLastMinimized maximizeWindowAndFocus)
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module XMonad.Actions.Minimize
|
||||
( -- * Usage
|
||||
-- $usage
|
||||
minimizeWindow
|
||||
, maximizeWindow
|
||||
, maximizeWindowAndFocus
|
||||
, withLastMinimized
|
||||
, withLastMinimized'
|
||||
, withMinimized
|
||||
) where
|
||||
|
||||
import XMonad
|
||||
import qualified XMonad.StackSet as W
|
||||
|
||||
import qualified XMonad.Layout.BoringWindows as BW
|
||||
import qualified XMonad.Util.ExtensibleState as XS
|
||||
import XMonad.Util.Minimize
|
||||
import XMonad.Util.WindowProperties (getProp32)
|
||||
|
||||
import Foreign.C.Types (CLong)
|
||||
import Control.Applicative((<$>))
|
||||
import Control.Monad (join)
|
||||
import Data.Maybe (fromMaybe, listToMaybe)
|
||||
import qualified Data.List as L
|
||||
import qualified Data.Map as M
|
||||
|
||||
-- $usage
|
||||
-- Import this module with "XMonad.Layout.Minimize" and "XMonad.Layout.BoringWindows":
|
||||
-- > import XMonad.Actions.Minimize
|
||||
-- > import XMonad.Layout.Minimize
|
||||
-- > import qualified XMonad.Layout.BoringWindows as BW
|
||||
--
|
||||
-- Then apply 'minimize' and 'boringWindows' to your layout hook and use some
|
||||
-- actions from this module:
|
||||
-- > main = xmonad def { layoutHook = minimize . BW.boringWindows $ whatever }
|
||||
-- Example keybindings:
|
||||
-- > , ((modm, xK_m ), withFocused minimizeWindow )
|
||||
-- > , ((modm .|. shiftMask, xK_m ), withLastMinimized maximizeWindow)
|
||||
|
||||
setMinimizedState :: Window -> Int -> (CLong -> [CLong] -> [CLong]) -> X ()
|
||||
setMinimizedState win st f = do
|
||||
setWMState win st
|
||||
withDisplay $ \dpy -> do
|
||||
wm_state <- getAtom "_NET_WM_STATE"
|
||||
hidden <- fromIntegral <$> getAtom "_NET_WM_STATE_HIDDEN"
|
||||
wstate <- fromMaybe [] <$> getProp32 wm_state win
|
||||
io $ changeProperty32 dpy win wm_state aTOM propModeReplace (f hidden wstate)
|
||||
|
||||
setMinimized :: Window -> X ()
|
||||
setMinimized win = setMinimizedState win iconicState (:)
|
||||
|
||||
setNotMinimized :: Window -> X ()
|
||||
setNotMinimized win = setMinimizedState win normalState L.delete
|
||||
|
||||
-- It does not just set minimizedStack to newWindows because it should save
|
||||
-- order in which elements were added (newer first)
|
||||
modified :: (RectMap -> RectMap) -> X Bool
|
||||
modified f = XS.modified $
|
||||
\Minimized { rectMap = oldRectMap, minimizedStack = oldStack } ->
|
||||
let newRectMap = f oldRectMap
|
||||
newWindows = M.keys newRectMap
|
||||
in Minimized { rectMap = newRectMap
|
||||
, minimizedStack = (newWindows L.\\ oldStack)
|
||||
++
|
||||
(newWindows `L.intersect` oldStack)
|
||||
}
|
||||
|
||||
|
||||
-- | Minimize a window
|
||||
minimizeWindow :: Window -> X ()
|
||||
minimizeWindow w = withWindowSet $ \ws ->
|
||||
whenX (modified $ M.insert w (M.lookup w $ W.floating ws)) $ do
|
||||
setMinimized w
|
||||
windows $ W.sink w
|
||||
BW.focusDown
|
||||
|
||||
|
||||
-- | Maximize window and apply a function to maximized window and 'WindowSet'
|
||||
maximizeWindowAndChangeWSet :: (Window -> WindowSet -> WindowSet) -> Window -> X ()
|
||||
maximizeWindowAndChangeWSet f w = do
|
||||
mrect <- XS.gets (join . M.lookup w . rectMap)
|
||||
whenX (modified $ M.delete w) $ do
|
||||
setNotMinimized w
|
||||
broadcastMessage BW.UpdateBoring
|
||||
windows $ f w . maybe id (W.float w) mrect
|
||||
|
||||
-- | Just maximize a window without focusing
|
||||
maximizeWindow :: Window -> X ()
|
||||
maximizeWindow = maximizeWindowAndChangeWSet $ const id
|
||||
|
||||
-- | Maximize a window and then focus it
|
||||
maximizeWindowAndFocus :: Window -> X ()
|
||||
maximizeWindowAndFocus = maximizeWindowAndChangeWSet W.focusWindow
|
||||
|
||||
-- | Perform an action with last minimized window on current workspace
|
||||
-- or do nothing if there is no minimized windows on current workspace
|
||||
withLastMinimized :: (Window -> X ()) -> X ()
|
||||
withLastMinimized action = withLastMinimized' (flip whenJust action)
|
||||
|
||||
-- | Like withLastMinimized but the provided action is always invoked with a
|
||||
-- 'Maybe Window', that will be nothing if there is no last minimized window.
|
||||
withLastMinimized' :: (Maybe Window -> X ()) -> X ()
|
||||
withLastMinimized' action = withMinimized (action . listToMaybe)
|
||||
|
||||
withMinimized :: ([Window] -> X a) -> X a
|
||||
withMinimized action = do
|
||||
minimized <- XS.gets minimizedStack
|
||||
currentStack <- withWindowSet $ return . W.index
|
||||
action $ minimized `L.intersect` currentStack
|
@ -28,7 +28,7 @@ import XMonad
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Actions.GridSelect
|
||||
import XMonad.Layout.Maximize
|
||||
import XMonad.Layout.Minimize
|
||||
import XMonad.Actions.Minimize
|
||||
import XMonad.Util.XUtils (fi)
|
||||
|
||||
-- $usage
|
||||
|
@ -44,6 +44,7 @@ import XMonad.Layout.WindowSwitcherDecoration
|
||||
|
||||
import XMonad.Actions.BluetileCommands
|
||||
import XMonad.Actions.CycleWS
|
||||
import XMonad.Actions.Minimize
|
||||
import XMonad.Actions.WindowMenu
|
||||
|
||||
import XMonad.Hooks.CurrentWorkspaceOnTop
|
||||
@ -143,7 +144,7 @@ bluetileKeys conf@(XConfig {XMonad.modMask = modMask'}) = M.fromList $
|
||||
|
||||
-- Minimizing
|
||||
, ((modMask', xK_m ), withFocused minimizeWindow)
|
||||
, ((modMask' .|. shiftMask, xK_m ), sendMessage RestoreNextMinimizedWin)
|
||||
, ((modMask' .|. shiftMask, xK_m ), withLastMinimized maximizeWindow)
|
||||
]
|
||||
++
|
||||
-- mod-[1..9] ++ [0] %! Switch to workspace N
|
||||
|
@ -23,7 +23,7 @@ import Data.Monoid
|
||||
import Control.Monad(when)
|
||||
|
||||
import XMonad
|
||||
import XMonad.Layout.Minimize
|
||||
import XMonad.Actions.Minimize
|
||||
|
||||
-- $usage
|
||||
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
|
||||
@ -43,10 +43,10 @@ minimizeEventHook (ClientMessageEvent {ev_window = w,
|
||||
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
|
||||
a_cs <- getAtom "WM_CHANGE_STATE"
|
||||
|
||||
when (mt == a_aw) $ sendMessage (RestoreMinimizedWin w)
|
||||
when (mt == a_aw) $ maximizeWindow w
|
||||
when (mt == a_cs) $ do
|
||||
let message = fromIntegral . head $ dt
|
||||
when (message == normalState) $ sendMessage (RestoreMinimizedWin w)
|
||||
when (message == normalState) $ maximizeWindow w
|
||||
when (message == iconicState) $ minimizeWindow w
|
||||
|
||||
return (All True)
|
||||
|
@ -1,4 +1,4 @@
|
||||
----------------------------------------------------------------------------
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Hooks.RestoreMinimized
|
||||
-- Copyright : (c) Jan Vornberger 2009
|
||||
@ -15,6 +15,7 @@
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module XMonad.Hooks.RestoreMinimized
|
||||
{-# DEPRECATED "Use XMonad.Hooks.Minimize instead, this module has no effect" #-}
|
||||
( -- * Usage
|
||||
-- $usage
|
||||
RestoreMinimized (..)
|
||||
@ -22,10 +23,8 @@ module XMonad.Hooks.RestoreMinimized
|
||||
) where
|
||||
|
||||
import Data.Monoid
|
||||
import Control.Monad(when)
|
||||
|
||||
import XMonad
|
||||
import XMonad.Layout.Minimize
|
||||
|
||||
-- $usage
|
||||
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
|
||||
@ -39,11 +38,4 @@ import XMonad.Layout.Minimize
|
||||
data RestoreMinimized = RestoreMinimized deriving ( Show, Read )
|
||||
|
||||
restoreMinimizedEventHook :: Event -> X All
|
||||
restoreMinimizedEventHook (ClientMessageEvent {ev_window = w,
|
||||
ev_message_type = mt}) = do
|
||||
a_aw <- getAtom "_NET_ACTIVE_WINDOW"
|
||||
a_cs <- getAtom "WM_CHANGE_STATE"
|
||||
when (mt == a_aw || mt == a_cs) $ do
|
||||
sendMessage (RestoreMinimizedWin w)
|
||||
return (All True)
|
||||
restoreMinimizedEventHook _ = return (All True)
|
||||
|
@ -24,7 +24,7 @@ import XMonad
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Layout.Decoration
|
||||
import XMonad.Actions.WindowMenu
|
||||
import XMonad.Layout.Minimize
|
||||
import XMonad.Actions.Minimize
|
||||
import XMonad.Layout.Maximize
|
||||
import XMonad.Hooks.ManageDocks
|
||||
import XMonad.Util.Font
|
||||
|
@ -38,7 +38,7 @@ import XMonad.Layout.DecorationAddons
|
||||
import XMonad.Util.Image
|
||||
|
||||
import XMonad.Actions.WindowMenu
|
||||
import XMonad.Layout.Minimize
|
||||
import XMonad.Actions.Minimize
|
||||
import XMonad.Layout.Maximize
|
||||
|
||||
-- $usage
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable, TypeSynonymInstances, FlexibleContexts, PatternGuards #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleContexts, PatternGuards #-}
|
||||
----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Layout.Minimize
|
||||
@ -18,20 +18,14 @@ module XMonad.Layout.Minimize (
|
||||
-- * Usage
|
||||
-- $usage
|
||||
minimize,
|
||||
minimizeWindow,
|
||||
MinimizeMsg(RestoreMinimizedWin,RestoreNextMinimizedWin),
|
||||
Minimize,
|
||||
) where
|
||||
|
||||
import XMonad
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Util.Minimize (Minimized(..))
|
||||
import XMonad.Layout.LayoutModifier
|
||||
import XMonad.Layout.BoringWindows as BW
|
||||
import XMonad.Util.WindowProperties (getProp32)
|
||||
import Data.List
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe
|
||||
import Foreign.C.Types (CLong)
|
||||
import qualified XMonad.Util.ExtensibleState as XS
|
||||
|
||||
-- $usage
|
||||
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
|
||||
@ -47,97 +41,33 @@ import Foreign.C.Types (CLong)
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
|
||||
--
|
||||
-- In the key-bindings, do something like:
|
||||
--
|
||||
-- > , ((modm, xK_m ), withFocused minimizeWindow)
|
||||
-- > , ((modm .|. shiftMask, xK_m ), sendMessage RestoreNextMinimizedWin)
|
||||
--
|
||||
-- The first action will minimize the focused window, while the second one will restore
|
||||
-- the next minimized window.
|
||||
--
|
||||
-- For detailed instruction on editing the key binding see:
|
||||
--
|
||||
-- "XMonad.Doc.Extending#Editing_key_bindings".
|
||||
--
|
||||
-- The module is designed to work together with "XMonad.Layout.BoringWindows" so
|
||||
-- that minimized windows will be skipped over when switching the focused window with
|
||||
-- the keyboard. Include 'BW.boringWindows' in your layout hook and see the
|
||||
-- documentation of "XMonad.Layout.BoringWindows" on how to modify your keybindings.
|
||||
--
|
||||
-- See "XMonad.Actions.Minimize" for possible actions for minimizing/restoring windows
|
||||
--
|
||||
-- Also see "XMonad.Hooks.Minimize" if you want to be able to minimize
|
||||
-- and restore windows from your taskbar.
|
||||
|
||||
data Minimize a = Minimize [Window] (M.Map Window W.RationalRect) deriving ( Read, Show )
|
||||
minimize :: LayoutClass l Window => l Window -> ModifiedLayout Minimize l Window
|
||||
minimize = ModifiedLayout $ Minimize [] M.empty
|
||||
data Minimize a = Minimize deriving ( Read, Show )
|
||||
minimize :: l Window -> ModifiedLayout Minimize l Window
|
||||
minimize = ModifiedLayout Minimize
|
||||
|
||||
data MinimizeMsg = MinimizeWin Window
|
||||
| RestoreMinimizedWin Window
|
||||
| RestoreNextMinimizedWin
|
||||
deriving (Typeable, Eq)
|
||||
instance Message MinimizeMsg
|
||||
|
||||
minimizeWindow :: Window -> X ()
|
||||
minimizeWindow w = sendMessage (MinimizeWin w) >> BW.focusDown
|
||||
|
||||
setMinimizedState :: Window -> Int -> (CLong -> [CLong] -> [CLong]) -> X ()
|
||||
setMinimizedState win st f = do
|
||||
setWMState win st
|
||||
withDisplay $ \dpy -> do
|
||||
wm_state <- getAtom "_NET_WM_STATE"
|
||||
mini <- getAtom "_NET_WM_STATE_HIDDEN"
|
||||
wstate <- fromMaybe [] `fmap` getProp32 wm_state win
|
||||
let ptype = 4 -- The atom property type for changeProperty
|
||||
fi_mini = fromIntegral mini
|
||||
io $ changeProperty32 dpy win wm_state ptype propModeReplace (f fi_mini wstate)
|
||||
|
||||
setMinimized :: Window -> X ()
|
||||
setMinimized win = setMinimizedState win iconicState (:)
|
||||
|
||||
setNotMinimized :: Window -> X ()
|
||||
setNotMinimized win = setMinimizedState win normalState delete
|
||||
|
||||
instance LayoutModifier Minimize Window where
|
||||
modifierDescription _ = "Minimize"
|
||||
|
||||
modifyLayout (Minimize minimized _) wksp rect = do
|
||||
modifyLayout Minimize wksp rect = do
|
||||
minimized <- XS.gets minimizedStack
|
||||
let stack = W.stack wksp
|
||||
filtStack = stack >>=W.filter (\w -> not (w `elem` minimized))
|
||||
filtStack = stack >>= W.filter (`notElem` minimized)
|
||||
runLayout (wksp {W.stack = filtStack}) rect
|
||||
|
||||
handleMess (Minimize minimized unfloated) m
|
||||
| Just (MinimizeWin w) <- fromMessage m, not (w `elem` minimized) = do
|
||||
setMinimized w
|
||||
ws <- gets windowset
|
||||
case M.lookup w (W.floating ws) of
|
||||
Nothing -> return $ Just $ Minimize (w:minimized) unfloated
|
||||
Just r -> do
|
||||
modify (\s -> s { windowset = W.sink w ws})
|
||||
return $ Just $ Minimize (w:minimized) (M.insert w r unfloated)
|
||||
| Just (RestoreMinimizedWin w) <- fromMessage m = do
|
||||
setNotMinimized w
|
||||
case M.lookup w unfloated of
|
||||
Nothing -> return $ Just $ Minimize (minimized \\ [w]) unfloated
|
||||
Just r -> do
|
||||
ws <- gets windowset
|
||||
modify (\s -> s { windowset = W.float w r ws})
|
||||
return $ Just $ Minimize (minimized \\ [w]) (M.delete w unfloated)
|
||||
| Just RestoreNextMinimizedWin <- fromMessage m = do
|
||||
ws <- gets windowset
|
||||
if not (null minimized)
|
||||
then case M.lookup (head minimized) unfloated of
|
||||
Nothing -> do
|
||||
let w = head minimized
|
||||
setNotMinimized w
|
||||
modify (\s -> s { windowset = W.focusWindow w ws})
|
||||
return $ Just $ Minimize (tail minimized) unfloated
|
||||
Just r -> do
|
||||
let w = head minimized
|
||||
setNotMinimized w
|
||||
modify (\s -> s { windowset = (W.focusWindow w . W.float w r) ws})
|
||||
return $ Just $ Minimize (tail minimized) (M.delete w unfloated)
|
||||
else return Nothing
|
||||
handleMess Minimize m
|
||||
| Just BW.UpdateBoring <- fromMessage m = do
|
||||
minimized <- XS.gets minimizedStack
|
||||
ws <- gets (W.workspace . W.current . windowset)
|
||||
flip sendMessageWithNoRefresh ws $ BW.Replace "Minimize" minimized
|
||||
return Nothing
|
||||
|
37
XMonad/Util/Minimize.hs
Normal file
37
XMonad/Util/Minimize.hs
Normal file
@ -0,0 +1,37 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Util.Minimize
|
||||
-- Copyright : (c) Bogdan Sinitsyn (2016)
|
||||
-- License : BSD3-style (see LICENSE)
|
||||
--
|
||||
-- Maintainer : bogdan.sinitsyn@gmail.com
|
||||
-- Stability : unstable
|
||||
-- Portability : not portable
|
||||
--
|
||||
-- Stores some common utilities for modules used for window minimizing/maximizing
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
module XMonad.Util.Minimize
|
||||
( RectMap
|
||||
, Minimized(..)
|
||||
) where
|
||||
|
||||
import XMonad
|
||||
import qualified XMonad.StackSet as W
|
||||
|
||||
import qualified Data.Map as M
|
||||
|
||||
type RectMap = M.Map Window (Maybe W.RationalRect)
|
||||
|
||||
data Minimized = Minimized
|
||||
{ rectMap :: RectMap
|
||||
, minimizedStack :: [Window]
|
||||
}
|
||||
deriving (Eq, Typeable, Read, Show)
|
||||
|
||||
instance ExtensionClass Minimized where
|
||||
initialValue = Minimized { rectMap = M.empty
|
||||
, minimizedStack = []
|
||||
}
|
||||
extensionType = PersistentExtension
|
@ -111,6 +111,7 @@ library
|
||||
XMonad.Actions.Launcher
|
||||
XMonad.Actions.LinkWorkspaces
|
||||
XMonad.Actions.MessageFeedback
|
||||
XMonad.Actions.Minimize
|
||||
XMonad.Actions.MouseGestures
|
||||
XMonad.Actions.MouseResize
|
||||
XMonad.Actions.Navigation2D
|
||||
@ -313,6 +314,7 @@ library
|
||||
XMonad.Util.Invisible
|
||||
XMonad.Util.Loggers
|
||||
XMonad.Util.Loggers.NamedScratchpad
|
||||
XMonad.Util.Minimize
|
||||
XMonad.Util.NamedActions
|
||||
XMonad.Util.NamedScratchpad
|
||||
XMonad.Util.NamedWindows
|
||||
|
Loading…
x
Reference in New Issue
Block a user