Move module to new module XMonad.Util.Hacks

This commit is contained in:
elkowar
2021-01-01 13:13:28 +01:00
parent 3d553ad5e0
commit b41a5a50e9
4 changed files with 38 additions and 31 deletions

View File

@@ -575,10 +575,6 @@ Here is a list of the modules found in @XMonad.Hooks@:
* "XMonad.Hooks.WorkspaceHistory":
Keeps track of workspace viewing order.
* "XMonad.Hooks.WindowedFullscreenFix":
Provides a handleEventHook that fixes the rendering behaviour
of some (mostly chromium based) applications when in windowed fullscreen.
* "XMonad.Hooks.WindowSwallowing"
A handleEventHook that implements window swallowing:
Hide parent windows like terminals when opening other programs (like image viewers) from within them,
@@ -1160,6 +1156,9 @@ A non complete list with a brief description:
A module for abstracting a font facility over
Core fonts and Xft.
* "XMonad.Util.Hacks":
A collection of small fixes and utilities with possibly hacky implementations.
* "XMonad.Util.Image":
Utilities for manipulating [[Bool]] as images.

View File

@@ -1,7 +1,6 @@
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.WindowedFullscreenFix
-- Module : XMonad.Util.Hacks
-- Copyright : (c) 2020 Leon Kowarschick
-- License : BSD3-style (see LICENSE)
--
@@ -9,6 +8,30 @@
-- Stability : unstable
-- Portability : unportable
--
-- This module is a collection of random fixes, workarounds and other functions
-- that rely on somewhat hacky implementations which may have unwanted sideeffects.
--
-- Import this module as qualified like so:
--
-- > import qualified XMonad.Util.Hacks as Hacks
--
-- and then use the functions you want as described in their respective documentation.
--
-----------------------------------------------------------------------------
module XMonad.Util.Hacks
( -- * Windowed fullscreen
-- $windowedFullscreenFix
windowedFullscreenFixEventHook
) where
import XMonad
import Data.Monoid (All(All))
import Control.Monad (when)
-- $windowedFullscreenFix
-- Windowed fullscreen describes the behaviour in which XMonad,
-- by default, does not automatically put windows that request being fullscreened
-- into actual fullscreen, but keeps them constrained
@@ -21,25 +44,9 @@
-- This module works around that issue by forcing the window to recalculate their
-- dimensions after initiating fullscreen, thus making chrome-based applications
-- behave properly when in windowed fullscreen.
-----------------------------------------------------------------------------
module XMonad.Hooks.WindowedFullscreenFix
( -- * Usage
-- $usage
windowedFullscreenFixEventHook
) where
import XMonad
import Data.Monoid (All(All))
import Control.Monad (when)
-- $usage
-- Use this module by importing
--
-- > import XMonad.Hooks.WindowedFullscreenFix
--
-- and then registering the provided eventHook in your handleEventHook:
-- Usage:
-- add to handleEventHook as follows:
--
-- > handleEventHook = handleEventHook def <+> windowedFullscreenFixEventHook
--
@@ -53,8 +60,8 @@ windowedFullscreenFixEventHook (ClientMessageEvent _ _ _ dpy win typ (_:dats)) =
fullscreen <- getAtom "_NET_WM_STATE_FULLSCREEN"
when (typ == wmstate && fromIntegral fullscreen `elem` dats) $ do
withWindowAttributes dpy win $ \attrs ->
liftIO $ resizeWindow dpy win (fromIntegral $ wa_width attrs - 1) (fromIntegral $ wa_height attrs)
withWindowAttributes dpy win $ \attrs ->
liftIO $ resizeWindow dpy win (fromIntegral $ wa_width attrs + 1) (fromIntegral $ wa_height attrs)
liftIO $ do
resizeWindow dpy win (fromIntegral $ wa_width attrs - 1) (fromIntegral $ wa_height attrs)
resizeWindow dpy win (fromIntegral $ wa_width attrs + 1) (fromIntegral $ wa_height attrs)
return $ All True
windowedFullscreenFixEventHook _ = return $ All True