diff --git a/CHANGES.md b/CHANGES.md index d6d6c193..74d94e0f 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -113,6 +113,11 @@ - Removed the `Wrap` and `NextLayoutNoWrap` data constructors. + - `XMonad.Actions.CycleWS` + + - Deprecated `EmptyWS`, `HiddenWS`, `NonEmptyWS`, `HiddenNonEmptyWS`, + `HiddenEmptyWS`, `AnyWS` and `WSTagGroup` + ### New Modules * `XMonad.Hooks.StatusBar.PP` @@ -630,6 +635,14 @@ - Added `copiesPP` to make a `PP` aware of copies of the focused window. + - `XMonad.Actions.CycleWS` + + - Added `:&:`, `:|:` and `Not` data constructors to `WSType` to logically + combine predicates. + + - Added `hiddenWS`, `emptyWS` and `anyWS` to replace deprecated + constructors. + ## 0.16 ### Breaking Changes diff --git a/XMonad/Actions/CycleWS.hs b/XMonad/Actions/CycleWS.hs index 863209fc..8eb4dfce 100644 --- a/XMonad/Actions/CycleWS.hs +++ b/XMonad/Actions/CycleWS.hs @@ -18,13 +18,13 @@ -- -- Note that this module now subsumes the functionality of the former -- @XMonad.Actions.RotView@. Former users of @rotView@ can simply replace --- @rotView True@ with @moveTo Next NonEmptyWS@, and so on. +-- @rotView True@ with @moveTo Next (Not emptyWS)@, and so on. -- -- If you want to exactly replicate the action of @rotView@ (cycling -- through workspace in order lexicographically by tag, instead of in -- the order specified in the config), it can be implemented as: -- --- > rotView b = do t <- findWorkspace getSortByTag (bToDir b) NonEmptyWS 1 +-- > rotView b = do t <- findWorkspace getSortByTag (bToDir b) (Not emptyWS) 1 -- > windows . greedyView $ t -- > where bToDir True = Next -- > bToDir False = Prev @@ -63,6 +63,10 @@ module XMonad.Actions.CycleWS ( , Direction1D(..) , WSType(..) + , emptyWS + , hiddenWS + , anyWS + , wsTagGroup , shiftTo , moveTo @@ -78,7 +82,7 @@ module XMonad.Actions.CycleWS ( ) where -import XMonad.Prelude (find, findIndex, isJust, isNothing) +import XMonad.Prelude (find, findIndex, isJust, isNothing, liftM2) import XMonad hiding (workspaces) import qualified XMonad.Hooks.WorkspaceHistory as WH import XMonad.StackSet hiding (filter) @@ -110,9 +114,9 @@ import XMonad.Util.WorkspaceCompare -- You can also get fancier with 'moveTo', 'shiftTo', and 'findWorkspace'. -- For example: -- --- > , ((modm , xK_f), moveTo Next EmptyWS) -- find a free workspace +-- > , ((modm , xK_f), moveTo Next emptyWS) -- find a free workspace -- > , ((modm .|. controlMask, xK_Right), -- a crazy keybinding! --- > do t <- findWorkspace getSortByXineramaRule Next NonEmptyWS 2 +-- > do t <- findWorkspace getSortByXineramaRule Next (Not emptyWS) 2 -- > windows . view $ t ) -- -- For detailed instructions on editing your key bindings, see @@ -211,7 +215,7 @@ shiftBy :: Int -> X () shiftBy d = wsBy d >>= windows . shift wsBy :: Int -> X WorkspaceId -wsBy = findWorkspace getSortByIndex Next AnyWS +wsBy = findWorkspace getSortByIndex Next anyWS {- $taketwo @@ -220,7 +224,7 @@ through subsets of workspaces. For example, -> moveTo Next EmptyWS +> moveTo Next emptyWS will move to the first available workspace with no windows, and @@ -231,6 +235,13 @@ the letter 'p' in its name. =) -} +{-# DEPRECATED EmptyWS "Use emptyWS instead." #-} +{-# DEPRECATED HiddenWS "Use hiddenWS instead." #-} +{-# DEPRECATED NonEmptyWS "Use Not emptyWS instead." #-} +{-# DEPRECATED HiddenNonEmptyWS "Use hiddenWS :&: Not emptyWS instead." #-} +{-# DEPRECATED HiddenEmptyWS "Use hiddenWS :&: emptyWS instead." #-} +{-# DEPRECATED AnyWS "Use anyWS instead." #-} +{-# DEPRECATED WSTagGroup "Use wsTagGroup instead." #-} -- | What type of workspaces should be included in the cycle? data WSType = EmptyWS -- ^ cycle through empty workspaces | NonEmptyWS -- ^ cycle through non-empty workspaces @@ -245,6 +256,11 @@ data WSType = EmptyWS -- ^ cycle through empty workspaces | WSIs (X (WindowSpace -> Bool)) -- ^ cycle through workspaces satisfying -- an arbitrary predicate + | WSType :&: WSType -- ^ cycle through workspaces satisfying both + -- predicates. + | WSType :|: WSType -- ^ cycle through workspaces satisfying one of + -- the predicates. + | Not WSType -- ^ cycle through workspaces not satisfying the predicate -- | Convert a WSType value to a predicate on workspaces. wsTypeToPred :: WSType -> X (WindowSpace -> Bool) @@ -262,7 +278,34 @@ wsTypeToPred AnyWS = return (const True) wsTypeToPred (WSTagGroup sep) = do cur <- groupName.workspace.current <$> gets windowset return $ (cur ==).groupName where groupName = takeWhile (/=sep).tag -wsTypeToPred (WSIs p) = p +wsTypeToPred (WSIs p ) = p +wsTypeToPred (p :&: q) = liftM2 (&&) <$> wsTypeToPred p <*> wsTypeToPred q +wsTypeToPred (p :|: q) = liftM2 (||) <$> wsTypeToPred p <*> wsTypeToPred q +wsTypeToPred (Not p ) = fmap not <$> wsTypeToPred p + +-- | Cycle through empty workspaces +emptyWS :: WSType +emptyWS = WSIs . return $ isNothing . stack + +-- | Cycle through non-visible workspaces +hiddenWS :: WSType +hiddenWS = WSIs $ do + hs <- gets (map tag . hidden . windowset) + return $ (`elem` hs) . tag + +-- | Cycle through all workspaces +anyWS :: WSType +anyWS = WSIs . return $ const True + +-- | Cycle through workspaces in the same group, the +-- group name is all characters up to the first +-- separator character or the end of the tag +wsTagGroup :: Char -> WSType +wsTagGroup sep = WSIs $ do + cur <- groupName . workspace . current <$> gets windowset + return $ (cur ==) . groupName + where groupName = takeWhile (/= sep) . tag + -- | View the next workspace in the given direction that satisfies -- the given condition. diff --git a/XMonad/Actions/SwapWorkspaces.hs b/XMonad/Actions/SwapWorkspaces.hs index 71bf38ec..2e147fb2 100644 --- a/XMonad/Actions/SwapWorkspaces.hs +++ b/XMonad/Actions/SwapWorkspaces.hs @@ -53,7 +53,7 @@ swapWithCurrent t s = swapWorkspaces t (currentTag s) s -- | Say @swapTo Next@ or @swapTo Prev@ to move your current workspace. -- This is an @X ()@ so can be hooked up to your keybindings directly. swapTo :: Direction1D -> X () -swapTo dir = findWorkspace getSortByIndex dir AnyWS 1 >>= windows . swapWithCurrent +swapTo dir = findWorkspace getSortByIndex dir anyWS 1 >>= windows . swapWithCurrent -- | Takes two workspace tags and an existing XMonad.StackSet and returns a new -- one with the two corresponding workspaces' tags swapped. diff --git a/XMonad/Actions/WorkspaceNames.hs b/XMonad/Actions/WorkspaceNames.hs index 3124f2eb..8114e8f4 100644 --- a/XMonad/Actions/WorkspaceNames.hs +++ b/XMonad/Actions/WorkspaceNames.hs @@ -48,7 +48,7 @@ import XMonad.Prelude (fromMaybe, isInfixOf, (<&>), (>=>)) import qualified XMonad.StackSet as W import qualified XMonad.Util.ExtensibleState as XS -import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..)) +import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..), anyWS) import qualified XMonad.Actions.SwapWorkspaces as Swap import XMonad.Hooks.DynamicLog (PP(..)) import XMonad.Prompt (mkXPrompt, XPConfig) @@ -141,7 +141,7 @@ workspaceNamesPP pp = getWorkspaceNames ":" <&> \ren -> pp{ ppRename = ppRename -- | See 'XMonad.Actions.SwapWorkspaces.swapTo'. This is the same with names. swapTo :: Direction1D -> X () -swapTo dir = swapTo' dir AnyWS +swapTo dir = swapTo' dir anyWS -- | Swap with the previous or next workspace of the given type. swapTo' :: Direction1D -> WSType -> X () diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs index 63a82cd8..ca111477 100644 --- a/XMonad/Config/Droundy.hs +++ b/XMonad/Config/Droundy.hs @@ -39,8 +39,8 @@ import XMonad.Prompt.Shell ( shellPrompt ) import XMonad.Actions.CopyWindow ( kill1, copy ) import XMonad.Actions.DynamicWorkspaces ( withNthWorkspace, withWorkspace, selectWorkspace, renameWorkspace, removeWorkspace ) -import XMonad.Actions.CycleWS ( moveTo, WSType( HiddenNonEmptyWS ), - Direction1D( Prev, Next) ) +import XMonad.Actions.CycleWS ( moveTo, hiddenWS, emptyWS, + Direction1D( Prev, Next), WSType ((:&:), Not) ) import XMonad.Hooks.ManageDocks ( avoidStruts, docks ) import XMonad.Hooks.EwmhDesktops ( ewmh ) @@ -80,8 +80,8 @@ keys x = M.fromList $ , ((modMask x .|. shiftMask, xK_Escape), io exitSuccess) -- %! Quit xmonad , ((modMask x , xK_Escape), restart "xmonad" True) -- %! Restart xmonad - , ((modMask x .|. shiftMask, xK_Right), moveTo Next HiddenNonEmptyWS) - , ((modMask x .|. shiftMask, xK_Left), moveTo Prev HiddenNonEmptyWS) + , ((modMask x .|. shiftMask, xK_Right), moveTo Next $ hiddenWS :&: Not emptyWS) + , ((modMask x .|. shiftMask, xK_Left), moveTo Prev $ hiddenWS :&: Not emptyWS) , ((modMask x, xK_Right), sendMessage $ Go R) , ((modMask x, xK_Left), sendMessage $ Go L) , ((modMask x, xK_Up), sendMessage $ Go U)