mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-26 09:41:52 -07:00
renamed the module to X.U.ExclusiveScratchpads
This commit is contained in:
@@ -1,7 +1,7 @@
|
|||||||
|
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
-- |
|
-- |
|
||||||
-- Module : XMonad.Util.MutexScratchpads
|
-- Module : XMonad.Util.ExclusiveScratchpads
|
||||||
-- Copyright : Bruce Forte (2017)
|
-- Copyright : Bruce Forte (2017)
|
||||||
-- License : BSD-style (see LICENSE)
|
-- License : BSD-style (see LICENSE)
|
||||||
--
|
--
|
||||||
@@ -13,29 +13,28 @@
|
|||||||
--
|
--
|
||||||
-----------------------------------------------------------------------------
|
-----------------------------------------------------------------------------
|
||||||
|
|
||||||
module XMonad.Util.MutexScratchpads (
|
module XMonad.Util.ExclusiveScratchpads (
|
||||||
-- * Usage
|
-- * Usage
|
||||||
-- $usage
|
-- $usage
|
||||||
mkMutexSps,
|
mkXScratchpads,
|
||||||
mutexSpsManageHook,
|
xScratchpadsManageHook,
|
||||||
-- * Keyboard related
|
-- * Keyboard related
|
||||||
scratchpadAction,
|
scratchpadAction,
|
||||||
hideAll,
|
hideAll,
|
||||||
resetMutexSp,
|
resetExclusiveSp,
|
||||||
-- * Mouse related
|
-- * Mouse related
|
||||||
setNomutex,
|
setNoexclusive,
|
||||||
resizeNomutex,
|
resizeNoexclusive,
|
||||||
floatMoveNomutex,
|
floatMoveNoexclusive,
|
||||||
-- * Types
|
-- * Types
|
||||||
MutexScratchpad(..),
|
ExclusiveScratchpad(..),
|
||||||
MutexScratchpads,
|
ExclusiveScratchpads,
|
||||||
-- * Hooks
|
-- * Hooks
|
||||||
nonFloating,
|
nonFloating,
|
||||||
defaultFloating,
|
defaultFloating,
|
||||||
customFloating
|
customFloating
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Applicative ((<$>))
|
|
||||||
import Control.Monad (filterM,unless,void,(<=<))
|
import Control.Monad (filterM,unless,void,(<=<))
|
||||||
import Data.Monoid (appEndo)
|
import Data.Monoid (appEndo)
|
||||||
import XMonad hiding (hide)
|
import XMonad hiding (hide)
|
||||||
@@ -48,27 +47,27 @@ import qualified XMonad.StackSet as W
|
|||||||
-- $usage
|
-- $usage
|
||||||
-- To use this module, put the following in your @~\/.xmonad\/xmonad.hs@:
|
-- To use this module, put the following in your @~\/.xmonad\/xmonad.hs@:
|
||||||
--
|
--
|
||||||
-- > import XMonad.Utils.MutexScratchpads
|
-- > import XMonad.Utils.ExclusiveScratchpads
|
||||||
-- > import XMonad.ManageHook
|
-- > import XMonad.ManageHook
|
||||||
-- > import qualified XMonad.StackSet as W
|
-- > import qualified XMonad.StackSet as W
|
||||||
--
|
--
|
||||||
-- Add mutually exclusive scratchpads, for example:
|
-- Add exclusive scratchpads, for example:
|
||||||
--
|
--
|
||||||
-- > mutexSps = mkMutexSps [ ("htop", "urxvt -e htop", title =? "htop")
|
-- > exclusiveSps = mkXScratchpads [ ("htop", "urxvt -e htop", title =? "htop")
|
||||||
-- > , ("xclock", "xclock", appName =? "xclock")
|
-- > , ("xclock", "xclock", appName =? "xclock")
|
||||||
-- > ] $ customFloating $ W.RationalRect (1/4) (1/4) (1/2) (1/2)
|
-- > ] $ customFloating $ W.RationalRect (1/4) (1/4) (1/2) (1/2)
|
||||||
--
|
--
|
||||||
-- The scratchpads don\'t have to be mutually exclusive, you can create them like this (see 'MutexScratchpad'):
|
-- The scratchpads don\'t have to be exclusive, you can create them like this (see 'ExclusiveScratchpad'):
|
||||||
--
|
--
|
||||||
-- > regularSps = [ MNS "term" "urxvt -name scratchpad" (appName =? "scratchpad") defaultFloating [] ]
|
-- > regularSps = [ EXS "term" "urxvt -name scratchpad" (appName =? "scratchpad") defaultFloating [] ]
|
||||||
--
|
--
|
||||||
-- Create a list that contains all your scratchpads like this:
|
-- Create a list that contains all your scratchpads like this:
|
||||||
--
|
--
|
||||||
-- > scratchpads = mutexSps ++ regularSps
|
-- > scratchpads = exclusiveSps ++ regularSps
|
||||||
--
|
--
|
||||||
-- Add the hooks to your managehook, eg. (see "XMonad.Doc.Extending#Editing_the_manage_hook"):
|
-- Add the hooks to your managehook, eg. (see "XMonad.Doc.Extending#Editing_the_manage_hook"):
|
||||||
--
|
--
|
||||||
-- > manageHook = myManageHook <+> mutexSpsManageHook 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"):
|
||||||
--
|
--
|
||||||
@@ -82,67 +81,67 @@ import qualified XMonad.StackSet as W
|
|||||||
-- scratchpad then @htop@ gets hidden.
|
-- scratchpad then @htop@ gets hidden.
|
||||||
--
|
--
|
||||||
-- If you move a scratchpad it still gets hidden when you fetch a scratchpad of
|
-- If you move a scratchpad it still gets hidden when you fetch a scratchpad of
|
||||||
-- the same family, to change that behaviour and make windows not mutually exclusive
|
-- the same family, to change that behaviour and make windows not exclusive
|
||||||
-- anymore when they get resized or moved add these mouse bindings
|
-- anymore when they get resized or moved add these mouse bindings
|
||||||
-- (see "XMonad.Doc.Extending#Editing_mouse_bindings"):
|
-- (see "XMonad.Doc.Extending#Editing_mouse_bindings"):
|
||||||
--
|
--
|
||||||
-- > , ((mod4Mask, button1), floatMoveNomutex scratchpads)
|
-- > , ((mod4Mask, button1), floatMoveNoexclusive scratchpads)
|
||||||
-- > , ((mod4Mask, button3), resizeNomutex scratchpads)
|
-- > , ((mod4Mask, button3), resizeNoexclusive scratchpads)
|
||||||
--
|
--
|
||||||
-- To reset a moved scratchpad to the original position that you set with its hook,
|
-- To reset a moved scratchpad to the original position that you set with its hook,
|
||||||
-- call @resetMutexSp@ when it is in focus. For example if you want to extend
|
-- call @resetExclusiveSp@ when it is in focus. For example if you want to extend
|
||||||
-- Mod-Return to reset the placement when a scratchpad is in focus but keep the
|
-- Mod-Return to reset the placement when a scratchpad is in focus but keep the
|
||||||
-- default behaviour for tiled windows, set these key bindings:
|
-- default behaviour for tiled windows, set these key bindings:
|
||||||
--
|
--
|
||||||
-- > , ((modMask, xK_Return), windows W.swapMaster >> resetMutexSp scratchpads)
|
-- > , ((modMask, xK_Return), windows W.swapMaster >> resetExclusiveSp scratchpads)
|
||||||
--
|
--
|
||||||
-- If you are annoyed by the @NSP@ workspace in your statusbar and are using
|
-- If you are annoyed by the @NSP@ workspace in your statusbar and are using
|
||||||
-- @dynamicLogWithPP@ add this to your PP:
|
-- @dynamicLogWithPP@ add this to your PP:
|
||||||
--
|
--
|
||||||
-- > , ppHidden = \x -> if x == "NSP" then "" else x
|
-- > , ppHidden = \x -> if x == "NSP" then "" else x
|
||||||
--
|
--
|
||||||
-- __Note:__ This is just an example, in general you can add more than two mutually
|
-- __Note:__ This is just an example, in general you can add more than two
|
||||||
-- exclusive scratchpads and multiple families of such.
|
-- exclusive scratchpads and multiple families of such.
|
||||||
|
|
||||||
|
|
||||||
-- | MutexScratchpad record specifies its properties
|
-- | ExclusiveScratchpad record specifies its properties
|
||||||
data MutexScratchpad = MNS { name :: String -- ^ Name of the scratchpad
|
data ExclusiveScratchpad = EXS { name :: String -- ^ Name of the scratchpad
|
||||||
, cmd :: String -- ^ Command to spawn the scratchpad
|
, cmd :: String -- ^ Command to spawn the scratchpad
|
||||||
, query :: Query Bool -- ^ Query to match the scratchpad
|
, query :: Query Bool -- ^ Query to match the scratchpad
|
||||||
, hook :: ManageHook -- ^ Hook to specify the placement policy
|
, hook :: ManageHook -- ^ Hook to specify the placement policy
|
||||||
, rivals :: [String] -- ^ Names of rivalling scratchpads
|
, exclusive :: [String] -- ^ Names of exclusive scratchpads
|
||||||
}
|
}
|
||||||
|
|
||||||
type MutexScratchpads = [MutexScratchpad]
|
type ExclusiveScratchpads = [ExclusiveScratchpad]
|
||||||
|
|
||||||
-- | Name of the hidden workspace
|
-- | Name of the hidden workspace
|
||||||
nsp :: String
|
nsp :: String
|
||||||
nsp = "NSP"
|
nsp = "NSP"
|
||||||
|
|
||||||
-- | Create 'MutexScratchpads' from @[(name,cmd,query)]@ with a common @hook@
|
-- | Create 'ExclusiveScratchpads' from @[(name,cmd,query)]@ with a common @hook@
|
||||||
mkMutexSps :: [(String,String,Query Bool)] -- ^ List of @(name,cmd,query)@ of the
|
mkXScratchpads :: [(String,String,Query Bool)] -- ^ List of @(name,cmd,query)@ of the
|
||||||
-- mutually exclusive scratchpads
|
-- exclusive scratchpads
|
||||||
-> ManageHook -- ^ The common @hook@ that they use
|
-> ManageHook -- ^ The common @hook@ that they use
|
||||||
-> MutexScratchpads
|
-> ExclusiveScratchpads
|
||||||
mkMutexSps sps h = foldl accumulate [] sps
|
mkXScratchpads sps h = foldl accumulate [] sps
|
||||||
where
|
where
|
||||||
accumulate a (n,c,q) = MNS n c q h (filter (n/=) names) : a
|
accumulate a (n,c,q) = EXS n c q h (filter (n/=) names) : a
|
||||||
names = map (\(n,_,_) -> n) sps
|
names = map (\(n,_,_) -> n) sps
|
||||||
|
|
||||||
-- | Create 'ManageHook' from 'MutexScratchpads'
|
-- | Create 'ManageHook' from 'ExclusiveScratchpads'
|
||||||
mutexSpsManageHook :: MutexScratchpads -- ^ List of mutually exclusive scratchpads from
|
xScratchpadsManageHook :: ExclusiveScratchpads -- ^ List of exclusive scratchpads from
|
||||||
-- which a 'ManageHook' should be generated
|
-- which a 'ManageHook' should be generated
|
||||||
-> ManageHook
|
-> ManageHook
|
||||||
mutexSpsManageHook = composeAll . fmap (\sp -> query sp --> hook sp)
|
xScratchpadsManageHook = composeAll . fmap (\sp -> query sp --> hook sp)
|
||||||
|
|
||||||
-- | Pop up/hide the scratchpad by name and possibly hide its rivals
|
-- | Pop up/hide the scratchpad by name and possibly hide its exclusive
|
||||||
scratchpadAction :: MutexScratchpads -- ^ List of mutually exclusive scratchpads
|
scratchpadAction :: ExclusiveScratchpads -- ^ List of exclusive scratchpads
|
||||||
-> String -- ^ Name of the scratchpad to toggle
|
-> String -- ^ Name of the scratchpad to toggle
|
||||||
-> X ()
|
-> X ()
|
||||||
scratchpadAction sps n = popOrHide sps n >> whenX (isMutex sps n) (hideOthers sps n)
|
scratchpadAction sps n = popOrHide sps n >> whenX (isExclusive sps n) (hideOthers sps n)
|
||||||
|
|
||||||
-- | Toggles the scratchpad, if 'nsp' is not present create it on a spawn
|
-- | Toggles the scratchpad, if 'nsp' is not present create it on a spawn
|
||||||
popOrHide :: MutexScratchpads -> String -> X ()
|
popOrHide :: ExclusiveScratchpads -> String -> X ()
|
||||||
popOrHide sps n = do
|
popOrHide sps n = do
|
||||||
let sp = filter ((n==).name) sps
|
let sp = filter ((n==).name) sps
|
||||||
q = joinQueries $ map query sp
|
q = joinQueries $ map query sp
|
||||||
@@ -163,19 +162,19 @@ popOrHide sps n = do
|
|||||||
hide :: Window -> WindowSet -> WindowSet
|
hide :: Window -> WindowSet -> WindowSet
|
||||||
hide = W.shiftWin nsp
|
hide = W.shiftWin nsp
|
||||||
|
|
||||||
-- | Hide all 'MutexScratchpads' on the current screen
|
-- | Hide all 'ExclusiveScratchpads' on the current screen
|
||||||
hideAll :: MutexScratchpads -- ^ List of mutually exclusive scratchpads
|
hideAll :: ExclusiveScratchpads -- ^ List of exclusive scratchpads
|
||||||
-> X ()
|
-> X ()
|
||||||
hideAll sps = void $ mapWithCurrentScreen q hide
|
hideAll sps = void $ mapWithCurrentScreen q hide
|
||||||
where q = joinQueries $ map query sps
|
where q = joinQueries $ map query sps
|
||||||
|
|
||||||
-- | Hide the scratchpad of the same family by name if it's on the focused workspace
|
-- | Hide the scratchpad of the same family by name if it's on the focused workspace
|
||||||
hideOthers :: MutexScratchpads -> String -> X ()
|
hideOthers :: ExclusiveScratchpads -> String -> X ()
|
||||||
hideOthers sps n =
|
hideOthers sps n =
|
||||||
let others = concatMap rivals $ filter ((n==).name) sps
|
let others = concatMap exclusive $ filter ((n==).name) sps
|
||||||
otherQueries = map query $ filter ((`elem` others).name) sps
|
otherQueries = map query $ filter ((`elem` others).name) sps
|
||||||
joinedQuery = joinQueries otherQueries
|
joinedQuery = joinQueries otherQueries
|
||||||
qry = joinedQuery <&&> isMutexQuery in
|
qry = joinedQuery <&&> isExclusiveQuery in
|
||||||
|
|
||||||
void $ mapWithCurrentScreen qry hide
|
void $ mapWithCurrentScreen qry hide
|
||||||
|
|
||||||
@@ -187,25 +186,25 @@ mapWithCurrentScreen q f = withWindowSet $ \s -> do
|
|||||||
|
|
||||||
return $ ws /= []
|
return $ ws /= []
|
||||||
|
|
||||||
-- | Check if scratchpad is mutually exclusive
|
-- | Check if scratchpad is exclusive
|
||||||
isMutex :: MutexScratchpads -> String -> X Bool
|
isExclusive :: ExclusiveScratchpads -> String -> X Bool
|
||||||
isMutex sps n = withWindowSet $ \s -> do
|
isExclusive sps n = withWindowSet $ \s -> do
|
||||||
let q = isMutexQuery <&&> joinQueries (map query $ filter ((n==).name) sps)
|
let q = isExclusiveQuery <&&> joinQueries (map query $ filter ((n==).name) sps)
|
||||||
|
|
||||||
ws <- filterM (runQuery q) $ W.allWindows s
|
ws <- filterM (runQuery q) $ W.allWindows s
|
||||||
return $ ws /= []
|
return $ ws /= []
|
||||||
|
|
||||||
-- | Check if given window is a scratchpad
|
-- | Check if given window is a scratchpad
|
||||||
isScratchpad :: MutexScratchpads -> Window -> X Bool
|
isScratchpad :: ExclusiveScratchpads -> Window -> X Bool
|
||||||
isScratchpad sps w = withWindowSet $ \s -> do
|
isScratchpad sps w = withWindowSet $ \s -> do
|
||||||
let q = joinQueries $ map query sps
|
let q = joinQueries $ map query sps
|
||||||
|
|
||||||
ws <- filterM (runQuery q) $ W.allWindows s
|
ws <- filterM (runQuery q) $ W.allWindows s
|
||||||
return $ elem w ws
|
return $ elem w ws
|
||||||
|
|
||||||
-- | Query that matches if the window is mutually exclusive
|
-- | Query that matches if the window is exclusive
|
||||||
isMutexQuery :: Query Bool
|
isExclusiveQuery :: Query Bool
|
||||||
isMutexQuery = (notElem "CS_NOMUTEX" . words) <$> stringProperty "_XMONAD_TAGS"
|
isExclusiveQuery = (notElem "CS_NOEXCLUSIVE" . words) <$> stringProperty "_XMONAD_TAGS"
|
||||||
|
|
||||||
-- | Build a disjunction from a list of clauses
|
-- | Build a disjunction from a list of clauses
|
||||||
joinQueries :: [Query Bool] -> Query Bool
|
joinQueries :: [Query Bool] -> Query Bool
|
||||||
@@ -220,10 +219,10 @@ unlessX :: X Bool -> X () -> X ()
|
|||||||
unlessX = whenX . fmap not
|
unlessX = whenX . fmap not
|
||||||
|
|
||||||
-- | If the focused window is a scratchpad, the scratchpad gets reset to the original
|
-- | If the focused window is a scratchpad, the scratchpad gets reset to the original
|
||||||
-- placement specified with the hook and becomes mutually exclusive again
|
-- placement specified with the hook and becomes exclusive again
|
||||||
resetMutexSp :: MutexScratchpads -- ^ List of mutually exclusive scratchpads
|
resetExclusiveSp :: ExclusiveScratchpads -- ^ List of exclusive scratchpads
|
||||||
-> X ()
|
-> X ()
|
||||||
resetMutexSp sps = withFocused $ \w -> whenX (isScratchpad sps w) $ do
|
resetExclusiveSp sps = withFocused $ \w -> whenX (isScratchpad sps w) $ do
|
||||||
let msp = filterM (flip runQuery w . query) sps
|
let msp = filterM (flip runQuery w . query) sps
|
||||||
|
|
||||||
unlessX (null <$> msp) $ do
|
unlessX (null <$> msp) $ do
|
||||||
@@ -232,29 +231,29 @@ resetMutexSp sps = withFocused $ \w -> whenX (isScratchpad sps w) $ do
|
|||||||
|
|
||||||
(windows . appEndo <=< runQuery mh) w
|
(windows . appEndo <=< runQuery mh) w
|
||||||
hideOthers sps n
|
hideOthers sps n
|
||||||
delTag "CS_NOMUTEX" w
|
delTag "CS_NOEXCLUSIVE" w
|
||||||
|
|
||||||
-- | Make a window not mutually exclusive anymore
|
-- | Make a window not exclusive anymore
|
||||||
setNomutex :: MutexScratchpads -- ^ List of mutually exclusive scratchpads
|
setNoexclusive :: ExclusiveScratchpads -- ^ List of exclusive scratchpads
|
||||||
-> Window -- ^ Window which should be made not mutually
|
-> Window -- ^ Window which should be made not
|
||||||
-- exclusive anymore
|
-- exclusive anymore
|
||||||
-> X ()
|
-> X ()
|
||||||
setNomutex sps w = whenX (isScratchpad sps w) $ addTag "CS_NOMUTEX" w
|
setNoexclusive sps w = whenX (isScratchpad sps w) $ addTag "CS_NOEXCLUSIVE" w
|
||||||
|
|
||||||
-- | Float and drag the window, make it not mutually exclusive anymore
|
-- | Float and drag the window, make it not exclusive anymore
|
||||||
floatMoveNomutex :: MutexScratchpads -- ^ List of mutually exclusive scratchpads
|
floatMoveNoexclusive :: ExclusiveScratchpads -- ^ List of exclusive scratchpads
|
||||||
-> Window -- ^ Window which should be moved
|
-> Window -- ^ Window which should be moved
|
||||||
-> X ()
|
-> X ()
|
||||||
floatMoveNomutex sps w = setNomutex sps w
|
floatMoveNoexclusive sps w = setNoexclusive sps w
|
||||||
>> focus w
|
>> focus w
|
||||||
>> mouseMoveWindow w
|
>> mouseMoveWindow w
|
||||||
>> windows W.shiftMaster
|
>> windows W.shiftMaster
|
||||||
|
|
||||||
-- | Resize window, make it not mutually exclusive anymore
|
-- | Resize window, make it not exclusive anymore
|
||||||
resizeNomutex :: MutexScratchpads -- ^ List of mutually exclusive scratchpads
|
resizeNoexclusive :: ExclusiveScratchpads -- ^ List of exclusive scratchpads
|
||||||
-> Window -- ^ Window which should be resized
|
-> Window -- ^ Window which should be resized
|
||||||
-> X ()
|
-> X ()
|
||||||
resizeNomutex sps w = setNomutex sps w
|
resizeNoexclusive sps w = setNoexclusive sps w
|
||||||
>> focus w
|
>> focus w
|
||||||
>> mouseResizeWindow w
|
>> mouseResizeWindow w
|
||||||
>> windows W.shiftMaster
|
>> windows W.shiftMaster
|
Reference in New Issue
Block a user