mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 11:30:22 -07:00
Merge pull request #684 from TheMC47/feature/workspace-screen
Export `WindowScreen` type and add a new module: `X.H.WorkspaceScreen`
This commit is contained in:
commit
6a46ff449f
@ -40,6 +40,12 @@
|
|||||||
A wrapper around the 'ReadP' parser combinator, providing behaviour
|
A wrapper around the 'ReadP' parser combinator, providing behaviour
|
||||||
that's closer to the more popular parser combinator libraries.
|
that's closer to the more popular parser combinator libraries.
|
||||||
|
|
||||||
|
* `XMonad.Hooks.StatusBar.WorkspaceScreen`
|
||||||
|
|
||||||
|
In multi-head setup, it might be useful to have screen information of the
|
||||||
|
visible workspaces combined with the workspace name, for example in a status
|
||||||
|
bar. This module provides utility functions to do just that.
|
||||||
|
|
||||||
### Bug Fixes and Minor Changes
|
### Bug Fixes and Minor Changes
|
||||||
|
|
||||||
* `XMonad.Prompt.OrgMode`
|
* `XMonad.Prompt.OrgMode`
|
||||||
@ -121,6 +127,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
|
||||||
|
@ -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
|
||||||
|
@ -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
|
||||||
|
105
XMonad/Hooks/StatusBar/WorkspaceScreen.hs
Normal file
105
XMonad/Hooks/StatusBar/WorkspaceScreen.hs
Normal file
@ -0,0 +1,105 @@
|
|||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
{-# LANGUAGE TypeApplications #-}
|
||||||
|
|
||||||
|
{- |
|
||||||
|
Module : XMonad.Hooks.StatusBar.WorkspaceScreen
|
||||||
|
Description : Combine workspace names with screen information
|
||||||
|
Copyright : (c) Yecine Megdiche <yecine.megdiche@gmail.com>
|
||||||
|
License : BSD3-style (see LICENSE)
|
||||||
|
|
||||||
|
Maintainer : Yecine Megdiche <yecine.megdiche@gmail.com>
|
||||||
|
Stability : unstable
|
||||||
|
Portability : unportable
|
||||||
|
|
||||||
|
In multi-head setup, it might be useful to have screen information of the
|
||||||
|
visible workspaces combined with the workspace name, for example in a status
|
||||||
|
bar. This module provides utility functions to do just that.
|
||||||
|
-}
|
||||||
|
module XMonad.Hooks.StatusBar.WorkspaceScreen
|
||||||
|
(
|
||||||
|
-- * Usage
|
||||||
|
-- $usage
|
||||||
|
combineWithScreen
|
||||||
|
, combineWithScreenName
|
||||||
|
, combineWithScreenNumber
|
||||||
|
, WorkspaceScreenCombiner
|
||||||
|
-- * Limitations
|
||||||
|
-- $limitations
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Graphics.X11.Xrandr
|
||||||
|
import XMonad
|
||||||
|
import XMonad.Hooks.StatusBar.PP
|
||||||
|
import XMonad.Prelude
|
||||||
|
import qualified XMonad.StackSet as W
|
||||||
|
|
||||||
|
{- $usage
|
||||||
|
You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
|
||||||
|
|
||||||
|
> import XMonad
|
||||||
|
> import XMonad.Hooks.StatusBar
|
||||||
|
> import XMonad.Hooks.StatusBar.PP
|
||||||
|
> import XMonad.Hooks.StatusBar.WorkspaceScreen
|
||||||
|
|
||||||
|
For example, to add the screen number in parentheses to each visible
|
||||||
|
workspace number, you can use 'combineWithScreenNumber':
|
||||||
|
|
||||||
|
> myWorkspaceScreenCombiner :: WorkspaceId -> String -> String
|
||||||
|
> myWorkspaceScreenCombiner w sc = w <> wrap "(" ")" sc
|
||||||
|
>
|
||||||
|
> mySB = statusBarProp "xmobar" (combineWithScreenNumber myWorkspaceScreenCombiner xmobarPP)
|
||||||
|
> main = xmonad $ withEasySB mySB defToggleStrutsKey def
|
||||||
|
|
||||||
|
This will annotate the workspace names as following:
|
||||||
|
|
||||||
|
> [1(0)] 2 3 4 <5(1)> 6 7 8 9
|
||||||
|
|
||||||
|
To use the screen's name instead, checkout 'combineWithScreenName':
|
||||||
|
|
||||||
|
> [1(eDP-1)] 2 3 4 <5(HDMI-1)> 6 7 8 9
|
||||||
|
|
||||||
|
For advanced cases, use 'combineWithScreen'.
|
||||||
|
-}
|
||||||
|
|
||||||
|
{- $limitations
|
||||||
|
For simplicity, this module assumes xmonad screen ids match screen/monitor
|
||||||
|
numbers as managed by the X server (for example, as given by @xrandr
|
||||||
|
--listactivemonitors@). Thus, it may not work well when screens show an
|
||||||
|
overlapping range of the framebuffer, e.g. when using a projector. This also
|
||||||
|
means that it doesn't work with "XMonad.Layout.LayoutScreens".
|
||||||
|
(This isn't difficult to fix, PRs welcome.)
|
||||||
|
-}
|
||||||
|
|
||||||
|
-- | Type synonym for a function that combines a workspace name with a screen.
|
||||||
|
type WorkspaceScreenCombiner = WorkspaceId -> WindowScreen -> String
|
||||||
|
|
||||||
|
-- | A helper function that returns a list of screen names.
|
||||||
|
screenNames :: X [Maybe String]
|
||||||
|
screenNames = do
|
||||||
|
XConf { display, theRoot } <- ask
|
||||||
|
let getName mi = getAtomName display (xrr_moninf_name mi)
|
||||||
|
io
|
||||||
|
$ maybe (pure []) (traverse getName)
|
||||||
|
=<< xrrGetMonitors display theRoot True
|
||||||
|
|
||||||
|
-- | Combine a workspace name with the screen name it's visible on.
|
||||||
|
combineWithScreenName :: (WorkspaceId -> String -> String) -> PP -> X PP
|
||||||
|
combineWithScreenName c = combineWithScreen $ do
|
||||||
|
screens <- screenNames
|
||||||
|
return $ \w sc -> maybe w (c w) $ join (screens !? fi (W.screen sc))
|
||||||
|
|
||||||
|
-- | Combine a workspace name with the screen number it's visible on.
|
||||||
|
combineWithScreenNumber :: (WorkspaceId -> String -> String) -> PP -> X PP
|
||||||
|
combineWithScreenNumber c =
|
||||||
|
combineWithScreen . return $ \w sc -> c w (show @Int . fi . W.screen $ sc)
|
||||||
|
|
||||||
|
-- | Combine a workspace name with a screen according to the given
|
||||||
|
-- 'WorkspaceScreenCombiner'.
|
||||||
|
combineWithScreen :: X WorkspaceScreenCombiner -> PP -> X PP
|
||||||
|
combineWithScreen xCombiner pp = do
|
||||||
|
combiner <- xCombiner
|
||||||
|
ss <- withWindowSet (return . W.screens)
|
||||||
|
return $ pp
|
||||||
|
{ ppRename = ppRename pp <=< \s w ->
|
||||||
|
maybe s (combiner s) (find ((== W.tag w) . W.tag . W.workspace) ss)
|
||||||
|
}
|
@ -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.
|
||||||
|
@ -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
|
||||||
|
@ -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
|
||||||
|
@ -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.
|
||||||
|
@ -200,6 +200,7 @@ library
|
|||||||
XMonad.Hooks.SetWMName
|
XMonad.Hooks.SetWMName
|
||||||
XMonad.Hooks.StatusBar
|
XMonad.Hooks.StatusBar
|
||||||
XMonad.Hooks.StatusBar.PP
|
XMonad.Hooks.StatusBar.PP
|
||||||
|
XMonad.Hooks.StatusBar.WorkspaceScreen
|
||||||
XMonad.Hooks.TaffybarPagerHints
|
XMonad.Hooks.TaffybarPagerHints
|
||||||
XMonad.Hooks.ToggleHook
|
XMonad.Hooks.ToggleHook
|
||||||
XMonad.Hooks.UrgencyHook
|
XMonad.Hooks.UrgencyHook
|
||||||
|
Loading…
x
Reference in New Issue
Block a user