Make usage of ManageDocks simpler and more robust

As it now consists of a startup hook, a manage hook, an event hook and
a layout modifier, and behaves erratically when any one component is not
included in a user's config (which happens to be the case for all
configs from xmonad-contrib 0.12 since the startup hook is a new
inclusion), it's probably wise to have a single function that adds
all the hooks to the config instead.

NB: This will need a release notes entry anyway!
This commit is contained in:
Tomas Janousek
2016-09-06 16:46:03 +02:00
committed by Bogdan Sinitsyn
parent c48d81e378
commit e38fb3bdb8
8 changed files with 22 additions and 37 deletions

View File

@@ -180,8 +180,7 @@ bluetileManageHook :: ManageHook
bluetileManageHook = composeAll
[ workspaceByPos, positionStoreManageHook (Just defaultThemeWithButtons)
, className =? "MPlayer" --> doFloat
, isFullscreen --> doFullFloat
, manageDocks]
, isFullscreen --> doFullFloat]
bluetileLayoutHook = avoidStruts $ minimize $ boringWindows $ (
named "Floating" floating |||
@@ -199,6 +198,7 @@ bluetileLayoutHook = avoidStruts $ minimize $ boringWindows $ (
floatingDeco l = buttonDeco shrinkText defaultThemeWithButtons l
bluetileConfig =
docks $
def
{ modMask = mod4Mask, -- logo key
manageHook = bluetileManageHook,

View File

@@ -164,11 +164,9 @@ import qualified Data.Map as M
-- > adjustEventInput
--
desktopConfig = ewmh def
{ startupHook = setDefaultCursor xC_left_ptr <+> docksStartupHook <+> startupHook def
desktopConfig = docks $ ewmh def
{ startupHook = setDefaultCursor xC_left_ptr <+> startupHook def
, layoutHook = desktopLayoutModifiers $ layoutHook def
, manageHook = manageDocks <+> manageHook def
, handleEventHook = docksEventHook <+> handleEventHook def
, keys = desktopKeys <+> keys def }
desktopKeys (XConfig {modMask = modm}) = M.fromList $

View File

@@ -205,7 +205,7 @@ instance PPrint ScreenId
instance (Show a, Show b) => PPrint (Map a b)
-- }}}
-- main {{{
dmwitConfig nScreens = def {
dmwitConfig nScreens = docks $ def {
borderWidth = 2,
workspaces = withScreens nScreens (map show [1..5]),
terminal = "urxvt",
@@ -221,7 +221,6 @@ dmwitConfig nScreens = def {
<+> (appName =? "huludesktop" --> doRectFloat fullscreen43on169)
<+> fullscreenMPlayer
<+> floatAll ["Gimp", "Wine"]
<+> manageDocks
<+> manageSpawn,
logHook = allPPs nScreens,
startupHook = refresh

View File

@@ -42,7 +42,7 @@ import XMonad.Actions.DynamicWorkspaces ( withNthWorkspace, withWorkspace,
import XMonad.Actions.CycleWS ( moveTo, WSType( HiddenNonEmptyWS ),
Direction1D( Prev, Next) )
import XMonad.Hooks.ManageDocks ( avoidStruts, manageDocks )
import XMonad.Hooks.ManageDocks ( avoidStruts, docks )
import XMonad.Hooks.EwmhDesktops ( ewmh )
myXPConfig :: XPConfig
@@ -117,7 +117,7 @@ keys x = M.fromList $
++
zip (zip (repeat (modMask x .|. shiftMask)) [xK_F1..xK_F12]) (map (withNthWorkspace copy) [0..])
config = ewmh def
config = docks $ ewmh def
{ borderWidth = 1 -- Width of the window border in pixels.
, XMonad.workspaces = ["mutt","iceweasel"]
, layoutHook = showWName $ workspaceDir "~" $
@@ -129,7 +129,6 @@ config = ewmh def
named "widescreen" ((mytab *||* mytab)
****//* combineTwo Square mytab mytab) -- |||
--mosaic 0.25 0.5
, manageHook = manageHook def <+> manageDocks -- add panel-handling
, terminal = "xterm" -- The preferred terminal program.
, normalBorderColor = "#222222" -- Border color for unfocused windows.
, focusedBorderColor = "#00ff00" -- Border color for focused windows.

View File

@@ -21,7 +21,7 @@ import XMonad.Layout.TwoPane
import qualified Data.Map as M
sjanssenConfig =
ewmh $ def
docks $ ewmh $ def
{ terminal = "exec urxvt"
, workspaces = ["irc", "web"] ++ map show [3 .. 9 :: Int]
, mouseBindings = \(XConfig {modMask = modm}) -> M.fromList $
@@ -35,7 +35,7 @@ sjanssenConfig =
| (x, w) <- [ ("Firefox", "web")
, ("Ktorrent", "7")
, ("Amarokapp", "7")]]
<+> manageHook def <+> manageDocks <+> manageSpawn
<+> manageHook def <+> manageSpawn
<+> (isFullscreen --> doFullFloat)
, startupHook = mapM_ spawnOnce spawns
}