1
0
mirror of https://github.com/xmonad/xmonad-contrib.git synced 2025-08-05 06:31:53 -07:00
Files
.github
XMonad
Actions
Config
Doc
Hooks
StatusBar
BorderPerWindow.hs
CurrentWorkspaceOnTop.hs
DebugEvents.hs
DebugKeyEvents.hs
DebugStack.hs
DynamicBars.hs
DynamicHooks.hs
DynamicIcons.hs
DynamicLog.hs
DynamicProperty.hs
EwmhDesktops.hs
FadeInactive.hs
FadeWindows.hs
FloatConfigureReq.hs
FloatNext.hs
Focus.hs
InsertPosition.hs
ManageDebug.hs
ManageDocks.hs
ManageHelpers.hs
Minimize.hs
Modal.hs
OnPropertyChange.hs
Place.hs
PositionStoreHooks.hs
RefocusLast.hs
Rescreen.hs
ScreenCorners.hs
Script.hs
ServerMode.hs
SetWMName.hs
ShowWName.hs
StatusBar.hs
TaffybarPagerHints.hs
ToggleHook.hs
UrgencyHook.hs
WallpaperSetter.hs
WindowSwallowing.hs
WorkspaceByPos.hs
WorkspaceHistory.hs
XPropManage.hs
Layout
Prompt
Util
Doc.hs
Prelude.hs
Prompt.hs
scripts
tests
.gitignore
.hlint.yaml
.mailmap
CHANGES.md
CONTRIBUTING.md
LICENSE
NIX.md
README.md
Setup.lhs
cabal.haskell-ci
cabal.project
flake.nix
stack-master.yaml
stack.yaml
xmonad-contrib.cabal
xmonad-contrib/XMonad/Hooks/WorkspaceByPos.hs
Tony Zorman b1b3c4c469 ~/.xmonad/xmonad.hs -> xmonad.hs
With XDG support so firmly ingrained now, it's about time we stop
hard-coding the configuration path in the docs.
2023-12-22 18:17:17 +01:00

56 lines
1.8 KiB
Haskell

{-# LANGUAGE LambdaCase #-}
----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.WorkspaceByPos
-- Description : Move new window to non-focused screen based on its requested geometry.
-- Copyright : (c) Jan Vornberger 2009
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : jan.vornberger@informatik.uni-oldenburg.de
-- Stability : unstable
-- Portability : not portable
--
-- Useful in a dual-head setup: Looks at the requested geometry of
-- new windows and moves them to the workspace of the non-focused
-- screen if necessary.
--
-----------------------------------------------------------------------------
module XMonad.Hooks.WorkspaceByPos (
-- * Usage
-- $usage
workspaceByPos
) where
import XMonad
import XMonad.Prelude
import qualified XMonad.StackSet as W
import Control.Monad.Except (runExceptT, throwError)
import Control.Monad.Trans (lift)
-- $usage
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Hooks.WorkspaceByPos
-- >
-- > myManageHook = workspaceByPos <> manageHook def
-- >
-- > main = xmonad def { manageHook = myManageHook }
workspaceByPos :: ManageHook
workspaceByPos = (maybe idHook doShift <=< liftX . needsMoving) =<< ask
needsMoving :: Window -> X (Maybe WorkspaceId)
needsMoving w = safeGetWindowAttributes w >>= \case
Nothing -> pure Nothing
Just wa -> fmap (either (const Nothing) Just) . runExceptT $ do
-- only relocate windows with non-zero position
guard $ wa_x wa /= 0 || wa_y wa /= 0
ws <- gets windowset
sc <- lift $ fromMaybe (W.current ws)
<$> pointScreen (fi $ wa_x wa) (fi $ wa_y wa)
Just wkspc <- lift $ screenWorkspace (W.screen sc)
guard $ W.currentTag ws /= wkspc
return wkspc `asTypeOf` throwError ""