diff --git a/CHANGES.md b/CHANGES.md index 3579d151..e2768242 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -408,6 +408,9 @@ - The API for this module is frozen: this is now a compatibility wrapper. + - References for this module are updated to point to `X.H.StatusBar` or + `X.H.StatusBar.PP` + * `XMonad.Layout.BoringWindows` - Added boring-aware `swapUp`, `swapDown`, `siftUp`, and `siftDown` functions. diff --git a/XMonad/Actions/DynamicWorkspaceOrder.hs b/XMonad/Actions/DynamicWorkspaceOrder.hs index 4b5564bf..eb8291a5 100644 --- a/XMonad/Actions/DynamicWorkspaceOrder.hs +++ b/XMonad/Actions/DynamicWorkspaceOrder.hs @@ -11,7 +11,7 @@ -- -- Remember a dynamically updateable ordering on workspaces, together -- with tools for using this ordering with "XMonad.Actions.CycleWS" --- and "XMonad.Hooks.DynamicLog". +-- and "XMonad.Hooks.StatusBar.PP". -- ----------------------------------------------------------------------------- @@ -68,10 +68,10 @@ import Data.Ord (comparing) -- order of workspaces must be updated to use the auxiliary ordering. -- -- To change the order in which workspaces are displayed by --- "XMonad.Hooks.DynamicLog", use 'getSortByOrder' in your --- 'XMonad.Hooks.DynamicLog.ppSort' field, for example: +-- "XMonad.Hooks.StatusBar.PP", use 'getSortByOrder' in your +-- 'XMonad.Hooks.StatusBar.PP.ppSort' field, for example: -- --- > ... dynamicLogWithPP $ byorgeyPP { +-- > myPP = ... byorgeyPP { -- > ... -- > , ppSort = DO.getSortByOrder -- > ... diff --git a/XMonad/Actions/Prefix.hs b/XMonad/Actions/Prefix.hs index f10ff553..616fca7d 100644 --- a/XMonad/Actions/Prefix.hs +++ b/XMonad/Actions/Prefix.hs @@ -195,7 +195,12 @@ isPrefixNumeric _ = False -- > myPrinter :: PP -- > myPrinter = def { ppExtras = [ppFormatPrefix] } -- --- And then in your 'logHook' configuration +-- And then add to your status bar using "XMonad.Hooks.StatusBar": +-- +-- > mySB = statusBarProp "xmobar" myPrinter +-- > main = xmonad $ withEasySB mySB defToggleStrutsKey def +-- +-- Or, directly in your 'logHook' configuration -- -- > logHook = dynamicLogWithPP myPrinter ppFormatPrefix :: X (Maybe String) diff --git a/XMonad/Actions/TopicSpace.hs b/XMonad/Actions/TopicSpace.hs index 46ceb6f3..6060301b 100644 --- a/XMonad/Actions/TopicSpace.hs +++ b/XMonad/Actions/TopicSpace.hs @@ -72,16 +72,16 @@ where import XMonad import XMonad.Prelude -import qualified Data.Map.Strict as M -import qualified XMonad.Hooks.DynamicLog as DL -import qualified XMonad.StackSet as W +import qualified Data.Map.Strict as M +import qualified XMonad.Hooks.StatusBar.PP as SBPP +import qualified XMonad.StackSet as W import Data.Map (Map) import XMonad.Prompt (XPConfig) import XMonad.Prompt.Workspace (workspacePrompt) -import XMonad.Hooks.DynamicLog (PP(ppHidden, ppVisible)) +import XMonad.Hooks.StatusBar.PP (PP(ppHidden, ppVisible)) import XMonad.Hooks.UrgencyHook (readUrgents) import XMonad.Hooks.WorkspaceHistory ( workspaceHistory @@ -284,9 +284,9 @@ setLastFocusedTopic tc w predicate = do reverseLastFocusedTopics :: X () reverseLastFocusedTopics = workspaceHistoryModify reverse --- | This function is a variant of 'DL.pprWindowSet' which takes a topic configuration --- and a pretty-printing record 'PP'. It will show the list of topics sorted historically --- and highlight topics with urgent windows. +-- | This function is a variant of 'SBPP.pprWindowSet' which takes a topic +-- configuration and a pretty-printing record 'PP'. It will show the list of +-- topics sorted historically and highlight topics with urgent windows. pprWindowSet :: TopicConfig -> PP -> X String pprWindowSet tg pp = do winset <- gets windowset @@ -301,7 +301,7 @@ pprWindowSet tg pp = do add_depth proj topic = proj pp . (((topic++":")++) . show) . depth $ topic pp' = pp { ppHidden = add_depth ppHidden, ppVisible = add_depth ppVisible } sortWindows = take maxDepth . sortOn (depth . W.tag) - return $ DL.pprWindowSet sortWindows urgents pp' winset + return $ SBPP.pprWindowSet sortWindows urgents pp' winset -- | Given a prompt configuration and a topic configuration, trigger the action associated with -- the topic given in prompt. diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs index 8ef11964..5f06cdf9 100644 --- a/XMonad/Actions/WindowNavigation.hs +++ b/XMonad/Actions/WindowNavigation.hs @@ -63,6 +63,11 @@ import qualified Data.Set as S -- > $ def { ... } -- > xmonad config -- +-- Or, for the brave souls: +-- +-- > main = xmonad =<< withWindowNavigation (xK_w, xK_a, xK_s, xK_d) +-- > $ def { ... } +-- -- Here, we pass in the keys for navigation in counter-clockwise order from up. -- It creates keybindings for @modMask@ to move to window, and @modMask .|. shiftMask@ -- to swap windows. diff --git a/XMonad/Actions/WorkspaceCursors.hs b/XMonad/Actions/WorkspaceCursors.hs index b0e34f0e..0e0d7b94 100644 --- a/XMonad/Actions/WorkspaceCursors.hs +++ b/XMonad/Actions/WorkspaceCursors.hs @@ -58,13 +58,10 @@ import XMonad.Prelude (find, fromJust, guard, liftA2, toList, when, (<=<)) -- -- > import XMonad -- > import XMonad.Actions.WorkspaceCursors --- > import XMonad.Hooks.DynamicLog -- > import XMonad.Util.EZConfig -- > import qualified XMonad.StackSet as W -- > --- > main = do --- > x <- xmobar conf --- > xmonad x +-- > main = xmonad conf -- > -- > conf = additionalKeysP def -- > { layoutHook = workspaceCursors myCursors $ layoutHook def @@ -89,7 +86,8 @@ import XMonad.Prelude (find, fromJust, guard, liftA2, toList, when, (<=<)) -- workspaces. Or change it such that workspaces are created when you try to -- view it. -- --- * Function for pretty printing for DynamicLog that groups workspaces by +-- * Function for pretty printing for "XMonad.Hooks.StatusBar.PP" that groups +-- workspaces by -- common prefixes -- -- * Examples of adding workspaces to the cursors, having them appear multiple diff --git a/XMonad/Actions/WorkspaceNames.hs b/XMonad/Actions/WorkspaceNames.hs index 1e877ec0..1f250025 100644 --- a/XMonad/Actions/WorkspaceNames.hs +++ b/XMonad/Actions/WorkspaceNames.hs @@ -9,7 +9,7 @@ -- Stability : experimental -- Portability : unportable -- --- Provides bindings to rename workspaces, show these names in DynamicLog and +-- Provides bindings to rename workspaces, show these names in a status bar and -- swap workspaces along with their names. These names survive restart. -- Together with "XMonad.Layout.WorkspaceDir" this provides for a fully -- dynamic topic space workflow. @@ -49,7 +49,7 @@ import qualified XMonad.Util.ExtensibleState as XS import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..), anyWS) import qualified XMonad.Actions.SwapWorkspaces as Swap -import XMonad.Hooks.DynamicLog (PP(..)) +import XMonad.Hooks.StatusBar.PP (PP(..)) import XMonad.Prompt (mkXPrompt, XPConfig) import XMonad.Prompt.Workspace (Wor(Wor)) import XMonad.Util.WorkspaceCompare (getSortByIndex) @@ -65,10 +65,12 @@ import qualified Data.Map as M -- -- > , ((modm .|. shiftMask, xK_r ), renameWorkspace def) -- --- and apply workspaceNamesPP to your DynamicLog pretty-printer: +-- and apply workspaceNamesPP to your pretty-printer: -- --- > myLogHook = --- > workspaceNamesPP xmobarPP >>= dynamicLogString >>= xmonadPropLog +-- > myPP = workspaceNamesPP xmobarPP +-- +-- Check "XMonad.Hooks.StatusBar" for more information on how to incorprate +-- this into your status bar. -- -- We also provide a modification of "XMonad.Actions.SwapWorkspaces"\'s -- functionality, which may be used this way: @@ -133,7 +135,7 @@ renameWorkspace conf = mkXPrompt pr conf (const (return [])) setCurrentWorkspaceName where pr = Wor "Workspace name: " --- | Modify "XMonad.Hooks.DynamicLog"\'s pretty-printing format to show +-- | Modify 'XMonad.Hooks.StatusBar.PP.PP'\'s pretty-printing format to show -- workspace names as well. workspaceNamesPP :: PP -> X PP workspaceNamesPP pp = getWorkspaceNames ":" <&> \ren -> pp{ ppRename = ppRename pp >=> ren } diff --git a/XMonad/Hooks/DynamicBars.hs b/XMonad/Hooks/DynamicBars.hs index c26b1dce..455bbd9d 100644 --- a/XMonad/Hooks/DynamicBars.hs +++ b/XMonad/Hooks/DynamicBars.hs @@ -13,7 +13,7 @@ -- ----------------------------------------------------------------------------- -module XMonad.Hooks.DynamicBars ( +module XMonad.Hooks.DynamicBars {-# DEPRECATED "Use XMonad.Hooks.StatusBar instead" #-} ( -- * Usage -- $usage DynamicStatusBar diff --git a/XMonad/Hooks/DynamicIcons.hs b/XMonad/Hooks/DynamicIcons.hs index 75db35ae..871f5197 100644 --- a/XMonad/Hooks/DynamicIcons.hs +++ b/XMonad/Hooks/DynamicIcons.hs @@ -10,7 +10,7 @@ -- Stability : unstable -- Portability : unportable -- --- Dynamically augment workspace names logged to a status bar via DynamicLog +-- Dynamically augment workspace names logged to a status bar -- based on the contents (windows) of the workspace. ----------------------------------------------------------------------------- @@ -19,7 +19,7 @@ module XMonad.Hooks.DynamicIcons ( -- $usage -- * Creating Dynamic Icons - dynamicLogIconsWithPP, appIcon, + iconsPP, dynamicLogIconsWithPP, appIcon, -- * Customization dynamicIconsPP, getWorkspaceIcons, @@ -55,11 +55,10 @@ import XMonad.Prelude (for, maybeToList, (<&>), (<=<), (>=>)) -- > , className =? "Spotify" <||> className =? "spotify" --> appIcon "阮" -- > ] -- --- then you can add the hook to your config: +-- then you can add it to your "XMonad.Hooks.StatusBar" config: -- --- > main = xmonad $ … $ def --- > { logHook = dynamicLogIconsWithPP icons xmobarPP --- > , … } +-- > myBar = statusBarProp "xmobar" (iconsPP myIcons myPP) +-- > main = xmonad . withSB myBar $ … $ def -- -- Here is an example of this -- @@ -73,6 +72,18 @@ import XMonad.Prelude (for, maybeToList, (<&>), (<=<), (>=>)) -- advanced example how to do that: -- -- > myIconConfig = def{ iconConfigIcons = myIcons, iconConfigFmt = iconsFmtAppend concat } +-- > myBar = statusBarProp "xmobar" (clickablePP =<< dynamicIconsPP myIconConfig myPP) +-- > main = xmonad . withSB myBar . … $ def +-- +-- This can be also used with "XMonad.Hooks.DynamicLog": +-- +-- > main = xmonad $ … $ def +-- > { logHook = dynamicLogIconsWithPP myIcons xmobarPP +-- > , … } +-- +-- or with more customziation: +-- +-- > myIconConfig = def{ iconConfigIcons = myIcons, iconConfigFmt = iconsFmtAppend concat } -- > main = xmonad $ … $ def -- > { logHook = xmonadPropLog =<< dynamicLogString =<< clickablePP =<< -- > dynamicIconsPP myIconConfig xmobarPP @@ -87,9 +98,15 @@ appIcon = pure . pure dynamicLogIconsWithPP :: Query [String] -- ^ The 'IconSet' to use -> PP -- ^ The 'PP' to alter -> X () -- ^ The resulting 'X' action -dynamicLogIconsWithPP q = dynamicLogWithPP <=< dynamicIconsPP def{ iconConfigIcons = q } +dynamicLogIconsWithPP q = dynamicLogWithPP <=< iconsPP q --- | Modify "XMonad.Hooks.DynamicLog"\'s pretty-printing format to augment +-- | Adjusts the 'PP' with the given 'IconSet' +iconsPP :: Query [String] -- ^ The 'IconSet' to use + -> PP -- ^ The 'PP' to alter + -> X PP -- ^ The resulting 'X PP' +iconsPP q = dynamicIconsPP def{ iconConfigIcons = q } + +-- | Modify a pretty-printer, 'PP', to augment -- workspace names with icons based on the contents (windows) of the workspace. dynamicIconsPP :: IconConfig -> PP -> X PP dynamicIconsPP ic pp = getWorkspaceIcons ic <&> \ren -> pp{ ppRename = ppRename pp >=> ren } diff --git a/XMonad/Hooks/FloatNext.hs b/XMonad/Hooks/FloatNext.hs index 19ec6ec2..9ffcbdab 100644 --- a/XMonad/Hooks/FloatNext.hs +++ b/XMonad/Hooks/FloatNext.hs @@ -30,7 +30,7 @@ module XMonad.Hooks.FloatNext ( -- * Usage , willFloatNext , willFloatAllNew - -- * 'DynamicLog' utilities + -- * Status bar utilities -- $pp , willFloatNextPP , willFloatAllNewPP @@ -97,10 +97,10 @@ willFloatAllNew = willHookAllNew hookName -- $pp -- The following functions are used to display the current -- state of 'floatNext' and 'floatAllNew' in your --- 'XMonad.Hooks.DynamicLog.dynamicLogWithPP'. +-- "XMonad.Hooks.StatusBar.PP". -- 'willFloatNextPP' and 'willFloatAllNewPP' should be added --- to the 'XMonad.Hooks.DynamicLog.ppExtras' field of your --- 'XMonad.Hooks.DynamicLog.PP'. +-- to the 'XMonad.Hooks.StatusBar.PP.ppExtras' field of your +-- "XMonad.Hooks.StatusBar.PP". -- -- Use 'runLogHook' to refresh the output of your 'logHook', so -- that the effects of a 'floatNext'/... will be visible diff --git a/XMonad/Hooks/ToggleHook.hs b/XMonad/Hooks/ToggleHook.hs index 77440923..0eac9027 100644 --- a/XMonad/Hooks/ToggleHook.hs +++ b/XMonad/Hooks/ToggleHook.hs @@ -30,7 +30,7 @@ module XMonad.Hooks.ToggleHook ( -- * Usage , willHookNext , willHookAllNew - -- * 'DynamicLog' utilities + -- * Status bar utilities -- $pp , willHookNextPP , willHookAllNewPP @@ -143,10 +143,10 @@ willHookAllNew n = _get n snd -- $pp -- The following functions are used to display the current -- state of 'hookNext' and 'hookAllNew' in your --- 'XMonad.Hooks.DynamicLog.dynamicLogWithPP'. --- 'willHookNextPP' and 'willHookAllNewPP' should be added --- to the 'XMonad.Hooks.DynamicLog.ppExtras' field of your --- 'XMonad.Hooks.DynamicLog.PP'. +-- "XMonad.Hooks.StatusBar". 'willHookNextPP' and +-- 'willHookAllNewPP' should be added to the +-- 'XMonad.Hooks.StatusBar.PP.ppExtras' field of your +-- "XMonad.Hooks.StatusBar.PP". -- -- Use 'runLogHook' to refresh the output of your 'logHook', so -- that the effects of a 'hookNext'/... will be visible diff --git a/XMonad/Hooks/UrgencyHook.hs b/XMonad/Hooks/UrgencyHook.hs index c133c2fc..cc9b0e7b 100644 --- a/XMonad/Hooks/UrgencyHook.hs +++ b/XMonad/Hooks/UrgencyHook.hs @@ -116,10 +116,10 @@ import Foreign.C.Types (CLong) -- > main = xmonad $ withUrgencyHook NoUrgencyHook -- > $ def -- --- Now, your "XMonad.Hooks.DynamicLog" must be set up to display the urgent --- windows. If you're using the 'dzen' or 'dzenPP' functions from that module, --- then you should be good. Otherwise, you want to figure out how to set --- 'ppUrgent'. +-- Now, your "XMonad.Hooks.StatusBar.PP" must be set up to display the urgent +-- windows. If you're using the 'dzen' (from "XMonad.Hooks.DynamicLog") or +-- 'dzenPP' functions from that module, then you should be good. Otherwise, +-- you want to figure out how to set 'ppUrgent'. -- $keybinding -- diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs index ffa3d2c4..3921c6b1 100644 --- a/XMonad/Layout/IndependentScreens.hs +++ b/XMonad/Layout/IndependentScreens.hs @@ -38,7 +38,7 @@ import Graphics.X11.Xinerama import XMonad import XMonad.Prelude import qualified XMonad.StackSet as W -import XMonad.Hooks.DynamicLog +import XMonad.Hooks.StatusBar.PP -- $usage -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: diff --git a/XMonad/Layout/LayoutModifier.hs b/XMonad/Layout/LayoutModifier.hs index 29ddf102..9528258b 100644 --- a/XMonad/Layout/LayoutModifier.hs +++ b/XMonad/Layout/LayoutModifier.hs @@ -234,7 +234,7 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where -- should only override this if it is important that the -- presence of the layout modifier be displayed in text -- representations of the layout (for example, in the status bar - -- of a "XMonad.Hooks.DynamicLog" user). + -- of a "XMonad.Hooks.StatusBar" user). modifierDescription :: m a -> String modifierDescription = const "" diff --git a/XMonad/Util/Loggers.hs b/XMonad/Util/Loggers.hs index 84557e1c..65d172ca 100644 --- a/XMonad/Util/Loggers.hs +++ b/XMonad/Util/Loggers.hs @@ -10,8 +10,8 @@ -- Portability : unportable -- -- A collection of simple logger functions and formatting utilities --- which can be used in the 'XMonad.Hooks.DynamicLog.ppExtras' field of --- a pretty-printing status logger format. See "XMonad.Hooks.DynamicLog" +-- which can be used in the 'XMonad.Hooks.StatusBar.PP.ppExtras' field of +-- a pretty-printing status logger format. See "XMonad.Hooks.StatusBar.PP" -- for more information. ----------------------------------------------------------------------------- @@ -51,7 +51,7 @@ module XMonad.Util.Loggers ( import XMonad (liftIO, Window, gets) import XMonad.Core import qualified XMonad.StackSet as W -import XMonad.Hooks.DynamicLog +import XMonad.Hooks.StatusBar.PP import XMonad.Util.Font (Align (..)) import XMonad.Util.NamedWindows (getName) @@ -71,35 +71,34 @@ econst = const . return -- > import XMonad.Util.Loggers -- -- Then, add one or more loggers to the --- 'XMonad.Hooks.DynamicLog.ppExtras' field of your --- 'XMonad.Hooks.DynamicLoc.PP', possibly with extra formatting . +-- 'XMonad.Hooks.StatusBar.PP.ppExtras' field of your +-- "XMonad.Hooks.StatusBar.PP", possibly with extra formatting . -- For example: -- --- > -- display load averages and a pithy quote along with xmonad status. --- > , logHook = dynamicLogWithPP $ def { --- > ppExtras = [ padL loadAvg, logCmd "fortune -n 40 -s" ] --- > } +-- > myPP = def { +-- > ppExtras = [ padL loadAvg, logCmd "fortune -n 40 -s" ] +-- > } -- > -- gives something like " 3.27 3.52 3.26 Drive defensively. Buy a tank." -- -- See the formatting section below for another example using -- a @where@ block to define some formatted loggers for a top-level --- @myLogHook@. +-- @myPP@. -- -- Loggers are named either for their function, as in 'battery', -- 'aumixVolume', and 'maildirNew', or are prefixed with \"log\" when -- making use of other functions or by analogy with the pp* functions. --- For example, the logger version of 'XMonad.Hooks.DynamicLog.ppTitle' +-- For example, the logger version of 'XMonad.Hooks.StatusBar.PP.ppTitle' -- is 'logTitle', and 'logFileCount' loggerizes the result of file -- counting code. -- -- Formatting utility names are generally as short as possible and -- carry the suffix \"L\". For example, the logger version of --- 'XMonad.Hooks.DynamicLog.shorten' is 'shortenL'. +-- 'XMonad.Hooks.StatusBar.PP.shorten' is 'shortenL'. -- -- Of course, there is nothing really special about these so-called -- \"loggers\": they are just @X (Maybe String)@ actions. So you can -- use them anywhere you would use an @X (Maybe String)@, not just --- with DynamicLog. +-- with PP. -- -- Additional loggers welcome! @@ -286,12 +285,12 @@ withScreen f n = do -- $format -- Combine logger formatting functions to make your --- 'XMonad.Hooks.DynamicLog.ppExtras' more colorful and readable. +-- 'XMonad.Hooks.StatusBar.PP.ppExtras' more colorful and readable. -- (For convenience, you can use '<$>' instead of \'.\' or \'$\' in hard to read -- formatting lines. -- For example: -- --- > myLogHook = dynamicLogWithPP def { +-- > myPP = def { -- > -- skipped -- > , ppExtras = [lLoad, lTitle, logSp 3, wrapL "[" "]" $ date "%a %d %b"] -- > , ppOrder = \(ws:l:_:xs) -> [l,ws] ++ xs @@ -304,6 +303,9 @@ withScreen f n = do -- > lLoad = dzenColorL "#6A5ACD" "" . wrapL loadIcon " " . padL $ loadAvg -- > loadIcon = " ^i(/home/me/.dzen/icons/load.xbm)" -- +-- For more information on how to add the pretty-printer to your status bar, please +-- check "XMonad.Hooks.StatusBar". +-- -- Note: When applying 'shortenL' or 'fixedWidthL' to logger strings -- containing colors or other formatting commands, apply the formatting -- /after/ the length adjustment, or include \"invisible\" characters diff --git a/XMonad/Util/Loggers/NamedScratchpad.hs b/XMonad/Util/Loggers/NamedScratchpad.hs index 8c5627fa..3abef4c8 100644 --- a/XMonad/Util/Loggers/NamedScratchpad.hs +++ b/XMonad/Util/Loggers/NamedScratchpad.hs @@ -35,7 +35,7 @@ import qualified XMonad.StackSet as W (allWindows) -- This is a set of 'Logger's for 'NamedScratchpad's. -- It provides a 'startupHook' and 'handleEventHook' to keep track of -- 'NamedScratchpad's, and several possible 'Logger's for use in --- 'XMonad.Hooks.DynamicLog' 'ppExtras'. +-- 'XMonad.Hooks.StatusBar.PP.ppExtras'. -- -- You must add 'nspTrackStartup' to your 'startupHook' to initialize -- 'NamedScratchpad' tracking and to detect any currently running diff --git a/XMonad/Util/NamedScratchpad.hs b/XMonad/Util/NamedScratchpad.hs index bdeacac4..9aecbdcb 100644 --- a/XMonad/Util/NamedScratchpad.hs +++ b/XMonad/Util/NamedScratchpad.hs @@ -35,7 +35,7 @@ module XMonad.Util.NamedScratchpad ( import XMonad import XMonad.Actions.DynamicWorkspaces (addHiddenWorkspace) import XMonad.Actions.SpawnOn (spawnHere) -import XMonad.Hooks.DynamicLog (PP, ppSort) +import XMonad.Hooks.StatusBar.PP (PP, ppSort) import XMonad.Hooks.ManageHelpers (doRectFloat) import XMonad.Hooks.RefocusLast (withRecentsIn) import XMonad.Prelude (filterM, find, unless, when) @@ -92,7 +92,7 @@ import qualified XMonad.StackSet as W -- -- For some applications (like displaying your workspaces in a status bar) it is -- convenient to filter out the @NSP@ workspace when looking at all workspaces. --- For this, you can use functions 'XMonad.Hooks.DynamicLog.filterOutWsPP' and +-- For this, you can use functions 'XMonad.Hooks.StatusBar.PP.filterOutWsPP' and -- 'XMonad.Util.WorkspaceCompare.filterOutWs'. See the documentation of these -- functions for examples. -- @@ -247,6 +247,6 @@ namedScratchpadFilterOutWorkspacePP :: PP -> PP namedScratchpadFilterOutWorkspacePP pp = pp { ppSort = fmap (. namedScratchpadFilterOutWorkspace) (ppSort pp) } -{-# DEPRECATED namedScratchpadFilterOutWorkspacePP "Use XMonad.Hooks.DynamicLog.filterOutWsPP [scratchpadWorkspaceTag] instead" #-} +{-# DEPRECATED namedScratchpadFilterOutWorkspacePP "Use XMonad.Hooks.StatusBar.PP.filterOutWsPP [scratchpadWorkspaceTag] instead" #-} -- vim:ts=4:shiftwidth=4:softtabstop=4:expandtab:foldlevel=20: diff --git a/XMonad/Util/WorkspaceCompare.hs b/XMonad/Util/WorkspaceCompare.hs index 688d0247..1290d1da 100644 --- a/XMonad/Util/WorkspaceCompare.hs +++ b/XMonad/Util/WorkspaceCompare.hs @@ -66,7 +66,7 @@ getWsCompareByTag = return compare -- | A comparison function for Xinerama based on visibility, workspace -- and screen id. It produces the same ordering as --- 'XMonad.Hooks.DynamicLog.pprWindowSetXinerama'. +-- 'XMonad.Hooks.StatusBar.PP.pprWindowSetXinerama'. getXineramaWsCompare :: X WorkspaceCompare getXineramaWsCompare = getXineramaPhysicalWsCompare $ screenComparatorById compare @@ -102,7 +102,7 @@ getSortByTag :: X WorkspaceSort getSortByTag = mkWsSort getWsCompareByTag -- | Sort serveral workspaces for xinerama displays, in the same order --- produced by 'XMonad.Hooks.DynamicLog.pprWindowSetXinerama': first +-- produced by 'XMonad.Hooks.StatusBar.PP.pprWindowSetXinerama': first -- visible workspaces, sorted by screen, then hidden workspaces, -- sorted by tag. getSortByXineramaRule :: X WorkspaceSort diff --git a/scripts/xmonadpropread.hs b/scripts/xmonadpropread.hs index 5ee04f18..f6b62bf5 100755 --- a/scripts/xmonadpropread.hs +++ b/scripts/xmonadpropread.hs @@ -7,7 +7,7 @@ -- -- Reads from an X property on the root window and writes to standard output. -- --- May be used together with XMonad.Hooks.DynamicLog.xmonadPropLog and a +-- May be used together with XMonad.Hooks.StatusBar.xmonadPropLog and a -- status bar that doesn't support reading from properties itself, such as -- dzen. --