Copyright | (c) Joachim Breitner <mail@joachim-breitner.de> |
---|---|
License | BSD |
Maintainer | Joachim Breitner <mail@joachim-breitner.de> |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides tools to automatically manage dock
type programs,
such as gnome-panel, kicker, dzen, and xmobar.
Synopsis
- docks :: XConfig a -> XConfig a
- manageDocks :: ManageHook
- checkDock :: Query Bool
- newtype AvoidStruts a = AvoidStruts (Set Direction2D)
- avoidStruts :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a
- avoidStrutsOn :: LayoutClass l a => [Direction2D] -> l a -> ModifiedLayout AvoidStruts l a
- data ToggleStruts
- data SetStruts = SetStruts {
- addedStruts :: [Direction2D]
- removedStruts :: [Direction2D]
- module XMonad.Util.Types
- calcGap :: Set Direction2D -> X (Rectangle -> Rectangle)
- docksEventHook :: Event -> X All
- docksStartupHook :: X ()
Usage
To use this module, add the following import to 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 Direction2D
, 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 the tutorial.
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. Ignores xmonad's own windows (usually _NET_WM_WINDOW_TYPE_DESKTOP) to avoid unnecessary refreshes.
newtype AvoidStruts a Source #
Instances
avoidStruts :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a Source #
Adjust layout automagically: don't cover up any docks, status bars, etc.
Note that this modifier must be applied before any modifier that
changes the screen rectangle, or struts will be applied in the wrong
place and may affect the other modifier(s) in odd ways. This is
most commonly seen with the spacing
modifier and friends.
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), Direction2D
(bottom), R
(right), or L
(left). The warning in
avoidStruts
applies to this modifier as well.
data ToggleStruts Source #
Message type which can be sent to an AvoidStruts
layout
modifier to alter its behavior.
Instances
Read ToggleStruts Source # | |
Defined in XMonad.Hooks.ManageDocks readsPrec :: Int -> ReadS ToggleStruts # readList :: ReadS [ToggleStruts] # | |
Show ToggleStruts Source # | |
Defined in XMonad.Hooks.ManageDocks showsPrec :: Int -> ToggleStruts -> ShowS # show :: ToggleStruts -> String # showList :: [ToggleStruts] -> ShowS # | |
Message ToggleStruts Source # | |
Defined in XMonad.Hooks.ManageDocks |
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])
SetStruts | |
|
module XMonad.Util.Types
For developers of other modules (XMonad.Actions.FloatSnap)
calcGap :: Set Direction2D -> X (Rectangle -> Rectangle) Source #
Goes through the list of windows and find the gap so that all STRUT settings are satisfied.
Standalone hooks (deprecated)
docksEventHook :: Event -> X All Source #
Deprecated: Use docks instead.
Whenever a new dock appears, refresh the layout immediately to avoid the new dock.
docksStartupHook :: X () Source #
Deprecated: Use docks instead.