XMonad.Prelude: add the WindowScreen type

`WindowScreen` is a type synonym for the specialized `Screen` type, that
results from the `WindowSet` definition in XMonad.Core. Having this type
defined and exported in a central module saves extension developers from
trying to reconstruct it, whenever the general `Screen i l a sid sd` is
not suitable.

Note: this should be moved to `XMonad.Core` in the next core release.
This commit is contained in:
Yecine Megdiche 2022-02-03 15:37:22 +01:00
parent d2b174f269
commit 2d33f18dec
7 changed files with 16 additions and 12 deletions

View File

@ -121,6 +121,9 @@
- Added `keymaskToString` and `keyToString` to show a key mask and a - Added `keymaskToString` and `keyToString` to show a key mask and a
key in the style of `XMonad.Util.EZConfig`. key in the style of `XMonad.Util.EZConfig`.
- Added `WindowScreen`, which is a type synonym for the specialized `Screen`
type, that results from the `WindowSet` definition in `XMonad.Core`.
* `XMonad.Util.XUtils` * `XMonad.Util.XUtils`
- Added `withSimpleWindow`, `showSimpleWindow`, `WindowConfig`, and - Added `withSimpleWindow`, `showSimpleWindow`, `WindowConfig`, and

View File

@ -271,7 +271,7 @@ handleSelectWindow c = do
$ M.elems $ M.elems
$ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m $ M.mapWithKey (\sid ks -> buildOverlays ks <$> sortedOverlayWindows sid) m
where where
screenById :: ScreenId -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail) screenById :: ScreenId -> Maybe WindowScreen
screenById sid = find ((== sid) . W.screen) (W.screens ws) screenById sid = find ((== sid) . W.screen) (W.screens ws)
visibleWindowsOnScreen :: ScreenId -> [Window] visibleWindowsOnScreen :: ScreenId -> [Window]
visibleWindowsOnScreen sid = filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace visibleWindowsOnScreen sid = filter (`elem` toList mappedWins) $ W.integrate' $ screenById sid >>= W.stack . W.workspace

View File

@ -388,7 +388,7 @@ data Navigation2DConfig = Navigation2DConfig
} }
-- | Shorthand for the tedious screen type -- | Shorthand for the tedious screen type
type Screen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail type Screen = WindowScreen
-- | Convenience function for enabling Navigation2D with typical keybindings. -- | Convenience function for enabling Navigation2D with typical keybindings.
-- Takes a Navigation2DConfig, an (up, left, down, right) tuple, a mapping from -- Takes a Navigation2DConfig, an (up, left, down, right) tuple, a mapping from

View File

@ -148,7 +148,7 @@ withWspOnScreen screenId operation ws = case workspaceOnScreen screenId ws of
Nothing -> ws Nothing -> ws
-- | Get the workspace that is active on a given screen. -- | Get the workspace that is active on a given screen.
screenOnMonitor :: ScreenId -> WindowSet -> Maybe (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail) screenOnMonitor :: ScreenId -> WindowSet -> Maybe WindowScreen
screenOnMonitor screenId ws = find ((screenId ==) . W.screen) (W.current ws : W.visible ws) screenOnMonitor screenId ws = find ((screenId ==) . W.screen) (W.current ws : W.visible ws)
-- | Focus a window, switching workspace on the correct Xinerama screen if neccessary. -- | Focus a window, switching workspace on the correct Xinerama screen if neccessary.

View File

@ -32,6 +32,7 @@ module XMonad.Prelude (
specialKeys, specialKeys,
multimediaKeys, multimediaKeys,
functionKeys, functionKeys,
WindowScreen,
) where ) where
import Foreign (alloca, peek) import Foreign (alloca, peek)
@ -57,6 +58,7 @@ import Data.Bits
import Data.List.NonEmpty (NonEmpty ((:|))) import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.Tuple (swap) import Data.Tuple (swap)
import GHC.Stack import GHC.Stack
import qualified XMonad.StackSet as W
-- | Short for 'fromIntegral'. -- | Short for 'fromIntegral'.
fi :: (Integral a, Num b) => a -> b fi :: (Integral a, Num b) => a -> b
@ -415,3 +417,7 @@ multimediaKeys = filter ((/= noSymbol) . snd) . map (id &&& stringToKeysym) $
, "XF86_Prev_VMode" , "XF86_Prev_VMode"
, "XF86Bluetooth" , "XF86Bluetooth"
] ]
-- | The specialized 'W.Screen' derived from 'WindowSet'.
type WindowScreen -- FIXME move to core
= W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail

View File

@ -48,7 +48,7 @@ module XMonad.Util.Loggers (
) where ) where
import XMonad (liftIO, Window, gets) import XMonad (liftIO, gets)
import XMonad.Core import XMonad.Core
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.Hooks.StatusBar.PP import XMonad.Hooks.StatusBar.PP
@ -56,7 +56,7 @@ import XMonad.Util.Font (Align (..))
import XMonad.Util.NamedWindows (getName) import XMonad.Util.NamedWindows (getName)
import Control.Exception as E import Control.Exception as E
import XMonad.Prelude (find, fromMaybe, isPrefixOf, isSuffixOf) import XMonad.Prelude (find, fromMaybe, isPrefixOf, isSuffixOf, WindowScreen)
import Data.Time (defaultTimeLocale, formatTime, getCurrentTime) import Data.Time (defaultTimeLocale, formatTime, getCurrentTime)
import System.Directory (getDirectoryContents) import System.Directory (getDirectoryContents)
import System.IO (hGetLine) import System.IO (hGetLine)
@ -272,9 +272,6 @@ logLayoutOnScreen :: ScreenId -> Logger
logLayoutOnScreen = logLayoutOnScreen =
withScreen $ logConst . description . W.layout . W.workspace withScreen $ logConst . description . W.layout . W.workspace
-- | A shortcut to a screen
type WindowScreen = W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-- | A helper function to create screen-specific loggers. -- | A helper function to create screen-specific loggers.
withScreen :: (WindowScreen -> Logger) -> ScreenId -> Logger withScreen :: (WindowScreen -> Logger) -> ScreenId -> Logger
withScreen f n = do withScreen f n = do

View File

@ -53,7 +53,7 @@ module XMonad.Util.PureX (
-- xmonad -- xmonad
import XMonad import XMonad
import XMonad.Prelude (Any (..), liftA2) import XMonad.Prelude (Any (..), liftA2, WindowScreen)
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import qualified XMonad.Actions.FocusNth import qualified XMonad.Actions.FocusNth
@ -220,9 +220,7 @@ peek :: XLike m => m (Maybe Window)
peek = withWindowSet' (return . W.peek) peek = withWindowSet' (return . W.peek)
-- | Get the current screen. -- | Get the current screen.
curScreen curScreen :: XLike m => m WindowScreen
:: XLike m
=> m (W.Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail)
curScreen = withWindowSet' (return . W.current) curScreen = withWindowSet' (return . W.current)
-- | Get the current workspace. -- | Get the current workspace.