Skip to content

Commit

Permalink
X.H.Screencorners: Add per monitor hot corners
Browse files Browse the repository at this point in the history
Signed-off-by: Pascal Jäger <pascal.jaeger@leimstift.de>
  • Loading branch information
Schievel1 committed Jan 3, 2025
1 parent de01015 commit 925ddcb
Show file tree
Hide file tree
Showing 2 changed files with 89 additions and 31 deletions.
11 changes: 11 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,17 @@
`DestroyWindowEvent` messages instead, which are broadcast to layouts
since xmonad v0.17.0.

* `XMonad.Hooks.ScreenCorners`

- Screencorners were only possible at the edge of the screen canvas not
the edges of monitors. This worked on single monitor setups because there
the screen canvas edges and the monitor edges fall into the some place.
This is not the case in multi monitor setups and therefore how corners/
edges were only possible on the outer edges/ corners of the outmost
monitors if those monitors were not shifted in the y axis.
With `addMonitorCorner` and `addMonitorCorners` it is now possible to add
hot cornern for each corner of a monitor.

## 0.18.1 (August 20, 2024)

### Breaking Changes
Expand Down
109 changes: 78 additions & 31 deletions XMonad/Hooks/ScreenCorners.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,8 @@
-- |
-- Module : XMonad.Hooks.ScreenCorners
-- Description : Run X () actions by touching the edge of your screen with your mouse.
-- Copyright : (c) 2009-2025 Nils Schweinsberg, 2015 Evgeny Kurnevsky, 2024 Yuanle Song
-- Copyright : (c) 2009-2025 Nils Schweinsberg, 2015 Evgeny Kurnevsky, 2024 Yuanle Song,
-- 2025 Pascal Jaeger
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : Nils Schweinsberg <mail@nils.cc>
Expand All @@ -21,6 +22,8 @@ module XMonad.Hooks.ScreenCorners
ScreenCorner (..),
addScreenCorner,
addScreenCorners,
addMonitorCorner,
addMonitorCorners,

-- * Event hook
screenCornerEventHook,
Expand All @@ -35,6 +38,7 @@ import XMonad
import XMonad.Layout.LayoutModifier
import XMonad.Prelude
import qualified XMonad.Util.ExtensibleState as XS
import Graphics.X11.Xinerama (xineramaQueryScreens, XineramaScreenInfo(..))

data ScreenCorner
= SCUpperLeft
Expand All @@ -51,31 +55,46 @@ data ScreenCorner
-- ExtensibleState modifications
--------------------------------------------------------------------------------

newtype ScreenCornerState = ScreenCornerState (M.Map Window (ScreenCorner, X ()))
newtype ScreenCornerState = ScreenCornerState (M.Map (ScreenCorner, Int) (Window, X ()))

instance ExtensionClass ScreenCornerState where
initialValue = ScreenCornerState M.empty

-- | Add one single @X ()@ action to a screen corner
{-# DEPRECATED addScreenCorner "addScreenCorner works only in a single monitor setup. Use addMonitorCorner instead." #-}
addScreenCorner :: ScreenCorner -> X () -> X ()
addScreenCorner corner xF = do
ScreenCornerState m <- XS.get
(win, xFunc) <- case find (\(_, (sc, _)) -> sc == corner) (M.toList m) of
Just (w, (_, xF')) -> return (w, xF' >> xF) -- chain X actions
let key = (corner, -1) -- Use -1 to indicate a non-monitor-specific corner
(win, xFunc) <- case M.lookup key m of
Just (w, xF') -> return (w, xF' >> xF) -- Chain X actions
Nothing -> (,xF) <$> createWindowAt corner

XS.modify $ \(ScreenCornerState m') -> ScreenCornerState $ M.insert win (corner, xFunc) m'
XS.modify $ \(ScreenCornerState m') -> ScreenCornerState $ M.insert key (win, xFunc) m'

-- | Add a list of @(ScreenCorner, X ())@ tuples
{-# DEPRECATED addScreenCorners "addScreenCorners works only in a single monitor setup. Use addMonitorCorners instead." #-}
addScreenCorners :: [(ScreenCorner, X ())] -> X ()
addScreenCorners = mapM_ (uncurry addScreenCorner)

-- | Add one single @X ()@ action to a screen corner on a specific monitor
addMonitorCorner :: ScreenCorner -> Int -> Dimension -> X () -> X ()
addMonitorCorner corner monitorNumber hotZoneSize xF = do
ScreenCornerState m <- XS.get
let key = (corner, monitorNumber)
(win, xFunc) <- case M.lookup key m of
Just (w, xF') -> return (w, xF' >> xF) -- Chain X actions
Nothing -> (,xF) <$> createWindowAtMonitor corner monitorNumber hotZoneSize
XS.modify $ \(ScreenCornerState m') -> ScreenCornerState $ M.insert key (win, xFunc) m'

-- | Add a list of @(ScreenCorner, Int, Dimension, X ())@ tuples
addMonitorCorners :: [(ScreenCorner, Int, Dimension, X ())] -> X ()
addMonitorCorners = mapM_ (\(corner, monitor, hotZoneSize, xF) -> addMonitorCorner corner monitor hotZoneSize xF)

--------------------------------------------------------------------------------
-- Xlib functions
--------------------------------------------------------------------------------

-- "Translate" a ScreenCorner to real (x,y) Positions with proper width and
-- height.
-- "Translate" a ScreenCorner to real (x,y) Positions with proper width and height.
createWindowAt :: ScreenCorner -> X Window
createWindowAt SCUpperLeft = createWindowAt' 0 0 1 1
createWindowAt SCUpperRight = withDisplay $ \dpy ->
Expand Down Expand Up @@ -108,6 +127,30 @@ createWindowAt SCRight = withDisplay $ \dpy ->
threshold = 150
in createWindowAt' (fi w) threshold 1 (fi $ fi h - threshold * 2)

-- "Translate" a ScreenCorner to real (x,y) Positions on a specific monitor
createWindowAtMonitor :: ScreenCorner -> Int -> Dimension -> X Window
createWindowAtMonitor corner monitorNumber hotZoneSize = withDisplay $ \dpy -> do
screens <- io $ xineramaQueryScreens dpy
case screens of
Just scrs | monitorNumber < length scrs -> do
let XineramaScreenInfo _ x y w h = scrs !! monitorNumber
hotZoneSize' = fromIntegral hotZoneSize :: Int
x' = fromIntegral x :: Int
y' = fromIntegral y :: Int
w' = fromIntegral w :: Int
h' = fromIntegral h :: Int
(xPos, yPos, width, height) = case corner of
SCUpperLeft -> (x', y', hotZoneSize', hotZoneSize')
SCUpperRight -> (x' + w' - hotZoneSize', y', hotZoneSize', hotZoneSize')
SCLowerLeft -> (x', y' + h' - hotZoneSize', hotZoneSize', hotZoneSize')
SCLowerRight -> (x' + w' - hotZoneSize', y' + h' - hotZoneSize', hotZoneSize', hotZoneSize')
SCTop -> (x' + 150, y', w' - 300, hotZoneSize')
SCBottom -> (x' + 150, y' + h' - hotZoneSize', w' - 300, hotZoneSize')
SCLeft -> (x', y' + 150, hotZoneSize', h' - 300)
SCRight -> (x' + w' - hotZoneSize', y' + 150, hotZoneSize', h' - 300)
createWindowAt' (fi xPos) (fi yPos) (fi width) (fi height)
_ -> error $ "Invalid monitor number or no screens available for monitorNumber=" ++ show monitorNumber

-- Create a new X window at a (x,y) Position, with given width and height.
createWindowAt' :: Position -> Position -> Dimension -> Dimension -> X Window
createWindowAt' x y width height = withDisplay $ \dpy -> io $ do
Expand All @@ -117,22 +160,22 @@ createWindowAt' x y width height = withDisplay $ \dpy -> io $ do
attrmask = cWOverrideRedirect

w <- allocaSetWindowAttributes $ \attributes -> do

set_override_redirect attributes True
createWindow
dpy -- display
rootw -- parent window
x -- x
y -- y
width -- width
height -- height
0 -- border width
0 -- depth
inputOnly -- class
visual -- visual
attrmask -- valuemask
attributes -- attributes

-- we only need mouse entry events
createWindow dpy -- display
rootw -- parent window
x -- x
y -- y
width -- width
height -- height
0 -- border width
0 -- depth
inputOnly -- class
visual -- visual
attrmask -- valuemask
attributes -- attributes

-- we only need mouse entry events selectInput dpy w enterWindowMask
selectInput dpy w enterWindowMask
mapWindow dpy w
sync dpy False
Expand All @@ -147,8 +190,8 @@ screenCornerEventHook :: Event -> X All
screenCornerEventHook CrossingEvent {ev_window = win} = do
ScreenCornerState m <- XS.get

case M.lookup win m of
Just (_, xF) -> xF
case find (\(_, (w, _)) -> w == win) (M.toList m) of
Just (_, (_, xF)) -> xF
Nothing -> return ()

return (All True)
Expand All @@ -164,7 +207,7 @@ data ScreenCornerLayout a = ScreenCornerLayout
instance LayoutModifier ScreenCornerLayout a where
hook ScreenCornerLayout = withDisplay $ \dpy -> do
ScreenCornerState m <- XS.get
io $ mapM_ (raiseWindow dpy) $ M.keys m
io $ mapM_ (raiseWindow dpy . fst . snd) $ M.toList m
unhook = hook

screenCornerLayoutHook :: l a -> ModifiedLayout ScreenCornerLayout l a
Expand All @@ -188,11 +231,15 @@ screenCornerLayoutHook = ModifiedLayout ScreenCornerLayout
--
-- > myStartupHook = do
-- > ...
-- > addScreenCorner SCUpperRight (goToSelected def { gs_cellwidth = 200})
-- > addScreenCorner SCBottom (goToSelected def)
-- > addScreenCorners [ (SCLowerRight, nextWS)
-- > , (SCLowerLeft, prevWS)
-- > ]
-- > addMonitorCorner SCUpperLeft 0 20 (spawn "firefox")
-- > addMonitorCorner SCBottom 0 20 (spawn "firefox")
-- > addMonitorCorners [ (SCUpperRight, 1, 20, spawn "xterm")
-- > , (SCLowerRight, 2, 20, nextWS)
-- > ]
-- > ...
--
-- Where 0-2 are the monitors and 20 is the size of the hot corner.
--
--
-- Then add layout hook:
--
Expand Down

0 comments on commit 925ddcb

Please sign in to comment.