xmonad-contrib-0.14: Third party extensions for xmonad

Copyright(c) Joachim Breitner <mail@joachim-breitner.de>
LicenseBSD
MaintainerJoachim Breitner <mail@joachim-breitner.de>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell98

XMonad.Hooks.ManageDocks

Contents

Description

This module provides tools to automatically manage dock type programs, such as gnome-panel, kicker, dzen, and xmobar.

Synopsis

Usage

To use this module, add the following import to ~/.xmonad/xmonad.hs:

import XMonad.Hooks.ManageDocks

Wrap your xmonad config with a call to docks, like so:

main = xmonad $ docks def

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)

AvoidStruts also supports toggling the dock gaps; add a keybinding similar to:

,((modm, xK_b     ), sendMessage ToggleStruts)

If you have multiple docks, you can toggle their gaps individually. For example, to toggle only the top gap:

,((modm .|. controlMask, xK_t), sendMessage $ ToggleStrut U)

Similarly, you can use D, L, and R to individually toggle gaps on the bottom, left, or right.

If you want certain docks to be avoided but others to be covered by default, you can manually specify the sides of the screen on which docks should be avoided, using avoidStrutsOn. For example:

layoutHook = avoidStrutsOn [U,L] (tall ||| mirror tall ||| ...)

For detailed instructions on editing your key bindings, see XMonad.Doc.Extending.

docks :: XConfig a -> XConfig a Source #

Add docks functionality to the given config. See above for an example.

manageDocks :: ManageHook Source #

Detects if the given window is of type DOCK and if so, reveals it, but does not manage it.

checkDock :: Query Bool Source #

Checks if a window is a DOCK or DESKTOP window

data AvoidStruts a Source #

Instances
LayoutModifier AvoidStruts a Source # 
Instance details

Defined in XMonad.Hooks.ManageDocks

Read (AvoidStruts a) Source # 
Instance details

Defined in XMonad.Hooks.ManageDocks

Show (AvoidStruts a) Source # 
Instance details

Defined in XMonad.Hooks.ManageDocks

avoidStruts :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a Source #

Adjust layout automagically: don't cover up any docks, status bars, etc.

avoidStrutsOn :: LayoutClass l a => [Direction2D] -> l a -> ModifiedLayout AvoidStruts l a Source #

Adjust layout automagically: don't cover up docks, status bars, etc. on the indicated sides of the screen. Valid sides are U (top), D (bottom), R (right), or L (left).

docksEventHook :: Event -> X All Source #

Whenever a new dock appears, refresh the layout immediately to avoid the new dock.

data ToggleStruts Source #

Message type which can be sent to an AvoidStruts layout modifier to alter its behavior.

data SetStruts Source #

SetStruts is a message constructor used to set or unset specific struts, regardless of whether or not the struts were originally set. Here are some example bindings:

Show all gaps:

  ,((modm .|. shiftMask  ,xK_b),sendMessage $ SetStruts [minBound .. maxBound] [])

Hide all gaps:

  ,((modm .|. controlMask,xK_b),sendMessage $ SetStruts [] [minBound .. maxBound])

Show only upper and left gaps:

  ,((modm .|. controlMask .|. shiftMask,xK_b),sendMessage $ SetStruts [U,L] [minBound .. maxBound])

Hide the bottom keeping whatever the other values were:

  ,((modm .|. controlMask .|. shiftMask,xK_g),sendMessage $ SetStruts [] [D])

Constructors

SetStruts 

Fields

calcGap :: Set Direction2D -> X (Rectangle -> Rectangle) Source #

Goes through the list of windows and find the gap so that all STRUT settings are satisfied.