Skip to content

Commit

Permalink
XMonad.Actions.GridSelect: added gs_cancelOnEmptyClick field
Browse files Browse the repository at this point in the history
In the original code, when a GridSelect is shown, user has to use keyboard to
cancel it (ESC key by default). With this field added, when it is set to True,
mouse click on empty space can cancel the GridSelect.
  • Loading branch information
sylecn committed Jun 9, 2024
1 parent 077b4ff commit b1d745d
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 7 deletions.
8 changes: 8 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,14 @@
myFunc` should be changed to `historyCompletionP myConf myFunc`.
If not `myConf` is lying around, `def` can be used instead.

* `XMonad.Actions.GridSelect`

- Added `gs_cancelOnEmptyClick` field in `GSConfig`. Previously when a
GridSelect is shown, user has to use keyboard to cancel it (ESC key by
default). With this field added, when it is set to True, mouse click on
empty space can cancel the GridSelect. when set to False (the default),
the old behavior is preserved.

### New Modules

* `XMonad.Actions.Profiles`
Expand Down
24 changes: 17 additions & 7 deletions XMonad/Actions/GridSelect.hs
Original file line number Diff line number Diff line change
Expand Up @@ -179,6 +179,7 @@ import qualified Data.List.NonEmpty as NE
-- > { gs_cellheight = 30
-- > , gs_cellwidth = 100
-- > , gs_navigate = myNavigation
-- > , gs_cancelOnEmptyClick = True -- cancel grid when click on empty space
-- > }

-- $screenshots
Expand All @@ -203,10 +204,14 @@ data GSConfig a = GSConfig {
gs_colorizer :: a -> Bool -> X (String, String),
gs_font :: String,
gs_navigate :: TwoD a (Maybe a),
-- ^ Customize key bindings for a GridSelect
gs_rearranger :: Rearranger a,
gs_originFractX :: Double,
gs_originFractY :: Double,
gs_bordercolor :: String
gs_bordercolor :: String,
gs_cancelOnEmptyClick :: Bool
-- ^ When True, click on empty space will
-- cancel GridSelect
}

-- | That is 'fromClassName' if you are selecting a 'Window', or
Expand Down Expand Up @@ -386,13 +391,18 @@ updateElementsWithColorizer colorizer elementmap = do
stdHandle :: Event -> TwoD a (Maybe a) -> TwoD a (Maybe a)
stdHandle ButtonEvent{ ev_event_type = t, ev_x = x, ev_y = y } contEventloop
| t == buttonRelease = do
s@TwoDState { td_paneX = px, td_paneY = py,
td_gsconfig = (GSConfig ch cw _ _ _ _ _ _ _ _) } <- get
let gridX = (fi x - (px - cw) `div` 2) `div` cw
s@TwoDState { td_paneX = px, td_paneY = py, td_gsconfig = gsconfig } <- get
let ch = gs_cellheight gsconfig
cw = gs_cellwidth gsconfig
gridX = (fi x - (px - cw) `div` 2) `div` cw
gridY = (fi y - (py - ch) `div` 2) `div` ch
case lookup (gridX,gridY) (td_elementmap s) of
Just (_,el) -> return (Just el)
Nothing -> contEventloop
Nothing -> if gs_cancelOnEmptyClick gsconfig
then
return Nothing
else
contEventloop
| otherwise = contEventloop

stdHandle ExposeEvent{} contEventloop = updateAllElements >> contEventloop
Expand Down Expand Up @@ -648,7 +658,7 @@ gridselect gsconfig elements =
liftIO $ mapWindow dpy win
liftIO $ selectInput dpy win (exposureMask .|. keyPressMask .|. buttonReleaseMask)
status <- io $ grabKeyboard dpy win True grabModeAsync grabModeAsync currentTime
io $ grabPointer dpy win True buttonReleaseMask grabModeAsync grabModeAsync none none currentTime
_ <- io $ grabPointer dpy win True buttonReleaseMask grabModeAsync grabModeAsync none none currentTime
font <- initXMF (gs_font gsconfig)
let screenWidth = toInteger $ rect_width scr
screenHeight = toInteger $ rect_height scr
Expand Down Expand Up @@ -706,7 +716,7 @@ decorateName' w = do

-- | Builds a default gs config from a colorizer function.
buildDefaultGSConfig :: (a -> Bool -> X (String,String)) -> GSConfig a
buildDefaultGSConfig col = GSConfig 50 130 10 col "xft:Sans-8" defaultNavigation noRearranger (1/2) (1/2) "white"
buildDefaultGSConfig col = GSConfig 50 130 10 col "xft:Sans-8" defaultNavigation noRearranger (1/2) (1/2) "white" False

-- | Brings selected window to the current workspace.
bringSelected :: GSConfig Window -> X ()
Expand Down

0 comments on commit b1d745d

Please sign in to comment.