X.L.IndependentScreens: Add workspacesOn, withScreen, fix marshallPP always sorting lexically

- Added `workspacesOn` for filtering workspaces on the current screen.

- Added `withScreen` to specify names for a given single screen.

- Added new aliases `PhysicalWindowSpace` and `VirtualWindowSpace`
  for a `WindowSpace` for easier to read function signatures.

- Fixed a bug where `marshallPP` always sorted workspace names
  lexically.

Fixes: https://github.com/xmonad/xmonad-contrib/issues/420
This commit is contained in:
oogeek 2021-04-01 00:49:58 +08:00 committed by slotThe
parent b6cd47db29
commit 8899078b00
4 changed files with 80 additions and 24 deletions

View File

@ -609,6 +609,22 @@
- The decoration window now sets a `WM_CLASS` property. This allows - The decoration window now sets a `WM_CLASS` property. This allows
other applications, like compositors, to properly match on it. other applications, like compositors, to properly match on it.
* `XMonad.Layout.IndependentScreens`
- Fixed a bug where `marshallPP` always sorted workspace names
lexically. This changes the default behaviour of `marshallPP`—the
given `ppSort` now operates in the _physical_ workspace names.
The documentation of `marshallSort` contains an example of how to
get the old behaviour, where `ppSort` operates in virtual names,
back.
- Added `workspacesOn` for filtering workspaces on the current screen.
- Added `withScreen` to specify names for a given single screen.
- Added new aliases `PhysicalWindowSpace` and `VirtualWindowSpace`
for a `WindowSpace` for easier to read function signatures.
## 0.16 ## 0.16
### Breaking Changes ### Breaking Changes

View File

@ -18,7 +18,7 @@ module XMonad.Actions.CopyWindow (
-- * Usage -- * Usage
-- $usage -- $usage
copy, copyToAll, copyWindow, runOrCopy copy, copyToAll, copyWindow, runOrCopy
, killAllOtherCopies, kill1 , killAllOtherCopies, kill1, taggedWindows, copiesOfOn
-- * Highlight workspaces containing copies in logHook -- * Highlight workspaces containing copies in logHook
-- $logHook -- $logHook
, wsContainingCopies , wsContainingCopies

View File

@ -25,7 +25,7 @@ import XMonad.Hooks.DynamicLog
import XMonad.Hooks.ManageDocks import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers import XMonad.Hooks.ManageHelpers
import XMonad.Layout.Grid import XMonad.Layout.Grid
import XMonad.Layout.IndependentScreens import XMonad.Layout.IndependentScreens hiding (withScreen)
import XMonad.Layout.Magnifier import XMonad.Layout.Magnifier
import XMonad.Layout.NoBorders import XMonad.Layout.NoBorders
import XMonad.Prelude import XMonad.Prelude

View File

@ -17,15 +17,18 @@ module XMonad.Layout.IndependentScreens (
-- * Usage -- * Usage
-- $usage -- $usage
VirtualWorkspace, PhysicalWorkspace, VirtualWorkspace, PhysicalWorkspace,
VirtualWindowSpace, PhysicalWindowSpace,
workspaces', workspaces',
withScreens, onCurrentScreen, withScreen, withScreens,
onCurrentScreen,
marshallPP, marshallPP,
whenCurrentOn, whenCurrentOn,
countScreens, countScreens,
workspacesOn,
-- * Converting between virtual and physical workspaces -- * Converting between virtual and physical workspaces
-- $converting -- $converting
marshall, unmarshall, unmarshallS, unmarshallW, marshall, unmarshall, unmarshallS, unmarshallW,
marshallWindowSpace, unmarshallWindowSpace, marshallSort marshallWindowSpace, unmarshallWindowSpace, marshallSort,
) where ) where
-- for the screen stuff -- for the screen stuff
@ -33,7 +36,7 @@ import Control.Arrow ((***))
import Graphics.X11.Xinerama import Graphics.X11.Xinerama
import XMonad import XMonad
import XMonad.Prelude import XMonad.Prelude
import XMonad.StackSet hiding (filter, workspaces) import qualified XMonad.StackSet as W
import XMonad.Hooks.DynamicLog import XMonad.Hooks.DynamicLog
-- $usage -- $usage
@ -78,6 +81,11 @@ import XMonad.Hooks.DynamicLog
type VirtualWorkspace = WorkspaceId type VirtualWorkspace = WorkspaceId
type PhysicalWorkspace = WorkspaceId type PhysicalWorkspace = WorkspaceId
-- | A 'WindowSpace' whose tags are 'PhysicalWorkspace's.
type PhysicalWindowSpace = WindowSpace
-- | A 'WindowSpace' whose tags are 'VirtualWorkspace's.
type VirtualWindowSpace = WindowSpace
-- $converting -- $converting
-- You shouldn't need to use the functions below very much. They are used -- You shouldn't need to use the functions below very much. They are used
-- internally. However, in some cases, they may be useful, and so are exported -- internally. However, in some cases, they may be useful, and so are exported
@ -100,13 +108,20 @@ unmarshallW = snd . unmarshall
workspaces' :: XConfig l -> [VirtualWorkspace] workspaces' :: XConfig l -> [VirtualWorkspace]
workspaces' = nub . map unmarshallW . workspaces workspaces' = nub . map unmarshallW . workspaces
-- | Specify workspace names for each screen
withScreen :: ScreenId -- ^ The screen to make workspaces for
-> [VirtualWorkspace] -- ^ The desired virtual workspace names
-> [PhysicalWorkspace] -- ^ A list of all internal physical workspace names
withScreen n vws = [marshall n pws | pws <- vws]
-- | Make all workspaces across the monitors bear the same names
withScreens :: ScreenId -- ^ The number of screens to make workspaces for withScreens :: ScreenId -- ^ The number of screens to make workspaces for
-> [VirtualWorkspace] -- ^ The desired virtual workspace names -> [VirtualWorkspace] -- ^ The desired virtual workspace names
-> [PhysicalWorkspace] -- ^ A list of all internal physical workspace names -> [PhysicalWorkspace] -- ^ A list of all internal physical workspace names
withScreens n vws = [marshall sc pws | pws <- vws, sc <- [0..n-1]] withScreens n vws = concatMap (`withScreen` vws) [0..n-1]
onCurrentScreen :: (VirtualWorkspace -> WindowSet -> a) -> (PhysicalWorkspace -> WindowSet -> a) onCurrentScreen :: (VirtualWorkspace -> WindowSet -> a) -> (PhysicalWorkspace -> WindowSet -> a)
onCurrentScreen f vws = screen . current >>= f . flip marshall vws onCurrentScreen f vws = W.screen . W.current >>= f . flip marshall vws
-- | In case you don't know statically how many screens there will be, you can call this in main before starting xmonad. For example, part of my config reads -- | In case you don't know statically how many screens there will be, you can call this in main before starting xmonad. For example, part of my config reads
-- --
@ -121,20 +136,25 @@ onCurrentScreen f vws = screen . current >>= f . flip marshall vws
countScreens :: (MonadIO m, Integral i) => m i countScreens :: (MonadIO m, Integral i) => m i
countScreens = fmap genericLength . liftIO $ openDisplay "" >>= liftA2 (<*) getScreenInfo closeDisplay countScreens = fmap genericLength . liftIO $ openDisplay "" >>= liftA2 (<*) getScreenInfo closeDisplay
-- | This turns a naive pretty-printer into one that is aware of the -- | This turns a pretty-printer into one that is aware of the independent screens. The
-- independent screens. That is, you can write your pretty printer to behave -- converted pretty-printer first filters out physical workspaces on other screens, then
-- the way you want on virtual workspaces; this function will convert that -- converts all the physical workspaces on this screen to their virtual names.
-- pretty-printer into one that first filters out physical workspaces on other -- Note that 'ppSort' still operates on physical (marshalled) workspace names,
-- screens, then converts all the physical workspaces on this screen to their -- otherwise functions from "XMonad.Util.WorkspaceCompare" wouldn't work.
-- virtual names. -- If you need to sort on virtual names, see 'marshallSort'.
-- --
-- For example, if you have handles @hLeft@ and @hRight@ for bars on the left and right screens, respectively, and @pp@ is a pretty-printer function that takes a handle, you could write -- For example, if you have have two bars on the left and right screens, respectively, and @pp@ is
-- a pretty-printer, you could apply 'marshallPP' when creating a @StatusBarConfig@ from "XMonad.Hooks.StatusBar".
--
-- A sample config looks like this:
--
-- > mySBL = statusBarProp "xmobar" $ pure (marshallPP (S 0) pp)
-- > mySBR = statusBarProp "xmobar" $ pure (marshallPP (S 1) pp)
-- > main = xmonad $ withEasySB (mySBL <> mySBR) defToggleStrutsKey def
-- --
-- > logHook = let log screen handle = dynamicLogWithPP . marshallPP screen . pp $ handle
-- > in log 0 hLeft >> log 1 hRight
marshallPP :: ScreenId -> PP -> PP marshallPP :: ScreenId -> PP -> PP
marshallPP s pp = pp { ppRename = ppRename pp . unmarshallW marshallPP s pp = pp { ppRename = ppRename pp . unmarshallW
, ppSort = fmap (marshallSort s) (ppSort pp) } , ppSort = (. workspacesOn s) <$> ppSort pp }
-- | Take a pretty-printer and turn it into one that only runs when the current -- | Take a pretty-printer and turn it into one that only runs when the current
-- workspace is one associated with the given screen. The way this works is a -- workspace is one associated with the given screen. The way this works is a
@ -161,7 +181,7 @@ whenCurrentOn s pp = pp
{ ppSort = do { ppSort = do
sortWs <- ppSort pp sortWs <- ppSort pp
return $ \xs -> case xs of return $ \xs -> case xs of
x:_ | unmarshallS (tag x) == s -> sortWs xs x:_ | unmarshallS (W.tag x) == s -> sortWs xs
_ -> [] _ -> []
, ppOrder = \i@(wss:_) -> case wss of , ppOrder = \i@(wss:_) -> case wss of
"" -> ["\0"] -- we got passed no workspaces; this is the signal from ppSort that this is a boring case "" -> ["\0"] -- we got passed no workspaces; this is the signal from ppSort that this is a boring case
@ -171,11 +191,31 @@ whenCurrentOn s pp = pp
_ -> ppOutput pp out _ -> ppOutput pp out
} }
-- | If @vSort@ is a function that sorts 'WindowSpace's with virtual names, then @marshallSort s vSort@ is a function which sorts 'WindowSpace's with physical names in an analogous way -- but keeps only the spaces on screen @s@. -- | Filter workspaces that are on current screen.
marshallSort :: ScreenId -> ([WindowSpace] -> [WindowSpace]) -> ([WindowSpace] -> [WindowSpace]) workspacesOn :: ScreenId -> [PhysicalWindowSpace] -> [PhysicalWindowSpace]
workspacesOn s = filter (\ws -> unmarshallS (W.tag ws) == s)
-- | @vSort@ is a function that sorts 'VirtualWindowSpace's with virtual names.
-- @marshallSort s vSort@ is a function which sorts 'PhysicalWindowSpace's with virtual names,
-- but keeps only the 'WindowSpace'\'s on screen @s@.
--
-- NOTE: @vSort@ operating on virtual names comes with some caveats, see
-- <https://github.com/xmonad/xmonad-contrib/issues/420 this issue> for
-- more information. You can use 'marshallSort' like in the following example:
--
-- === __Example__
--
-- > pp' :: ScreenId -> PP -> PP
-- > pp' s pp = (marshallPP s pp) { ppSort = fmap (marshallSort s) (ppSort pp) }
-- >
-- > mySBL = statusBarProp "xmobar" $ pure (pp' (S 0) pp)
-- > mySBR = statusBarProp "xmobar" $ pure (pp' (S 1) pp)
-- > main = xmonad $ withEasySB (mySBL <> mySBR) defToggleStrutsKey def
--
-- In this way, you have a custom virtual names sort on top of 'marshallPP'.
marshallSort :: ScreenId -> ([VirtualWindowSpace] -> [VirtualWindowSpace]) -> ([PhysicalWindowSpace] -> [PhysicalWindowSpace])
marshallSort s vSort = pScreens . vSort . vScreens where marshallSort s vSort = pScreens . vSort . vScreens where
onScreen ws = unmarshallS (tag ws) == s vScreens = map unmarshallWindowSpace . workspacesOn s
vScreens = map unmarshallWindowSpace . filter onScreen
pScreens = map (marshallWindowSpace s) pScreens = map (marshallWindowSpace s)
-- | Convert the tag of the 'WindowSpace' from a 'VirtualWorkspace' to a 'PhysicalWorkspace'. -- | Convert the tag of the 'WindowSpace' from a 'VirtualWorkspace' to a 'PhysicalWorkspace'.
@ -183,5 +223,5 @@ marshallWindowSpace :: ScreenId -> WindowSpace -> WindowSpace
-- | Convert the tag of the 'WindowSpace' from a 'PhysicalWorkspace' to a 'VirtualWorkspace'. -- | Convert the tag of the 'WindowSpace' from a 'PhysicalWorkspace' to a 'VirtualWorkspace'.
unmarshallWindowSpace :: WindowSpace -> WindowSpace unmarshallWindowSpace :: WindowSpace -> WindowSpace
marshallWindowSpace s ws = ws { tag = marshall s (tag ws) } marshallWindowSpace s ws = ws { W.tag = marshall s (W.tag ws) }
unmarshallWindowSpace ws = ws { tag = unmarshallW (tag ws) } unmarshallWindowSpace ws = ws { W.tag = unmarshallW (W.tag ws) }