Skip to content

Commit

Permalink
X.U.Ungrab: Avoid "Ambiguous occurrence" error in user configs
Browse files Browse the repository at this point in the history
  • Loading branch information
liskin committed Dec 18, 2023
1 parent d54a7e2 commit 3613d4d
Showing 1 changed file with 5 additions and 0 deletions.
5 changes: 5 additions & 0 deletions XMonad/Util/Ungrab.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Util.Ungrab
Expand All @@ -19,6 +20,9 @@ module XMonad.Util.Ungrab {-# DEPRECATED "Use XMonad.Operations.unGrab instead"
unGrab
) where

#if MIN_VERSION_xmonad(0, 17, 9)
import XMonad.Operations (unGrab)
#else
import Graphics.X11.Xlib (sync)
import Graphics.X11.Xlib.Extras (currentTime)
import Graphics.X11.Xlib.Misc (ungrabKeyboard, ungrabPointer)
Expand All @@ -43,3 +47,4 @@ import XMonad.Core
-- | Release xmonad's keyboard grab, so other grabbers can do their thing.
unGrab :: X ()
unGrab = withDisplay $ \d -> io (ungrabKeyboard d currentTime >> ungrabPointer d currentTime >> sync d False)
#endif

0 comments on commit 3613d4d

Please sign in to comment.