Files
xmonad-contrib/XMonad/Util/NoTaskbar.hs
slotThe 2469269119 New module: XMonad.Prelude
This is a convenience module in order to have less import noise.  It
re-exports the following:

  a) Commonly used modules in full (Data.Foldable, Data.Applicative, and
     so on); though only those that play nicely with each other, so that
     XMonad.Prelude can be imported unqualified without any problems.
     This prevents things like `Prelude.(.)` and `Control.Category.(.)`
     fighting with each other.

  b) Helper functions that don't necessarily fit in any other module;
     e.g., the often used abbreviation `fi = fromIntegral`.
2021-05-13 17:44:47 +02:00

31 lines
1.2 KiB
Haskell

module XMonad.Util.NoTaskbar (-- * Usage
-- $usage
noTaskbar
,markNoTaskbar) where
import XMonad.Core
import XMonad.Prelude (fi)
import XMonad.ManageHook
import Graphics.X11.Xlib (Window)
import Graphics.X11.Xlib.Atom (aTOM)
import Graphics.X11.Xlib.Extras (changeProperty32
,propModePrepend)
import Control.Monad.Reader (ask)
-- $usage
-- Utility functions to hide windows from pagers and taskbars. Mostly useful
-- when EWMH doesn't do what you intend (e.g. for 'NamedScratchpad' windows you
-- probably don't want to be dumped into the 'NSP' workspace).
-- | A 'ManageHook' to mark a window to not be shown in pagers or taskbars.
noTaskbar :: ManageHook
noTaskbar = ask >>= (>> idHook) . liftX . markNoTaskbar
-- | An 'X' action to mark a window to not be shown in pagers or taskbars.
markNoTaskbar :: Window -> X ()
markNoTaskbar w = withDisplay $ \d -> do
ws <- getAtom "_NET_WM_STATE"
ntb <- getAtom "_NET_WM_STATE_SKIP_TASKBAR"
npg <- getAtom "_NET_WM_STATE_SKIP_PAGER"
io $ changeProperty32 d w ws aTOM propModePrepend [fi ntb,fi npg]