diff options
author | Andrea Rossato <andrea.rossato@unibz.it> | 2007-11-14 20:13:27 +0100 |
---|---|---|
committer | Andrea Rossato <andrea.rossato@unibz.it> | 2007-11-14 20:13:27 +0100 |
commit | 63a46fcbd121500be0f7af214273c8ebe8f26f14 (patch) | |
tree | 6dfc1e6e9c3acba6f6399d5c5b155ceb998ad9b5 /XMonad/Hooks | |
parent | d76d82ef32c42ca55b34c840ce85d5174fccdfc7 (diff) | |
download | XMonadContrib-63a46fcbd121500be0f7af214273c8ebe8f26f14.tar.gz XMonadContrib-63a46fcbd121500be0f7af214273c8ebe8f26f14.tar.xz XMonadContrib-63a46fcbd121500be0f7af214273c8ebe8f26f14.zip |
ManageDocks.hs: haddock fixes
darcs-hash:20071114191327-32816-63abb4c8987e156def305e1ce6dfbbb068ad562a.gz
Diffstat (limited to 'XMonad/Hooks')
-rw-r--r-- | XMonad/Hooks/ManageDocks.hs | 13 |
1 files changed, 7 insertions, 6 deletions
diff --git a/XMonad/Hooks/ManageDocks.hs b/XMonad/Hooks/ManageDocks.hs index 0e372dd..fedca64 100644 --- a/XMonad/Hooks/ManageDocks.hs +++ b/XMonad/Hooks/ManageDocks.hs @@ -1,6 +1,6 @@ {-# LANGUAGE PatternGuards, FlexibleInstances, MultiParamTypeClasses #-} {-# OPTIONS -fglasgow-exts #-} --- ^ deriving Typeable +-- deriving Typeable ----------------------------------------------------------------------------- -- | -- Module : XMonad.Hooks.ManageDocks @@ -18,23 +18,24 @@ -- It also allows you to reset the gap to reflect the state of current STRUT -- windows (for example, after you resized or closed a panel), and to toggle the Gap -- in a STRUT-aware fashion. - +-- -- The avoidStruts layout modifier allows you to make xmonad dynamically -- avoid overlapping windows with panels. You can (optionally) enable this -- on a selective basis, so that some layouts will effectively hide the -- panel, by placing windows on top of it. An example use of avoidStruts -- would be: - +-- -- > layoutHook = Layout $ toggleLayouts (noBorders Full) $ avoidStruts $ -- > your actual layouts here ||| ... - +-- -- You may also wish to bind a key to sendMessage ToggleStruts, which will -- toggle the avoidStruts behavior, so you can hide your panel at will. - +-- -- This would enable a full-screen mode that overlaps the panel, while all -- other layouts avoid the panel. - +-- ----------------------------------------------------------------------------- + module XMonad.Hooks.ManageDocks ( -- * Usage -- $usage |