~/.xmonad/xmonad.hs -> xmonad.hs

With XDG support so firmly ingrained now, it's about time we stop
hard-coding the configuration path in the docs.
This commit is contained in:
Tony Zorman
2023-12-22 18:16:07 +01:00
parent c01cd3a33b
commit b1b3c4c469
194 changed files with 210 additions and 213 deletions

View File

@@ -25,7 +25,7 @@ import qualified XMonad.StackSet as W
import Data.Ratio
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Accordion
--

View File

@@ -35,7 +35,7 @@ import qualified Data.Map as M
import qualified Data.Set as S
-- $usage
-- You can use this module with the following in your ~\/.xmonad\/xmonad.hs file:
-- You can use this module with the following in your @xmonad.hs@ file:
--
-- > import XMonad.Layout.AvoidFloats
--

View File

@@ -52,7 +52,7 @@ import qualified Data.Set as S
import Data.Ratio ((%))
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.BinarySpacePartition
--

View File

@@ -38,7 +38,7 @@ import qualified Data.Map as M
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.BorderResize
-- > myLayout = borderResize (... layout setup that reacts to SetGeometry ...)

View File

@@ -45,7 +45,7 @@ import qualified XMonad.StackSet as W
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.BoringWindows
--

View File

@@ -33,7 +33,7 @@ import XMonad.Layout.DecorationAddons
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.DecorationAddons
-- > import XMonad.Layout.ButtonDecoration

View File

@@ -30,7 +30,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.Prelude (fi)
-- $usage
-- You can use this module by including the following in your @~\/.xmonad/xmonad.hs@:
-- You can use this module by including the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.CenteredIfSingle
--

View File

@@ -26,7 +26,7 @@ import GHC.Real (Ratio(..))
import XMonad.Layout.CircleEx
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Circle
--

View File

@@ -33,7 +33,7 @@ import XMonad.StackSet (Stack (..), Workspace (..), integrate')
import XMonad.Util.Stack (zipperFocusedAtFirstOf)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Combo
--

View File

@@ -34,7 +34,7 @@ import XMonad.Util.Stack (zipperFocusedAtFirstOf)
import XMonad.Util.WindowProperties
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.ComboP
--

View File

@@ -23,7 +23,7 @@ import XMonad.StackSet( focus, up, down )
import XMonad.Prelude( msum )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Cross
--

View File

@@ -100,7 +100,7 @@ import XMonad.Layout.SimpleFloat
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.DecorationMadness
--

View File

@@ -27,7 +27,7 @@ import XMonad.StackSet (integrate)
import XMonad.Prelude (ap)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Dishes
--

View File

@@ -35,7 +35,7 @@ import XMonad.Util.Invisible
import XMonad.Util.XUtils
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.DragPane
--

View File

@@ -41,7 +41,7 @@ import XMonad.StackSet as S
import XMonad.Layout.Reflect
-- $usage
-- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
-- To use this module, add the following import to @xmonad.hs@:
--
-- > import XMonad.Layout.Drawer
--

View File

@@ -30,7 +30,7 @@ import XMonad.Layout.Decoration
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.DwmStyle
--

View File

@@ -38,7 +38,7 @@ import XMonad.Layout.Decoration
import XMonad.Layout.LayoutHints
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.FixedAspectRatio
-- Then add it to your layout:

View File

@@ -28,7 +28,7 @@ import XMonad.Prelude
import qualified XMonad.StackSet as W
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.FixedColumn
--

View File

@@ -44,7 +44,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.Util.Types (Direction2D(..))
-- $usage
-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
-- You can use this module by importing it into your @xmonad.hs@ file:
--
-- > import XMonad.Layout.Gaps
--

View File

@@ -25,7 +25,7 @@ import XMonad
import XMonad.StackSet
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Grid
--

View File

@@ -76,7 +76,7 @@ import XMonad.Layout.Simplest
--
-- > import XMonad.Layout.Groups.Examples
--
-- to the top of your @.\/.xmonad\/xmonad.hs@.
-- to the top of your @xmonad.hs@.
--
-- For more information on using any of the layouts, jump directly
-- to its \"Example\" section.

View File

@@ -58,7 +58,7 @@ import qualified Data.Map as M
--
-- > import XMonad.Layout.Groups.Helpers
--
-- to the top of your @.\/.xmonad\/xmonad.hs@.
-- to the top of your @xmonad.hs@.
--
-- "XMonad.Layout.Groups"-based layouts do not have the same notion
-- of window ordering as the rest of XMonad. For this reason, the usual

View File

@@ -66,7 +66,7 @@ import XMonad.Layout.Simplest
--
-- > import XMonad.Layout.Groups.Wmii
--
-- to the top of your @.\/.xmonad\/xmonad.hs@, and adding 'wmii'
-- to the top of your @xmonad.hs@, and adding 'wmii'
-- (with a 'Shrinker' and decoration 'Theme' as
-- parameters) to your layout hook, for example:
--

View File

@@ -37,7 +37,7 @@ import qualified XMonad.StackSet as W
--------------------------------------------------------------------------------
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Hidden
--

View File

@@ -36,7 +36,7 @@ infixr 9 .
(.) = fmap
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.HintedGrid
--

View File

@@ -27,7 +27,7 @@ import qualified XMonad.StackSet as W
import XMonad.Prelude
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.HintedTile
--

View File

@@ -39,7 +39,7 @@ import qualified XMonad.StackSet as S
import Control.Arrow (first)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.IM
-- > import Data.Ratio ((%))

View File

@@ -47,7 +47,7 @@ import XMonad.Layout.Maximize
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.ImageButtonDecoration
--

View File

@@ -42,7 +42,7 @@ import XMonad.Prelude
import qualified XMonad.StackSet as W
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.IndependentScreens
--

View File

@@ -66,7 +66,7 @@ import XMonad.Util.WindowProperties
--------------------------------------------------------------------------------
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.LayoutBuilder
--

View File

@@ -51,7 +51,7 @@ import XMonad.Layout.Combo
import XMonad.Layout.DragPane
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.LayoutCombinators
--

View File

@@ -47,7 +47,7 @@ import Data.Set (Set)
import qualified Data.Set as Set
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.LayoutHints
--

View File

@@ -36,7 +36,7 @@ import qualified XMonad.StackSet as W
-- email window at all times, a crude mimic of sticky windows).
--
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@ file:
-- @xmonad.hs@ file:
--
-- > import XMonad.Layout.LayoutScreens
-- > import XMonad.Layout.TwoPane

View File

@@ -44,7 +44,7 @@ import XMonad.Prelude (fromJust, guard, (<=<))
import qualified XMonad.StackSet as W
-- $usage
-- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
-- To use this module, add the following import to @xmonad.hs@:
--
-- > import XMonad.Layout.LimitWindows
--

View File

@@ -34,7 +34,7 @@ import XMonad.Prelude(All(..))
import qualified Data.Map as M
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.MagicFocus
--

View File

@@ -59,7 +59,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.StackSet
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Magnifier
--

View File

@@ -31,7 +31,7 @@ import XMonad.Layout.LayoutModifier
import Control.Arrow (first)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Master
--

View File

@@ -31,7 +31,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.Prelude ( partition )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Maximize
--

View File

@@ -35,7 +35,7 @@ import XMonad.Layout.LayoutModifier (LayoutModifier(..), ModifiedLayout(..))
import Control.Arrow (second)
-- $usage
-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
-- You can use this module by importing it into your @xmonad.hs@ file:
--
-- > import XMonad.Layout.MessageEscape
--

View File

@@ -30,7 +30,7 @@ import XMonad.Layout.BoringWindows as BW
import qualified XMonad.Util.ExtensibleState as XS
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Minimize
--

View File

@@ -40,7 +40,7 @@ import XMonad.Hooks.ManageHelpers (doHideIgnore)
import XMonad.Hooks.FadeInactive (setOpacity)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Monitor
--

View File

@@ -41,7 +41,7 @@ import qualified XMonad.StackSet as W
import Control.Arrow(second, first)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Mosaic
--

View File

@@ -38,7 +38,7 @@ import XMonad.Prelude ( sortBy )
import Data.Ratio
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.MosaicAlt
-- > import qualified Data.Map as M

View File

@@ -41,7 +41,7 @@ import XMonad.Util.XUtils
import Graphics.X11 as X
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.MouseResizableTile
--

View File

@@ -29,7 +29,7 @@ import qualified XMonad.StackSet as W
import XMonad.Prelude
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.MultiColumns
--

View File

@@ -27,7 +27,7 @@ import XMonad.StackSet (integrate)
import XMonad.Prelude (ap)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.MultiDishes
--

View File

@@ -27,7 +27,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.Layout.Renamed
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Named
--

View File

@@ -45,7 +45,7 @@ import qualified Data.Map as M
-- $usage
-- You can use this module with the following in your ~\/.xmonad\/xmonad.hs file:
-- You can use this module with the following in your xmonad.hs file:
--
-- > import XMonad.Layout.NoBorders
--

View File

@@ -31,7 +31,7 @@ import XMonad.Layout.SimpleDecoration
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.NoFrillsDecoration
--

View File

@@ -34,7 +34,7 @@ import Data.Maybe (fromMaybe)
import System.Posix.Env (getEnv)
-- $usage
-- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
-- You can use this module by importing it into your @xmonad.hs@ file:
--
-- > import XMonad.Layout.OnHost
--

View File

@@ -29,7 +29,7 @@ import qualified XMonad.StackSet as W
import XMonad.Prelude (fromMaybe)
-- $usage
-- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
-- You can use this module by importing it into your @xmonad.hs@ file:
--
-- > import XMonad.Layout.PerScreen
--

View File

@@ -29,7 +29,7 @@ import qualified XMonad.StackSet as W
import XMonad.Prelude (fromMaybe)
-- $usage
-- You can use this module by importing it into your ~\/.xmonad\/xmonad.hs file:
-- You can use this module by importing it into your @xmonad.hs@ file:
--
-- > import XMonad.Layout.PerWorkspace
--

View File

@@ -33,7 +33,7 @@ import XMonad.Layout.WindowArranger
import XMonad.Prelude (fromMaybe, isJust, nub, when)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.PositionStoreFloat
-- > import XMonad.Layout.NoFrillsDecoration

View File

@@ -32,7 +32,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.Layout.MultiToggle
-- $usage
-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@ file:
-- You can use this module by importing it into your @xmonad.hs@ file:
--
-- > import XMonad.Layout.Reflect
--

View File

@@ -30,7 +30,7 @@ import XMonad.Layout.LayoutModifier
--
-- > import XMonad.Layout.Renamed
--
-- to your @~\/.xmonad\/xmonad.hs@.
-- to your @xmonad.hs@.
--
-- You can then use 'renamed' to modify the description of your
-- layouts. For example:

View File

@@ -31,7 +31,7 @@ import qualified Data.Map as M
import Data.Ratio
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.ResizableThreeColumns
--

View File

@@ -27,7 +27,7 @@ import qualified XMonad.StackSet as W
import qualified Data.Map as M
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.ResizableTile
--

View File

@@ -31,7 +31,7 @@ import XMonad.Layout.Decoration
-- $usage
-- You can use this module by importing it into your
-- @~\/.xmonad\/xmonad.hs@ file:
-- @xmonad.hs@ file:
--
-- > import XMonad.Layout.ResizeScreen
--

View File

@@ -27,7 +27,7 @@ import qualified XMonad.StackSet as W
import Data.Ratio
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Roledex
--

View File

@@ -35,7 +35,7 @@ import XMonad.Util.XUtils
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.ShowWName
-- > myLayout = layoutHook def

View File

@@ -32,7 +32,7 @@ import XMonad.Layout.Decoration
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.SimpleDecoration
--

View File

@@ -33,7 +33,7 @@ import XMonad.Layout.WindowArranger
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.SimpleFloat
--

View File

@@ -26,7 +26,7 @@ import qualified XMonad.StackSet as S
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.Simplest
--

View File

@@ -28,7 +28,7 @@ import XMonad.Layout.LayoutModifier
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.SimplestFloat
--

View File

@@ -33,7 +33,7 @@ import XMonad.Util.WindowProperties
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.SortedLayout
--

View File

@@ -51,7 +51,7 @@ import XMonad.Actions.MessageFeedback
-- $usage
-- You can use this module by importing it into your @~\/.xmonad\/xmonad.hs@
-- You can use this module by importing it into your @xmonad.hs@
-- file:
--
-- > import XMonad.Layout.Spacing

View File

@@ -31,7 +31,7 @@ import XMonad hiding ( Rotation )
import XMonad.StackSet ( integrate )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Spiral
--

View File

@@ -29,7 +29,7 @@ import XMonad
import XMonad.StackSet ( integrate )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
-- You can use this module with the following in your @xmonad.hs@ file:
--
-- > import XMonad.Layout.Square
--

View File

@@ -27,7 +27,7 @@ import qualified XMonad.StackSet as W
import XMonad.Prelude
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.StackTile
--

View File

@@ -58,7 +58,7 @@ import XMonad.Layout.LayoutModifier
import System.Posix.Signals
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad
-- > import XMonad.Layout.Stoppable

View File

@@ -113,7 +113,7 @@ import qualified Data.Set as S
--
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.SubLayouts
-- > import XMonad.Layout.WindowNavigation

View File

@@ -31,7 +31,7 @@ import XMonad.Prompt ( XPPosition (..) )
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.TabBarDecoration
--

View File

@@ -43,7 +43,7 @@ import XMonad.Layout.Simplest ( Simplest(Simplest) )
import XMonad.Util.Types (Direction2D(..))
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.Tabbed
--

View File

@@ -56,7 +56,7 @@ import XMonad.Util.Stack (zipperFocusedAtFirstOf)
---------------------------------------------------------------------------------
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.TallMastersCombo
--

View File

@@ -32,7 +32,7 @@ import qualified XMonad.StackSet as W
import Data.Ratio
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.ThreeColumns
--

View File

@@ -25,7 +25,7 @@ import XMonad.Prelude (fromMaybe)
import XMonad.StackSet (Workspace (..))
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.ToggleLayouts
--

View File

@@ -27,7 +27,7 @@ import XMonad hiding (focus)
import XMonad.StackSet ( focus, up, down)
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.TwoPane
--

View File

@@ -28,7 +28,7 @@ import XMonad.StackSet (focus, up, down, Stack, Stack(..))
import XMonad hiding (focus)
-- $usage
-- Import the module in @~\/.xmonad\/xmonad.hs@:
-- Import the module in @xmonad.hs@:
--
-- > import XMonad.Layout.TwoPanePersistent
--

View File

@@ -35,7 +35,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.StackSet (integrate)
-- $usage
-- You can use this module with the following in your ~\/.xmonad/xmonad.hs
-- You can use this module with the following in your @xmonad.hs@
-- file:
--
-- > import XMonad.Layout.VoidBorders

View File

@@ -35,7 +35,7 @@ import Control.Arrow ((***), (>>>), (&&&), first)
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.WindowArranger
-- > myLayout = layoutHook def

View File

@@ -35,7 +35,7 @@ import XMonad.Util.Types (Direction2D(..))
import XMonad.Util.XUtils
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.WindowNavigation
--

View File

@@ -36,7 +36,7 @@ import Foreign.C.Types(CInt)
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Layout.WindowSwitcherDecoration
-- > import XMonad.Layout.DraggingVisualizer

View File

@@ -41,7 +41,7 @@ import XMonad.Layout.LayoutModifier
import XMonad.StackSet ( tag, currentTag )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.WorkspaceDir
--

View File

@@ -49,7 +49,7 @@ import Control.Arrow (second)
-- and decreased, and a window can be set to use the whole available
-- space whenever it has focus.
--
-- You can use this module by including the following in your @~\/.xmonad/xmonad.hs@:
-- You can use this module by including the following in your @xmonad.hs@:
--
-- > import XMonad.Layout.ZoomRow
--