Skip to content

Commit

Permalink
Make usage of ManageDocks simpler and more robust
Browse files Browse the repository at this point in the history
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!
  • Loading branch information
liskin authored and f1u77y committed Sep 7, 2016
1 parent 7656ffe commit 3b373d6
Show file tree
Hide file tree
Showing 8 changed files with 22 additions and 37 deletions.
4 changes: 2 additions & 2 deletions XMonad/Config/Bluetile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 |||
Expand All @@ -199,6 +198,7 @@ bluetileLayoutHook = avoidStruts $ minimize $ boringWindows $ (
floatingDeco l = buttonDeco shrinkText defaultThemeWithButtons l

bluetileConfig =
docks $
def
{ modMask = mod4Mask, -- logo key
manageHook = bluetileManageHook,
Expand Down
6 changes: 2 additions & 4 deletions XMonad/Config/Desktop.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 $
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Config/Dmwit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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",
Expand All @@ -221,7 +221,6 @@ dmwitConfig nScreens = def {
<+> (appName =? "huludesktop" --> doRectFloat fullscreen43on169)
<+> fullscreenMPlayer
<+> floatAll ["Gimp", "Wine"]
<+> manageDocks
<+> manageSpawn,
logHook = allPPs nScreens,
startupHook = refresh
Expand Down
5 changes: 2 additions & 3 deletions XMonad/Config/Droundy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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 "~" $
Expand All @@ -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.
Expand Down
4 changes: 2 additions & 2 deletions XMonad/Config/Sjanssen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 $
Expand All @@ -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
}
Expand Down
3 changes: 1 addition & 2 deletions XMonad/Hooks/DynamicLog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -199,12 +199,11 @@ statusBar :: LayoutClass l Window
-> IO (XConfig (ModifiedLayout AvoidStruts l))
statusBar cmd pp k conf = do
h <- spawnPipe cmd
return $ conf
return $ docks $ conf
{ layoutHook = avoidStruts (layoutHook conf)
, logHook = do
logHook conf
dynamicLogWithPP pp { ppOutput = hPutStrLn h }
, manageHook = manageHook conf <+> manageDocks
, keys = liftM2 M.union keys' (keys conf)
}
where
Expand Down
2 changes: 1 addition & 1 deletion XMonad/Hooks/EwmhDesktops.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ import XMonad.Util.WindowProperties (getProp32)
-- > main = xmonad $ ewmh def{ handleEventHook =
-- > handleEventHook def <+> fullscreenEventHook }
--
-- You may also be interested in 'avoidStruts' from "XMonad.Hooks.ManageDocks".
-- You may also be interested in 'docks' from "XMonad.Hooks.ManageDocks".


-- | Add EWMH functionality to the given config. See above for an example.
Expand Down
32 changes: 11 additions & 21 deletions XMonad/Hooks/ManageDocks.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@
module XMonad.Hooks.ManageDocks (
-- * Usage
-- $usage
manageDocks, checkDock, AvoidStruts, avoidStruts, avoidStrutsOn,
docks, manageDocks, checkDock, AvoidStruts, avoidStruts, avoidStrutsOn,
docksEventHook, docksStartupHook,
ToggleStruts(..),
SetStruts(..),
Expand Down Expand Up @@ -52,25 +52,16 @@ import Control.Monad (when, forM_, filterM)
--
-- > import XMonad.Hooks.ManageDocks
--
-- The first component is a 'ManageHook' which recognizes these
-- windows and de-manages them, so that xmonad does not try to tile
-- them. To enable it:
-- Wrap your xmonad config with a call to 'docks', like so:
--
-- > manageHook = ... <+> manageDocks
-- > main = xmonad $ docks def
--
-- The second component is a layout modifier that prevents windows
-- from overlapping these dock windows. It is intended to replace
-- xmonad's so-called \"gap\" support. First, you must add it to your
-- list of layouts:
-- Then add 'avoidStruts' or 'avoidStrutsOn' layout modifier to your layout
-- to prevent windows from overlapping these windows.
--
-- > layoutHook = avoidStruts (tall ||| mirror tall ||| ...)
-- > where tall = Tall 1 (3/100) (1/2)
--
-- The third component is an event hook that causes new docks to appear
-- immediately, instead of waiting for the next focus change.
--
-- > handleEventHook = ... <+> docksEventHook
--
-- 'AvoidStruts' also supports toggling the dock gaps; add a keybinding
-- similar to:
--
Expand All @@ -90,17 +81,16 @@ import Control.Monad (when, forM_, filterM)
--
-- > layoutHook = avoidStrutsOn [U,L] (tall ||| mirror tall ||| ...)
--
-- /Important note/: if you are switching from manual gaps
-- (defaultGaps in your config) to avoidStruts (recommended, since
-- manual gaps will probably be phased out soon), be sure to switch
-- off all your gaps (with mod-b) /before/ reloading your config with
-- avoidStruts! Toggling struts with a 'ToggleStruts' message will
-- not work unless your gaps are set to zero.
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".
--

-- | Add docks functionality to the given config. See above for an example.
docks :: XConfig a -> XConfig a
docks c = c { startupHook = docksStartupHook <+> startupHook c
, handleEventHook = docksEventHook <+> handleEventHook c
, manageHook = manageDocks <+> manageHook c }

newtype StrutCache = StrutCache { fromStrutCache :: M.Map Window [Strut] }
deriving Eq

Expand Down

0 comments on commit 3b373d6

Please sign in to comment.