Replace <+> with <>

This commit is contained in:
John Lind 2022-05-01 10:53:14 +02:00
parent 3adb47235f
commit a7fd31d233
36 changed files with 91 additions and 91 deletions

View File

@ -47,7 +47,7 @@ import qualified XMonad.Util.ExtensibleState as ES
-- --
-- Then add the event hook handler: -- Then add the event hook handler:
-- --
-- > xmonad { handleEventHook = myHandleEventHooks <+> handleTimerEvent } -- > xmonad { handleEventHook = myHandleEventHooks <> handleTimerEvent }
-- --
-- You can then use flashText in your keybindings: -- You can then use flashText in your keybindings:
-- --

View File

@ -51,7 +51,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- > main = do -- > main = do
-- > xmonad def { -- > xmonad def {
-- > ... -- > ...
-- > manageHook = manageSpawn <+> manageHook def -- > manageHook = manageSpawn <> manageHook def
-- > ... -- > ...
-- > } -- > }
-- --

View File

@ -37,11 +37,11 @@ import qualified Data.Map as M
-- If you prefer, an azertyKeys function is provided which you can use as so: -- If you prefer, an azertyKeys function is provided which you can use as so:
-- --
-- > import qualified Data.Map as M -- > import qualified Data.Map as M
-- > main = xmonad someConfig { keys = \c -> azertyKeys c <+> keys someConfig c } -- > main = xmonad someConfig { keys = \c -> azertyKeys c <> keys someConfig c }
azertyConfig = def { keys = azertyKeys <+> keys def } azertyConfig = def { keys = azertyKeys <> keys def }
belgianConfig = def { keys = belgianKeys <+> keys def } belgianConfig = def { keys = belgianKeys <> keys def }
azertyKeys = azertyKeysTop [0x26,0xe9,0x22,0x27,0x28,0x2d,0xe8,0x5f,0xe7,0xe0] azertyKeys = azertyKeysTop [0x26,0xe9,0x22,0x27,0x28,0x2d,0xe8,0x5f,0xe7,0xe0]

View File

@ -38,7 +38,7 @@ import qualified Data.Map as M
-- > import qualified Data.Map as M -- > import qualified Data.Map as M
-- > main = xmonad someConfig { keys = \c -> bepoKeys c `M.union` keys someConfig c } -- > main = xmonad someConfig { keys = \c -> bepoKeys c `M.union` keys someConfig c }
bepoConfig = def { keys = bepoKeys <+> keys def } bepoConfig = def { keys = bepoKeys <> keys def }
bepoKeys conf@XConfig { modMask = modm } = M.fromList $ bepoKeys conf@XConfig { modMask = modm } = M.fromList $
((modm, xK_semicolon), sendMessage (IncMasterN (-1))) ((modm, xK_semicolon), sendMessage (IncMasterN (-1)))

View File

@ -106,7 +106,7 @@ import qualified Data.Map as M
-- > main = -- > main =
-- > xmonad $ desktopConfig { -- > xmonad $ desktopConfig {
-- > -- add manage hooks while still ignoring panels and using default manageHooks -- > -- add manage hooks while still ignoring panels and using default manageHooks
-- > manageHook = myManageHook <+> manageHook desktopConfig -- > manageHook = myManageHook <> manageHook desktopConfig
-- > -- >
-- > -- add a fullscreen tabbed layout that does not avoid covering -- > -- add a fullscreen tabbed layout that does not avoid covering
-- > -- up desktop panels before the desktop layouts -- > -- up desktop panels before the desktop layouts
@ -129,7 +129,7 @@ import qualified Data.Map as M
-- To add to the logHook while still sending workspace and window information -- To add to the logHook while still sending workspace and window information
-- to DE apps use something like: -- to DE apps use something like:
-- --
-- > , logHook = myLogHook <+> logHook desktopConfig -- > , logHook = myLogHook <> logHook desktopConfig
-- --
-- Or for more elaborate logHooks you can use @do@: -- Or for more elaborate logHooks you can use @do@:
-- --
@ -143,7 +143,7 @@ import qualified Data.Map as M
-- To customize xmonad's event handling while still having it respond -- To customize xmonad's event handling while still having it respond
-- to EWMH events from pagers, task bars: -- to EWMH events from pagers, task bars:
-- --
-- > , handleEventHook = myEventHooks <+> handleEventHook desktopConfig -- > , handleEventHook = myEventHooks <> handleEventHook desktopConfig
-- --
-- or 'mconcat' if you write a list event of event hooks -- or 'mconcat' if you write a list event of event hooks
-- --
@ -157,7 +157,7 @@ import qualified Data.Map as M
-- $startupHook -- $startupHook
-- To run the desktop startupHook, plus add further actions to be run each -- To run the desktop startupHook, plus add further actions to be run each
-- time xmonad starts or restarts, use '<+>' to combine actions as in the -- time xmonad starts or restarts, use '<>' to combine actions as in the
-- logHook example, or something like: -- logHook example, or something like:
-- --
-- > , startupHook = do -- > , startupHook = do
@ -169,9 +169,9 @@ import qualified Data.Map as M
desktopConfig :: XConfig (ModifiedLayout AvoidStruts desktopConfig :: XConfig (ModifiedLayout AvoidStruts
(Choose Tall (Choose (Mirror Tall) Full))) (Choose Tall (Choose (Mirror Tall) Full)))
desktopConfig = docks $ ewmh def desktopConfig = docks $ ewmh def
{ startupHook = setDefaultCursor xC_left_ptr <+> startupHook def { startupHook = setDefaultCursor xC_left_ptr <> startupHook def
, layoutHook = desktopLayoutModifiers $ layoutHook def , layoutHook = desktopLayoutModifiers $ layoutHook def
, keys = desktopKeys <+> keys def } , keys = desktopKeys <> keys def }
desktopKeys :: XConfig l -> M.Map (KeyMask, KeySym) (X ()) desktopKeys :: XConfig l -> M.Map (KeyMask, KeySym) (X ())
desktopKeys XConfig{modMask = modm} = M.fromList desktopKeys XConfig{modMask = modm} = M.fromList

View File

@ -217,13 +217,13 @@ dmwitConfig nScreens = docks $ def {
keys = keyBindings, keys = keyBindings,
layoutHook = magnifierOff $ avoidStruts (GridRatio 0.9) ||| noBorders Full, layoutHook = magnifierOff $ avoidStruts (GridRatio 0.9) ||| noBorders Full,
manageHook = (title =? "CGoban: Main Window" --> doF sinkFocus) manageHook = (title =? "CGoban: Main Window" --> doF sinkFocus)
<+> (className =? "Wine" <&&> (appName =? "hl2.exe" <||> appName =? "portal2.exe") --> ask >>= viewFullOn {-centerWineOn-} 1 "5") <> (className =? "Wine" <&&> (appName =? "hl2.exe" <||> appName =? "portal2.exe") --> ask >>= viewFullOn {-centerWineOn-} 1 "5")
<+> (className =? "VirtualBox" --> ask >>= viewFullOn 1 "5") <> (className =? "VirtualBox" --> ask >>= viewFullOn 1 "5")
<+> (isFullscreen --> doFullFloat) -- TF2 matches the "isFullscreen" criteria, so its manage hook should appear after (e.g., to the left of a <+> compared to) this one <> (isFullscreen --> doFullFloat) -- TF2 matches the "isFullscreen" criteria, so its manage hook should appear after (e.g., to the left of a <> compared to) this one
<+> (appName =? "huludesktop" --> doRectFloat fullscreen43on169) <> (appName =? "huludesktop" --> doRectFloat fullscreen43on169)
<+> fullscreenMPlayer <> fullscreenMPlayer
<+> floatAll ["Gimp", "Wine"] <> floatAll ["Gimp", "Wine"]
<+> manageSpawn, <> manageSpawn,
logHook = allPPs nScreens, logHook = allPPs nScreens,
startupHook = refresh startupHook = refresh
>> mapM_ (spawnOnce . xmobarCommand) [0 .. nScreens-1] >> mapM_ (spawnOnce . xmobarCommand) [0 .. nScreens-1]

View File

@ -28,10 +28,10 @@ main = do
-- simple overrides: -- simple overrides:
xmonad $ desktopConfig xmonad $ desktopConfig
{ modMask = mod4Mask -- Use the "Win" key for the mod key { modMask = mod4Mask -- Use the "Win" key for the mod key
, manageHook = myManageHook <+> manageHook desktopConfig , manageHook = myManageHook <> manageHook desktopConfig
, layoutHook = desktopLayoutModifiers myLayouts , layoutHook = desktopLayoutModifiers myLayouts
, logHook = (dynamicLogString def >>= xmonadPropLog) , logHook = (dynamicLogString def >>= xmonadPropLog)
<+> logHook desktopConfig <> logHook desktopConfig
} }
`additionalKeysP` -- Add some extra key bindings: `additionalKeysP` -- Add some extra key bindings:
@ -72,7 +72,7 @@ myManageHook = composeOne
-- Handle floating windows: -- Handle floating windows:
[ transience -- move transient windows to their parent [ transience -- move transient windows to their parent
, isDialog -?> doCenterFloat , isDialog -?> doCenterFloat
] <+> composeAll ] <> composeAll
[ className =? "Pidgin" --> doFloat [ className =? "Pidgin" --> doFloat
, className =? "XCalc" --> doFloat , className =? "XCalc" --> doFloat
, className =? "mpv" --> doFloat , className =? "mpv" --> doFloat

View File

@ -43,7 +43,7 @@ import System.Environment (getEnvironment)
gnomeConfig = desktopConfig gnomeConfig = desktopConfig
{ terminal = "gnome-terminal" { terminal = "gnome-terminal"
, keys = gnomeKeys <+> keys desktopConfig , keys = gnomeKeys <> keys desktopConfig
, startupHook = gnomeRegister >> startupHook desktopConfig } , startupHook = gnomeRegister >> startupHook desktopConfig }
gnomeKeys XConfig{modMask = modm} = M.fromList gnomeKeys XConfig{modMask = modm} = M.fromList

View File

@ -42,11 +42,11 @@ import qualified Data.Map as M
kdeConfig = desktopConfig kdeConfig = desktopConfig
{ terminal = "konsole" { terminal = "konsole"
, keys = kdeKeys <+> keys desktopConfig } , keys = kdeKeys <> keys desktopConfig }
kde4Config = desktopConfig kde4Config = desktopConfig
{ terminal = "konsole" { terminal = "konsole"
, keys = kde4Keys <+> keys desktopConfig } , keys = kde4Keys <> keys desktopConfig }
kdeKeys XConfig{modMask = modm} = M.fromList kdeKeys XConfig{modMask = modm} = M.fromList
[ ((modm, xK_p), spawn "dcop kdesktop default popupExecuteCommand") [ ((modm, xK_p), spawn "dcop kdesktop default popupExecuteCommand")

View File

@ -38,7 +38,7 @@ import qualified Data.Map as M
lxqtConfig = desktopConfig lxqtConfig = desktopConfig
{ terminal = "qterminal" { terminal = "qterminal"
, keys = lxqtKeys <+> keys desktopConfig } , keys = lxqtKeys <> keys desktopConfig }
lxqtKeys XConfig{modMask = modm} = M.fromList lxqtKeys XConfig{modMask = modm} = M.fromList
[ ((modm, xK_p), spawn "lxqt-runner") [ ((modm, xK_p), spawn "lxqt-runner")

View File

@ -50,7 +50,7 @@ import System.Environment (getEnvironment)
mateConfig = desktopConfig mateConfig = desktopConfig
{ terminal = "mate-terminal" { terminal = "mate-terminal"
, keys = mateKeys <+> keys desktopConfig , keys = mateKeys <> keys desktopConfig
, startupHook = mateRegister >> startupHook desktopConfig } , startupHook = mateRegister >> startupHook desktopConfig }
mateKeys XConfig{modMask = modm} = M.fromList mateKeys XConfig{modMask = modm} = M.fromList

View File

@ -280,7 +280,7 @@ instance SummableClass (Summable x y) y where
-- --
-- Note that operator precedence mandates the parentheses here. -- Note that operator precedence mandates the parentheses here.
manageHook :: Summable ManageHook ManageHook (XConfig l) manageHook :: Summable ManageHook ManageHook (XConfig l)
manageHook = Summable X.manageHook (\x c -> c { X.manageHook = x }) (<+>) manageHook = Summable X.manageHook (\x c -> c { X.manageHook = x }) (<>)
-- | Custom X event handler. Return @All True@ if the default handler should -- | Custom X event handler. Return @All True@ if the default handler should
-- also be run afterwards. Default does nothing. To add an event handler: -- also be run afterwards. Default does nothing. To add an event handler:
@ -289,7 +289,7 @@ manageHook = Summable X.manageHook (\x c -> c { X.manageHook = x }) (<+>)
-- > ... -- > ...
-- > handleEventHook =+ serverModeEventHook -- > handleEventHook =+ serverModeEventHook
handleEventHook :: Summable (Event -> X All) (Event -> X All) (XConfig l) handleEventHook :: Summable (Event -> X All) (Event -> X All) (XConfig l)
handleEventHook = Summable X.handleEventHook (\x c -> c { X.handleEventHook = x }) (<+>) handleEventHook = Summable X.handleEventHook (\x c -> c { X.handleEventHook = x }) (<>)
-- | List of workspaces' names. Default: @map show [1 .. 9 :: Int]@. Adding -- | List of workspaces' names. Default: @map show [1 .. 9 :: Int]@. Adding
-- appends to the end: -- appends to the end:

View File

@ -39,7 +39,7 @@ main = do
{ terminal = "xterm" { terminal = "xterm"
, workspaces = myWorkspaces , workspaces = myWorkspaces
, layoutHook = myLayoutHook , layoutHook = myLayoutHook
, manageHook = myManageHook <+> manageSpawn , manageHook = myManageHook <> manageSpawn
, startupHook = myStartupHook , startupHook = myStartupHook
, logHook = myLogHook myStatusBarPipe , logHook = myLogHook myStatusBarPipe
, focusFollowsMouse = False , focusFollowsMouse = False

View File

@ -41,8 +41,8 @@ sjanssenConfig =
| (x, w) <- [ ("Firefox", "web") | (x, w) <- [ ("Firefox", "web")
, ("Ktorrent", "7") , ("Ktorrent", "7")
, ("Amarokapp", "7")]] , ("Amarokapp", "7")]]
<+> manageHook def <+> manageSpawn <> manageHook def <> manageSpawn
<+> (isFullscreen --> doFullFloat) <> (isFullscreen --> doFullFloat)
, startupHook = mapM_ spawnOnce spawns , startupHook = mapM_ spawnOnce spawns
} }
where where

View File

@ -38,7 +38,7 @@ import qualified Data.Map as M
xfceConfig = desktopConfig xfceConfig = desktopConfig
{ terminal = "xfce4-terminal" { terminal = "xfce4-terminal"
, keys = xfceKeys <+> keys desktopConfig } , keys = xfceKeys <> keys desktopConfig }
xfceKeys XConfig{modMask = modm} = M.fromList xfceKeys XConfig{modMask = modm} = M.fromList
[ ((modm, xK_p), spawn "xfrun4") [ ((modm, xK_p), spawn "xfrun4")

View File

@ -608,7 +608,7 @@ This is another example of 'XMonad.Config.manageHook', taken from
> , resource =? "win" --> doF (W.shift "doc") -- xpdf > , resource =? "win" --> doF (W.shift "doc") -- xpdf
> , resource =? "firefox-bin" --> doF (W.shift "web") > , resource =? "firefox-bin" --> doF (W.shift "web")
> ] > ]
> newManageHook = myManageHook <+> manageHook def > newManageHook = myManageHook <> manageHook def
Again we use 'XMonad.ManageHook.composeAll' to compose a list of Again we use 'XMonad.ManageHook.composeAll' to compose a list of
@ -617,7 +617,7 @@ RealPlayer on the float layer, the second one will put the xpdf
windows in the workspace named \"doc\", with 'XMonad.ManageHook.doF' windows in the workspace named \"doc\", with 'XMonad.ManageHook.doF'
and 'XMonad.StackSet.shift' functions, and the third one will put all and 'XMonad.StackSet.shift' functions, and the third one will put all
firefox windows on the workspace called "web". Then we use the firefox windows on the workspace called "web". Then we use the
'XMonad.ManageHook.<+>' combinator to compose @myManageHook@ with the '<>' combinator to compose @myManageHook@ with the
default 'XMonad.Config.manageHook' to form @newManageHook@. default 'XMonad.Config.manageHook' to form @newManageHook@.
Each 'XMonad.Config.ManageHook' has the form: Each 'XMonad.Config.ManageHook' has the form:
@ -667,10 +667,10 @@ Then we create our own 'XMonad.Config.manageHook':
> myManageHook = resource =? "realplay.bin" --> doFloat > myManageHook = resource =? "realplay.bin" --> doFloat
We can now use the 'XMonad.ManageHook.<+>' combinator to add our We can now use the '<>' combinator to add our
'XMonad.Config.manageHook' to the default one: 'XMonad.Config.manageHook' to the default one:
> newManageHook = myManageHook <+> manageHook def > newManageHook = myManageHook <> manageHook def
(Of course, if we wanted to completely replace the default (Of course, if we wanted to completely replace the default
'XMonad.Config.manageHook', this step would not be necessary.) Now, 'XMonad.Config.manageHook', this step would not be necessary.) Now,

View File

@ -41,7 +41,7 @@ import System.IO (hPutStrLn
-- --
-- If you already have a handleEventHook then you should append it: -- If you already have a handleEventHook then you should append it:
-- --
-- > , handleEventHook = ... <+> debugKeyEvents -- > , handleEventHook = ... <> debugKeyEvents
-- --
-- Logged key events look like: -- Logged key events look like:
-- --

View File

@ -38,7 +38,7 @@ import qualified XMonad.Util.ExtensibleState as XS
-- --
-- To use this module, add 'dynamicMasterHook' to your 'manageHook': -- To use this module, add 'dynamicMasterHook' to your 'manageHook':
-- --
-- > xmonad { manageHook = myManageHook <+> dynamicMasterHook } -- > xmonad { manageHook = myManageHook <> dynamicMasterHook }
-- --
-- You can then use the supplied functions in your keybindings: -- You can then use the supplied functions in your keybindings:
-- --
@ -70,7 +70,7 @@ dynamicMasterHook = ask >>= \w -> liftX $ do
-- | Appends the given 'ManageHook' to the permanent dynamic 'ManageHook'. -- | Appends the given 'ManageHook' to the permanent dynamic 'ManageHook'.
addDynamicHook :: ManageHook -> X () addDynamicHook :: ManageHook -> X ()
addDynamicHook m = updateDynamicHook (<+> m) addDynamicHook m = updateDynamicHook (<> m)
-- | Modifies the permanent 'ManageHook' with an arbitrary function. -- | Modifies the permanent 'ManageHook' with an arbitrary function.
updateDynamicHook :: (ManageHook -> ManageHook) -> X () updateDynamicHook :: (ManageHook -> ManageHook) -> X ()

View File

@ -65,7 +65,7 @@ import XMonad.Prelude
-- --
-- > main = xmonad $ def -- > main = xmonad $ def
-- > { ... -- > { ...
-- > , handleEventHook = dynamicPropertyChange "WM_NAME" myDynamicManageHook <+> handleEventHook baseConfig -- > , handleEventHook = dynamicPropertyChange "WM_NAME" myDynamicManageHook <> handleEventHook baseConfig
-- > , ... -- > , ...
-- > } -- > }
-- --
@ -88,7 +88,7 @@ import XMonad.Prelude
-- --
-- > main = xmonad $ def -- > main = xmonad $ def
-- > { ... -- > { ...
-- > , handleEventHook = dynamicPropertyChange "WM_NAME" myDynHook <+> handleEventHook baseConfig -- > , handleEventHook = dynamicPropertyChange "WM_NAME" myDynHook <> handleEventHook baseConfig
-- > , ... -- > , ...
-- > } -- > }
-- > -- >

View File

@ -85,9 +85,9 @@ import qualified XMonad.Util.ExtensibleState as XS
-- | Add EWMH support for workspaces (virtual desktops) to the given -- | Add EWMH support for workspaces (virtual desktops) to the given
-- 'XConfig'. See above for an example. -- 'XConfig'. See above for an example.
ewmh :: XConfig a -> XConfig a ewmh :: XConfig a -> XConfig a
ewmh c = c { startupHook = ewmhDesktopsStartup <+> startupHook c ewmh c = c { startupHook = ewmhDesktopsStartup <> startupHook c
, handleEventHook = ewmhDesktopsEventHook <+> handleEventHook c , handleEventHook = ewmhDesktopsEventHook <> handleEventHook c
, logHook = ewmhDesktopsLogHook <+> logHook c } , logHook = ewmhDesktopsLogHook <> logHook c }
-- $customization -- $customization
@ -376,8 +376,8 @@ ewmhDesktopsEventHook' _ _ = mempty
-- | Add EWMH fullscreen functionality to the given config. -- | Add EWMH fullscreen functionality to the given config.
ewmhFullscreen :: XConfig a -> XConfig a ewmhFullscreen :: XConfig a -> XConfig a
ewmhFullscreen c = c { startupHook = startupHook c <+> fullscreenStartup ewmhFullscreen c = c { startupHook = startupHook c <> fullscreenStartup
, handleEventHook = handleEventHook c <+> fullscreenEventHook } , handleEventHook = handleEventHook c <> fullscreenEventHook }
-- | Advertises EWMH fullscreen support to the X server. -- | Advertises EWMH fullscreen support to the X server.
{-# DEPRECATED fullscreenStartup "Use ewmhFullscreen instead." #-} {-# DEPRECATED fullscreenStartup "Use ewmhFullscreen instead." #-}

View File

@ -53,7 +53,7 @@ hookName = "__float"
-- --
-- and adding 'floatNextHook' to your 'ManageHook': -- and adding 'floatNextHook' to your 'ManageHook':
-- --
-- > myManageHook = floatNextHook <+> manageHook def -- > myManageHook = floatNextHook <> manageHook def
-- --
-- The 'floatNext' and 'toggleFloatNext' functions can be used in key -- The 'floatNext' and 'toggleFloatNext' functions can be used in key
-- bindings to float the next spawned window: -- bindings to float the next spawned window:

View File

@ -160,7 +160,7 @@ import XMonad.Hooks.ManageHelpers (currentWs)
-- > --> keepFocus -- > --> keepFocus
-- > -- Default behavior for activated windows: switch -- > -- Default behavior for activated windows: switch
-- > -- workspace and focus. -- > -- workspace and focus.
-- > , return True --> switchWorkspace <+> switchFocus -- > , return True --> switchWorkspace <> switchFocus
-- > ] -- > ]
-- > -- >
-- > newFocusHook :: FocusHook -- > newFocusHook :: FocusHook
@ -202,7 +202,7 @@ import XMonad.Hooks.ManageHelpers (currentWs)
-- > acFh = manageFocus activateFocusHook -- > acFh = manageFocus activateFocusHook
-- > xcf = setEwmhActivateHook acFh -- > xcf = setEwmhActivateHook acFh
-- > . ewmh $ def -- > . ewmh $ def
-- > { manageHook = newFh <+> manageHook def -- > { manageHook = newFh <> manageHook def
-- > , modMask = mod4Mask -- > , modMask = mod4Mask
-- > } -- > }
-- > `additionalKeys` [((mod4Mask, xK_v), toggleLock)] -- > `additionalKeys` [((mod4Mask, xK_v), toggleLock)]
@ -227,7 +227,7 @@ import XMonad.Hooks.ManageHelpers (currentWs)
-- > ] -- > ]
-- > xcf = setEwmhActivateHook (fh True) -- > xcf = setEwmhActivateHook (fh True)
-- > . ewmh $ def -- > . ewmh $ def
-- > { manageHook = fh False <+> manageHook def -- > { manageHook = fh False <> manageHook def
-- > , modMask = mod4Mask -- > , modMask = mod4Mask
-- > } -- > }
-- > `additionalKeys` [((mod4Mask, xK_v), toggleLock)] -- > `additionalKeys` [((mod4Mask, xK_v), toggleLock)]
@ -250,11 +250,11 @@ import XMonad.Hooks.ManageHelpers (currentWs)
-- This can be worked around by splitting 'FocusHook' into several different -- This can be worked around by splitting 'FocusHook' into several different
-- values and evaluating each one separately, like: -- values and evaluating each one separately, like:
-- --
-- > (FH2 -- manageFocus --> MH2) <+> (FH1 -- manageFocus --> MH1) <+> .. -- > (FH2 -- manageFocus --> MH2) <> (FH1 -- manageFocus --> MH1) <> ..
-- --
-- E.g. -- E.g.
-- --
-- > manageFocus FH2 <+> manageFocus FH1 <+> .. -- > manageFocus FH2 <> manageFocus FH1 <> ..
-- --
-- now @FH2@ will see window shift made by @FH1@. -- now @FH2@ will see window shift made by @FH1@.
-- --
@ -275,9 +275,9 @@ import XMonad.Hooks.ManageHelpers (currentWs)
-- > [ pure activated -?> (newOnCur --> keepFocus) -- > [ pure activated -?> (newOnCur --> keepFocus)
-- > , pure True -?> newFocusHook -- > , pure True -?> newFocusHook
-- > ] -- > ]
-- > xcf = setEwmhActivateHook (fh True <+> activateOnCurrentWs) -- > xcf = setEwmhActivateHook (fh True <> activateOnCurrentWs)
-- > . ewmh $ def -- > . ewmh $ def
-- > { manageHook = fh False <+> manageHook def -- > { manageHook = fh False <> manageHook def
-- > , modMask = mod4Mask -- > , modMask = mod4Mask
-- > } -- > }
-- > `additionalKeys` [((mod4Mask, xK_v), toggleLock)] -- > `additionalKeys` [((mod4Mask, xK_v), toggleLock)]
@ -444,15 +444,15 @@ unlessFocusLock m = do
-- 'switchWorkspace' overwrite each other (the letftmost will determine what -- 'switchWorkspace' overwrite each other (the letftmost will determine what
-- happened): -- happened):
-- --
-- prop> keepFocus <+> switchFocus = keepFocus -- prop> keepFocus <> switchFocus = keepFocus
-- prop> switchFocus <+> keepFocus = switchFocus -- prop> switchFocus <> keepFocus = switchFocus
-- prop> keepWorkspace <+> switchWorkspace = keepWorkspace -- prop> keepWorkspace <> switchWorkspace = keepWorkspace
-- prop> switchWorkspace <+> keepWorkspace = switchWorkspace -- prop> switchWorkspace <> keepWorkspace = switchWorkspace
-- --
-- and operations from different pairs are commutative: -- and operations from different pairs are commutative:
-- --
-- prop> keepFocus <+> switchWorkspace = switchWorkspace <+> keepFocus -- prop> keepFocus <> switchWorkspace = switchWorkspace <> keepFocus
-- prop> switchFocus <+> switchWorkspace = switchWorkspace <+> switchFocus -- prop> switchFocus <> switchWorkspace = switchWorkspace <> switchFocus
-- --
-- etc. -- etc.
@ -540,7 +540,7 @@ when' b mx
-- | Default EWMH window activation behavior: switch to workspace with -- | Default EWMH window activation behavior: switch to workspace with
-- activated window and switch focus to it. Not to be used in a 'manageHook'. -- activated window and switch focus to it. Not to be used in a 'manageHook'.
activateSwitchWs :: ManageHook activateSwitchWs :: ManageHook
activateSwitchWs = manageFocus (switchWorkspace <+> switchFocus) activateSwitchWs = manageFocus (switchWorkspace <> switchFocus)
-- | Move activated window to current workspace. Not to be used in a 'manageHook'. -- | Move activated window to current workspace. Not to be used in a 'manageHook'.
activateOnCurrent' :: ManageHook activateOnCurrent' :: ManageHook
@ -551,9 +551,9 @@ activateOnCurrent' = currentWs >>= unlessFocusLock . doShift
-- activated window is /already/ on current workspace, focus won't be -- activated window is /already/ on current workspace, focus won't be
-- switched. Not to be used in a 'manageHook'. -- switched. Not to be used in a 'manageHook'.
activateOnCurrentWs :: ManageHook activateOnCurrentWs :: ManageHook
activateOnCurrentWs = manageFocus (newOnCur --> switchFocus) <+> activateOnCurrent' activateOnCurrentWs = manageFocus (newOnCur --> switchFocus) <> activateOnCurrent'
-- | Move activated window to current workspace, but keep focus unchanged. -- | Move activated window to current workspace, but keep focus unchanged.
-- Not to be used in a 'manageHook'. -- Not to be used in a 'manageHook'.
activateOnCurrentKeepFocus :: ManageHook activateOnCurrentKeepFocus :: ManageHook
activateOnCurrentKeepFocus = manageFocus (newOnCur --> keepFocus) <+> activateOnCurrent' activateOnCurrentKeepFocus = manageFocus (newOnCur --> keepFocus) <> activateOnCurrent'

View File

@ -29,7 +29,7 @@ import qualified XMonad.StackSet as W
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
-- --
-- > import XMonad.Hooks.InsertPosition -- > import XMonad.Hooks.InsertPosition
-- > xmonad def { manageHook = insertPosition Master Newer <+> myManageHook } -- > xmonad def { manageHook = insertPosition Master Newer <> myManageHook }
-- --
-- You should you put the manageHooks that use 'doShift' to take effect -- You should you put the manageHooks that use 'doShift' to take effect
-- /before/ 'insertPosition', so that the window order will be consistent. -- /before/ 'insertPosition', so that the window order will be consistent.

View File

@ -42,16 +42,16 @@ instance ExtensionClass ManageStackDebug where
-- | A combinator to add full 'ManageHook' debugging in a single operation. -- | A combinator to add full 'ManageHook' debugging in a single operation.
debugManageHook :: XConfig l -> XConfig l debugManageHook :: XConfig l -> XConfig l
debugManageHook cf = cf {logHook = manageDebugLogHook <+> logHook cf debugManageHook cf = cf {logHook = manageDebugLogHook <> logHook cf
,manageHook = manageDebug <+> manageHook cf ,manageHook = manageDebug <> manageHook cf
} }
-- | A combinator to add triggerable 'ManageHook' debugging in a single operation. -- | A combinator to add triggerable 'ManageHook' debugging in a single operation.
-- Specify a key sequence as a string in 'XMonad.Util.EZConfig' syntax; press -- Specify a key sequence as a string in 'XMonad.Util.EZConfig' syntax; press
-- this key before opening the window to get just that logged. -- this key before opening the window to get just that logged.
debugManageHookOn :: String -> XConfig l -> XConfig l debugManageHookOn :: String -> XConfig l -> XConfig l
debugManageHookOn key cf = cf {logHook = manageDebugLogHook <+> logHook cf debugManageHookOn key cf = cf {logHook = manageDebugLogHook <> logHook cf
,manageHook = maybeManageDebug <+> manageHook cf ,manageHook = maybeManageDebug <> manageHook cf
} }
`additionalKeysP` `additionalKeysP`
[(key,debugNextManagedWindow)] [(key,debugNextManagedWindow)]

View File

@ -88,9 +88,9 @@ import qualified XMonad.StackSet as W
-- | Add docks functionality to the given config. See above for an example. -- | Add docks functionality to the given config. See above for an example.
docks :: XConfig a -> XConfig a docks :: XConfig a -> XConfig a
docks c = c { startupHook = docksStartupHook <+> startupHook c docks c = c { startupHook = docksStartupHook <> startupHook c
, handleEventHook = docksEventHook <+> handleEventHook c , handleEventHook = docksEventHook <> handleEventHook c
, manageHook = manageDocks <+> manageHook c } , manageHook = manageDocks <> manageHook c }
type WindowStruts = M.Map Window [Strut] type WindowStruts = M.Map Window [Strut]
@ -137,7 +137,7 @@ updateStrut w cache = do
-- | Detects if the given window is of type DOCK and if so, reveals -- | Detects if the given window is of type DOCK and if so, reveals
-- it, but does not manage it. -- it, but does not manage it.
manageDocks :: ManageHook manageDocks :: ManageHook
manageDocks = checkDock --> (doIgnore <+> doRequestDockEvents) manageDocks = checkDock --> (doIgnore <> doRequestDockEvents)
where where
doRequestDockEvents = ask >>= liftX . requestDockEvents >> mempty doRequestDockEvents = ask >>= liftX . requestDockEvents >> mempty

View File

@ -57,10 +57,10 @@ import Control.Monad.Trans (lift)
-- and adding 'placeHook' to your 'manageHook', for example: -- and adding 'placeHook' to your 'manageHook', for example:
-- --
-- > main = xmonad $ def { manageHook = placeHook simpleSmart -- > main = xmonad $ def { manageHook = placeHook simpleSmart
-- > <+> manageHook def } -- > <> manageHook def }
-- --
-- Note that 'placeHook' should be applied after most other hooks, especially hooks -- Note that 'placeHook' should be applied after most other hooks, especially hooks
-- such as 'doFloat' and 'doShift'. Since hooks combined with '<+>' are applied from -- such as 'doFloat' and 'doShift'. Since hooks combined with '<>' are applied from
-- right to left, this means that 'placeHook' should be the /first/ hook in your chain. -- right to left, this means that 'placeHook' should be the /first/ hook in your chain.
-- --
-- You can also define a key to manually trigger repositioning with 'placeFocused' by -- You can also define a key to manually trigger repositioning with 'placeFocused' by

View File

@ -56,7 +56,7 @@ import qualified Data.Set as S
-- otherwise use 'Just def' or similar to inform the module about the -- otherwise use 'Just def' or similar to inform the module about the
-- decoration theme used. -- decoration theme used.
-- --
-- > myManageHook = positionStoreManageHook Nothing <+> manageHook def -- > myManageHook = positionStoreManageHook Nothing <> manageHook def
-- > myHandleEventHook = positionStoreEventHook -- > myHandleEventHook = positionStoreEventHook
-- > -- >
-- > main = xmonad def { manageHook = myManageHook -- > main = xmonad def { manageHook = myManageHook

View File

@ -79,10 +79,10 @@ import qualified Data.Map.Strict as M
-- > -- >
-- > main :: IO () -- > main :: IO ()
-- > main = xmonad def -- > main = xmonad def
-- > { handleEventHook = refocusLastWhen myPred <+> handleEventHook def -- > { handleEventHook = refocusLastWhen myPred <> handleEventHook def
-- > , logHook = refocusLastLogHook <+> logHook def -- > , logHook = refocusLastLogHook <> logHook def
-- > -- , layoutHook = refocusLastLayoutHook $ layoutHook def -- > -- , layoutHook = refocusLastLayoutHook $ layoutHook def
-- > , keys = refocusLastKeys <+> keys def -- > , keys = refocusLastKeys <> keys def
-- > } where -- > } where
-- > myPred = refocusingIsActive <||> isFloat -- > myPred = refocusingIsActive <||> isFloat
-- > refocusLastKeys cnf -- > refocusLastKeys cnf

View File

@ -84,12 +84,12 @@ modify' n f = XS.modify (HookState . setter . hooks)
-- and adding 'toggleHook name hook' to your 'ManageHook' where @name@ is the -- and adding 'toggleHook name hook' to your 'ManageHook' where @name@ is the
-- name of the hook and @hook@ is the hook to execute based on the state. -- name of the hook and @hook@ is the hook to execute based on the state.
-- --
-- > myManageHook = toggleHook "float" doFloat <+> manageHook def -- > myManageHook = toggleHook "float" doFloat <> manageHook def
-- --
-- Additionally, toggleHook' is provided to toggle between two hooks (rather -- Additionally, toggleHook' is provided to toggle between two hooks (rather
-- than on/off). -- than on/off).
-- --
-- > myManageHook = toggleHook' "oldfocus" (const id) W.focusWindow <+> manageHook def -- > myManageHook = toggleHook' "oldfocus" (const id) W.focusWindow <> manageHook def
-- --
-- The 'hookNext' and 'toggleHookNext' functions can be used in key -- The 'hookNext' and 'toggleHookNext' functions can be used in key
-- bindings to set whether the hook is applied or not. -- bindings to set whether the hook is applied or not.

View File

@ -33,7 +33,7 @@ import Control.Monad.Except (lift, runExceptT, throwError)
-- --
-- > import XMonad.Hooks.WorkspaceByPos -- > import XMonad.Hooks.WorkspaceByPos
-- > -- >
-- > myManageHook = workspaceByPos <+> manageHook def -- > myManageHook = workspaceByPos <> manageHook def
-- > -- >
-- > main = xmonad def { manageHook = myManageHook } -- > main = xmonad def { manageHook = myManageHook }

View File

@ -78,9 +78,9 @@ fullscreenSupport :: LayoutClass l Window =>
XConfig l -> XConfig (ModifiedLayout FullscreenFull l) XConfig l -> XConfig (ModifiedLayout FullscreenFull l)
fullscreenSupport c = c { fullscreenSupport c = c {
layoutHook = fullscreenFull $ layoutHook c, layoutHook = fullscreenFull $ layoutHook c,
handleEventHook = handleEventHook c <+> fullscreenEventHook, handleEventHook = handleEventHook c <> fullscreenEventHook,
manageHook = manageHook c <+> fullscreenManageHook, manageHook = manageHook c <> fullscreenManageHook,
startupHook = startupHook c <+> fullscreenStartup startupHook = startupHook c <> fullscreenStartup
} }
-- | fullscreenSupport with smartBorders support so the border doesn't -- | fullscreenSupport with smartBorders support so the border doesn't

View File

@ -73,7 +73,7 @@ import qualified Data.Set as Set
-- To make XMonad reflect changes in window hints immediately, add -- To make XMonad reflect changes in window hints immediately, add
-- 'hintsEventHook' to your 'handleEventHook'. -- 'hintsEventHook' to your 'handleEventHook'.
-- --
-- > myHandleEventHook = hintsEventHook <+> ... -- > myHandleEventHook = hintsEventHook <> ...
-- > -- >
-- > main = xmonad def { handleEventHook = myHandleEventHook -- > main = xmonad def { handleEventHook = myHandleEventHook
-- > , ... } -- > , ... }

View File

@ -73,7 +73,7 @@ import XMonad.Hooks.FadeInactive (setOpacity)
-- --
-- Add ManageHook to de-manage monitor windows and apply opacity settings. -- Add ManageHook to de-manage monitor windows and apply opacity settings.
-- --
-- > manageHook = myManageHook <+> manageMonitor clock -- > manageHook = myManageHook <> manageMonitor clock
-- --
-- Apply layout modifier. -- Apply layout modifier.
-- --

View File

@ -73,7 +73,7 @@ import qualified XMonad.StackSet as W
-- --
-- Add the hooks to your managehook (see "XMonad.Doc.Extending#Editing_the_manage_hook"), eg.: -- Add the hooks to your managehook (see "XMonad.Doc.Extending#Editing_the_manage_hook"), eg.:
-- --
-- > manageHook = myManageHook <+> xScratchpadsManageHook scratchpads -- > manageHook = myManageHook <> xScratchpadsManageHook scratchpads
-- --
-- And finally add some keybindings (see "XMonad.Doc.Extending#Editing_key_bindings"): -- And finally add some keybindings (see "XMonad.Doc.Extending#Editing_key_bindings"):
-- --

View File

@ -73,7 +73,7 @@ import System.Posix.Env (putEnv)
-- Usage: -- Usage:
-- add to handleEventHook as follows: -- add to handleEventHook as follows:
-- --
-- > handleEventHook = handleEventHook def <+> Hacks.windowedFullscreenFixEventHook -- > handleEventHook = handleEventHook def <> Hacks.windowedFullscreenFixEventHook
-- --
-- | Fixes fullscreen behaviour of chromium based apps by quickly applying and undoing a resize. -- | Fixes fullscreen behaviour of chromium based apps by quickly applying and undoing a resize.

View File

@ -59,7 +59,7 @@ instance ExtensionClass NSPTrack where
-- | 'startupHook' to initialize scratchpad activation tracking -- | 'startupHook' to initialize scratchpad activation tracking
-- --
-- > , startupHook = ... <+> nspTrackStartup scratchpads -- > , startupHook = ... <> nspTrackStartup scratchpads
-- --
-- If you kickstart the 'logHook', do it /after/ 'nspTrackStartup'! -- If you kickstart the 'logHook', do it /after/ 'nspTrackStartup'!
nspTrackStartup :: [NamedScratchpad] -> X () nspTrackStartup :: [NamedScratchpad] -> X ()
@ -83,7 +83,7 @@ scratchpadWindow ns = foldM sp' Nothing (zip [0..] ns)
-- | 'handleEventHook' to track scratchpad activation/deactivation -- | 'handleEventHook' to track scratchpad activation/deactivation
-- --
-- > , handleEventHook = ... <+> nspTrackHook scratchpads -- > , handleEventHook = ... <> nspTrackHook scratchpads
nspTrackHook :: [NamedScratchpad] -> Event -> X All nspTrackHook :: [NamedScratchpad] -> Event -> X All
nspTrackHook _ DestroyWindowEvent{ev_window = w} = do nspTrackHook _ DestroyWindowEvent{ev_window = w} = do
XS.modify $ \(NSPTrack ws) -> NSPTrack $ map (\sw -> if sw == Just w then Nothing else sw) ws XS.modify $ \(NSPTrack ws) -> NSPTrack $ map (\sw -> if sw == Just w then Nothing else sw) ws