~/.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

@@ -24,7 +24,7 @@ import XMonad
import Data.Time (NominalDiffTime, diffUTCTime, getCurrentTime)
-- $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.Actions.AfterDrag
--

View File

@@ -29,7 +29,7 @@ import System.Exit
-- $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.Hooks.ServerMode
-- > import XMonad.Actions.BluetileCommands

View File

@@ -37,7 +37,7 @@ 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.Actions.Commands
--

View File

@@ -26,7 +26,7 @@ import XMonad
-- $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 qualified XMonad.Actions.ConstrainedResize as Sqr
--

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@ file:
-- You can use this module with the following in your @xmonad.hs@ file:
--
-- > import XMonad.Actions.CopyWindow
--

View File

@@ -47,7 +47,7 @@ import Data.Function (on)
import Control.Monad.State (lift)
-- $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.Actions.CycleRecentWS
-- >

View File

@@ -23,7 +23,7 @@ import XMonad.Prelude (elemIndex, fromMaybe)
import qualified XMonad.StackSet 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
-- > import XMonad.Actions.CycleSelectedLayouts

View File

@@ -92,7 +92,7 @@ import XMonad.Util.Types
import XMonad.Util.WorkspaceCompare
-- $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.Actions.CycleWS
-- >

View File

@@ -64,7 +64,7 @@ import Control.Arrow (second)
import Control.Monad.Trans (lift)
-- $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.Actions.CycleWindows
-- > -- config

View File

@@ -39,7 +39,7 @@ import qualified XMonad.StackSet as W
import XMonad
-- $usage
-- To use demanage, add this import to your @~\/.xmonad\/xmonad.hs@:
-- To use demanage, add this import to your @xmonad.hs@:
--
-- > import XMonad.Actions.DeManage
--

View File

@@ -31,7 +31,7 @@ import qualified Data.List.NonEmpty as NE
-- $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.Actions.DwmPromote
--

View File

@@ -51,7 +51,7 @@ import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Actions.TopicSpace
-- $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.Actions.DynamicWorkspaceGroups
--

View File

@@ -49,7 +49,7 @@ import XMonad.Prelude (fromJust, fromMaybe)
import Data.Ord (comparing)
-- $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 qualified XMonad.Actions.DynamicWorkspaceOrder as DO
--

View File

@@ -44,7 +44,7 @@ import qualified Data.Map.Strict as Map
import qualified XMonad.Util.ExtensibleState as XS
-- $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.Actions.DynamicWorkspaces
-- > import XMonad.Actions.CopyWindow(copy)

View File

@@ -51,7 +51,7 @@ import qualified Data.Map.Strict as M (Map, elems, map, mapWithKey)
-- $usage
--
-- You can use this module's basic functionality with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Actions.EasyMotion (selectWindow)
--

View File

@@ -25,7 +25,7 @@ import XMonad.StackSet
-- $usage
--
-- To use, import this module into your @~\/.xmonad\/xmonad.hs@:
-- To use, import this module into your @xmonad.hs@:
--
-- > import XMonad.Actions.FindEmptyWorkspace
--

View File

@@ -29,7 +29,7 @@ import qualified Prelude as P
import Prelude (Double, Integer, Ord (..), const, fromIntegral, fst, id, otherwise, round, snd, uncurry, ($))
-- $usage
-- First, add this import to your @~\/.xmonad\/xmonad.hs@:
-- First, add this import to your @xmonad.hs@:
--
-- > import qualified XMonad.Actions.FlexibleManipulate as Flex
--

View File

@@ -25,7 +25,7 @@ import XMonad.Prelude (fi)
import Foreign.C.Types
-- $usage
-- To use, first import this module into your @~\/.xmonad\/xmonad.hs@ file:
-- To use, first import this module into your @xmonad.hs@ file:
--
-- > import qualified XMonad.Actions.FlexibleResize as Flex
--

View File

@@ -30,7 +30,7 @@ import XMonad.Prelude (fi)
import XMonad.Util.Types
-- $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.Actions.FloatKeys
--

View File

@@ -37,7 +37,7 @@ import XMonad.Util.Types (Direction2D(..))
import XMonad.Actions.AfterDrag
-- $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.Actions.FloatSnap
--

View File

@@ -25,7 +25,7 @@ import XMonad.Prelude
import XMonad.StackSet
-- $usage
-- Add the import to your @~\/.xmonad\/xmonad.hs@:
-- Add the import to your @xmonad.hs@:
--
-- > import XMonad.Actions.FocusNth
--

View File

@@ -101,7 +101,7 @@ import qualified Data.List.NonEmpty as NE
-- $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.Actions.GridSelect
--

View File

@@ -53,7 +53,7 @@ import qualified XMonad.Util.ExtensibleState as XS
{- $usage
Import the module into your @~\/.xmonad\/xmonad.hs@:
Import the module into your @xmonad.hs@:
> import XMonad.Actions.GroupNavigation
@@ -129,7 +129,7 @@ focusNextMatchOrDo qry act = findM (runQuery qry)
>=> maybe act (windows . SS.focusWindow)
-- Returns the list of windows ordered by workspace as specified in
-- ~/.xmonad/xmonad.hs
-- @xmonad.hs@.
orderedWindowList :: Direction -> X (Seq Window)
orderedWindowList History = fmap (\(HistoryDB w ws) -> maybe ws (ws |>) w) XS.get
orderedWindowList dir = withWindowSet $ \ss -> do
@@ -145,7 +145,7 @@ orderedWindowList dir = withWindowSet $ \ss -> do
dirfun _ = id
rotfun wins x = rotate $ rotateTo (== x) wins
-- Returns the ordered workspace list as specified in ~/.xmonad/xmonad.hs
-- Returns the ordered workspace list as specified in @xmonad.hs@.
orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace
orderedWorkspaceList ss wsids = rotateTo isCurWS wspcs'
where

View File

@@ -36,7 +36,7 @@ import qualified Data.Map as M
( insert, delete, Map, lookup, empty, filter )
-- $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.Actions.LinkWorkspaces
--

View File

@@ -53,7 +53,7 @@ import XMonad.StackSet ( Workspace, current, workspace, layout, tag )
import Control.Monad.State ( gets )
-- $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.Actions.MessageFeedback
--

View File

@@ -32,7 +32,7 @@ import Data.Map (Map)
-- $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.Actions.MouseGestures
-- > import qualified XMonad.StackSet as W

View File

@@ -37,7 +37,7 @@ import XMonad.Util.XUtils
-- "XMonad.Layout.SimpleFloat" or "XMonad.Layout.DecorationMadness".
--
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Actions.MouseResize
-- > import XMonad.Layout.WindowArranger

View File

@@ -85,7 +85,7 @@ import qualified Data.List.NonEmpty as NE
-- layers and allows customization of the navigation strategy for the tiled
-- layer based on the layout currently in effect.
--
-- You can use this module with (a subset of) the following in your @~\/.xmonad\/xmonad.hs@:
-- You can use this module with (a subset of) the following in your @xmonad.hs@:
--
-- > import XMonad.Actions.Navigation2D
--

View File

@@ -148,7 +148,7 @@ toggleOrView' f i st = fromMaybe (f i st) $ do
--
-- This module provides an easy way to control, what you see on other screens in
-- xinerama mode without having to focus them. Put this into your
-- @~\/.xmonad\/xmonad.hs@:
-- @xmonad.hs@:
--
-- > import XMonad.Actions.OnScreen
--

View File

@@ -25,7 +25,7 @@ import XMonad.StackSet 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.Actions.PerLayoutKeys
--

View File

@@ -24,7 +24,7 @@ import XMonad
-- $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.Actions.PerWindowKeys
--

View File

@@ -25,7 +25,7 @@ import XMonad.StackSet 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.Actions.PerWorkspaceKeys
--

View File

@@ -46,7 +46,7 @@ To create a screen comparator you can use screenComparatorByRectangle or screenC
The default ScreenComparator orders screens by the upper-left-most corner, from top-to-bottom
and then left-to-right.
Example usage in your @~\/.xmonad\/xmonad.hs@ file:
Example usage in your @xmonad.hs@ file:
> import XMonad.Actions.PhysicalScreens
> import Data.Default

View File

@@ -47,7 +47,7 @@ import XMonad.StackSet hiding (workspaces)
import XMonad.Util.Run
-- $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.Actions.Plane
-- > import Data.Map (union)

View File

@@ -28,7 +28,7 @@ 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.Actions.Promote
--

View File

@@ -35,7 +35,7 @@ import XMonad.StackSet (Screen (Screen), Stack (Stack), current, floating, modif
import XMonad.Util.Stack (reverseS)
{- $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.Actions.RotateSome

View File

@@ -42,7 +42,7 @@ import XMonad.Util.XUtils (createNewWindow
import qualified XMonad.Util.ExtensibleState as ES
-- $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.Actions.ShowText
--

View File

@@ -28,7 +28,7 @@ import XMonad.StackSet (Stack (Stack), StackSet, modify')
import XMonad.Util.Stack (reverseS)
-- $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.Actions.Sift
--

View File

@@ -24,7 +24,7 @@ import XMonad.Core
import XMonad.Util.Run
-- $usage
-- To use, import this module into @~\/.xmonad\/xmonad.hs@:
-- To use, import this module into @xmonad.hs@:
--
-- > import XMonad.Actions.SimpleDate
--

View File

@@ -23,7 +23,7 @@ import XMonad.Actions.WithAll (sinkAll)
-- $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.Actions.SinkAll
--

View File

@@ -43,7 +43,7 @@ import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Util.Process (getPPIDChain)
-- $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.Actions.SpawnOn
--

View File

@@ -32,10 +32,7 @@ import XMonad.Util.XUtils
{- $usage
First, import this module into your @~\/.xmonad\/xmonad.hs@:
First, import this module into your @xmonad.hs@:
> import XMonad.Actions.Submap

View File

@@ -30,7 +30,7 @@ import XMonad.Util.WorkspaceCompare
-- $usage
-- Add this import to your @~\/.xmonad\/xmonad.hs@:
-- Add this import to your @xmonad.hs@:
--
-- > import XMonad.Actions.SwapWorkspaces
--

View File

@@ -39,7 +39,7 @@ econst = const . return
-- $usage
--
-- To use window tags, import this module into your @~\/.xmonad\/xmonad.hs@:
-- To use window tags, import this module into your @xmonad.hs@:
--
-- > import XMonad.Actions.TagWindows
-- > import XMonad.Prompt -- to use tagPrompt

View File

@@ -27,7 +27,7 @@ import qualified XMonad.StackSet as W
import XMonad.Layout.DraggingVisualizer
-- $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.Actions.TiledWindowDragging
-- > import XMonad.Layout.DraggingVisualizer

View File

@@ -108,7 +108,7 @@ import XMonad.Hooks.WorkspaceHistory
-- <https://tony-zorman.com/posts/topic-space/2022-09-11-topic-spaces.html here>.
-- $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 qualified Data.Map.Strict as M
-- > import qualified XMonad.StackSet as W

View File

@@ -27,7 +27,7 @@ import qualified XMonad.StackSet as W
-- $usage
-- To make the focus update on mouse movement within an unfocused window, add the
-- following to your @~\/.xmonad\/xmonad.hs@:
-- following to your @xmonad.hs@:
--
-- > import XMonad.Actions.UpdateFocus
-- > xmonad $ def {

View File

@@ -31,7 +31,7 @@ import XMonad.StackSet (member, peek, screenDetail, current)
import Control.Arrow ((&&&), (***))
-- $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.Actions.UpdatePointer

View File

@@ -28,7 +28,7 @@ import XMonad
import 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.Actions.Warp

View File

@@ -36,7 +36,7 @@ import XMonad.Util.NamedWindows (getName, getNameWMClass)
-- $usage
--
-- Import the module into your @~\/.xmonad\/xmonad.hs@:
-- Import the module into your @xmonad.hs@:
--
-- > import XMonad.Actions.WindowBringer
--

View File

@@ -52,7 +52,7 @@ import qualified Data.List.NonEmpty as NE
{- $usage
Import the module into your @~\/.xmonad\/xmonad.hs@:
Import the module into your @xmonad.hs@:
> import XMonad.Actions.WindowGo

View File

@@ -34,7 +34,7 @@ import XMonad.Prelude (fi)
-- $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.Actions.WindowMenu
--

View File

@@ -24,7 +24,7 @@ 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.Actions.WithAll
--

View File

@@ -43,7 +43,7 @@ import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Actions.OnScreen
-- $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.Actions.Workscreen
-- > myWorkspaces = let myOldWorkspaces = ["adm","work","mail"]

View File

@@ -58,7 +58,7 @@ import XMonad.Util.WorkspaceCompare (getSortByIndex)
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.Actions.WorkspaceNames
--