mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-07-31 20:21:51 -07:00
{X.A.OnScreen,X.H.ScreenCorners}: Reformat
This commit is contained in:
@@ -1,4 +1,3 @@
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Actions.OnScreen
|
||||
-- Description : Control workspaces on different screens (in xinerama mode).
|
||||
@@ -10,139 +9,173 @@
|
||||
-- Portability : unportable
|
||||
--
|
||||
-- Control workspaces on different screens (in xinerama mode).
|
||||
--
|
||||
-----------------------------------------------------------------------------
|
||||
|
||||
module XMonad.Actions.OnScreen (
|
||||
-- * Usage
|
||||
module XMonad.Actions.OnScreen
|
||||
( -- * Usage
|
||||
-- $usage
|
||||
onScreen
|
||||
, onScreen'
|
||||
, Focus(..)
|
||||
, viewOnScreen
|
||||
, greedyViewOnScreen
|
||||
, onlyOnScreen
|
||||
, toggleOnScreen
|
||||
, toggleGreedyOnScreen
|
||||
) where
|
||||
onScreen,
|
||||
onScreen',
|
||||
Focus (..),
|
||||
viewOnScreen,
|
||||
greedyViewOnScreen,
|
||||
onlyOnScreen,
|
||||
toggleOnScreen,
|
||||
toggleGreedyOnScreen,
|
||||
)
|
||||
where
|
||||
|
||||
import XMonad
|
||||
import XMonad.Prelude (fromMaybe, guard, empty)
|
||||
import XMonad.Prelude (empty, fromMaybe, guard)
|
||||
import XMonad.StackSet hiding (new)
|
||||
|
||||
|
||||
-- | Focus data definitions
|
||||
data Focus = FocusNew -- ^ always focus the new screen
|
||||
| FocusCurrent -- ^ always keep the focus on the current screen
|
||||
| FocusTag WorkspaceId -- ^ always focus tag i on the new stack
|
||||
| FocusTagVisible WorkspaceId -- ^ focus tag i only if workspace with tag i is visible on the old stack
|
||||
|
||||
data Focus
|
||||
= -- | always focus the new screen
|
||||
FocusNew
|
||||
| -- | always keep the focus on the current screen
|
||||
FocusCurrent
|
||||
| -- | always focus tag i on the new stack
|
||||
FocusTag WorkspaceId
|
||||
| -- | focus tag i only if workspace with tag i is visible on the old stack
|
||||
FocusTagVisible WorkspaceId
|
||||
|
||||
-- | Run any function that modifies the stack on a given screen. This function
|
||||
-- will also need to know which Screen to focus after the function has been
|
||||
-- run.
|
||||
onScreen :: (WindowSet -> WindowSet) -- ^ function to run
|
||||
-> Focus -- ^ what to do with the focus
|
||||
-> ScreenId -- ^ screen id
|
||||
-> WindowSet -- ^ current stack
|
||||
-> WindowSet
|
||||
onScreen ::
|
||||
-- | function to run
|
||||
(WindowSet -> WindowSet) ->
|
||||
-- | what to do with the focus
|
||||
Focus ->
|
||||
-- | screen id
|
||||
ScreenId ->
|
||||
-- | current stack
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
onScreen f foc sc st = fromMaybe st $ do
|
||||
ws <- lookupWorkspace sc st
|
||||
ws <- lookupWorkspace sc st
|
||||
|
||||
let fStack = f $ view ws st
|
||||
|
||||
return $ setFocus foc st fStack
|
||||
let fStack = f $ view ws st
|
||||
|
||||
return $ setFocus foc st fStack
|
||||
|
||||
-- set focus for new stack
|
||||
setFocus :: Focus
|
||||
-> WindowSet -- ^ old stack
|
||||
-> WindowSet -- ^ new stack
|
||||
-> WindowSet
|
||||
setFocus FocusNew _ new = new
|
||||
setFocus FocusCurrent old new =
|
||||
case lookupWorkspace (screen $ current old) new of
|
||||
Nothing -> new
|
||||
Just i -> view i new
|
||||
setFocus (FocusTag i) _ new = view i new
|
||||
setFocus ::
|
||||
Focus ->
|
||||
-- | old stack
|
||||
WindowSet ->
|
||||
-- | new stack
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
setFocus FocusNew _ new = new
|
||||
setFocus FocusCurrent old new =
|
||||
case lookupWorkspace (screen $ current old) new of
|
||||
Nothing -> new
|
||||
Just i -> view i new
|
||||
setFocus (FocusTag i) _ new = view i new
|
||||
setFocus (FocusTagVisible i) old new =
|
||||
if i `elem` map (tag . workspace) (visible old)
|
||||
then setFocus (FocusTag i) old new
|
||||
else setFocus FocusCurrent old new
|
||||
if i `elem` map (tag . workspace) (visible old)
|
||||
then setFocus (FocusTag i) old new
|
||||
else setFocus FocusCurrent old new
|
||||
|
||||
-- | A variation of @onScreen@ which will take any @X ()@ function and run it
|
||||
-- on the given screen.
|
||||
-- Warning: This function will change focus even if the function it's supposed
|
||||
-- to run doesn't succeed.
|
||||
onScreen' :: X () -- ^ X function to run
|
||||
-> Focus -- ^ focus
|
||||
-> ScreenId -- ^ screen id
|
||||
-> X ()
|
||||
onScreen' ::
|
||||
-- | X function to run
|
||||
X () ->
|
||||
-- | focus
|
||||
Focus ->
|
||||
-- | screen id
|
||||
ScreenId ->
|
||||
X ()
|
||||
onScreen' x foc sc = do
|
||||
st <- gets windowset
|
||||
case lookupWorkspace sc st of
|
||||
Nothing -> return ()
|
||||
Just ws -> do
|
||||
windows $ view ws
|
||||
x
|
||||
windows $ setFocus foc st
|
||||
|
||||
st <- gets windowset
|
||||
case lookupWorkspace sc st of
|
||||
Nothing -> return ()
|
||||
Just ws -> do
|
||||
windows $ view ws
|
||||
x
|
||||
windows $ setFocus foc st
|
||||
|
||||
-- | Switch to workspace @i@ on screen @sc@. If @i@ is visible use @view@ to
|
||||
-- switch focus to the workspace @i@.
|
||||
viewOnScreen :: ScreenId -- ^ screen id
|
||||
-> WorkspaceId -- ^ index of the workspace
|
||||
-> WindowSet -- ^ current stack
|
||||
-> WindowSet
|
||||
viewOnScreen ::
|
||||
-- | screen id
|
||||
ScreenId ->
|
||||
-- | index of the workspace
|
||||
WorkspaceId ->
|
||||
-- | current stack
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
viewOnScreen sid i =
|
||||
onScreen (view i) (FocusTag i) sid
|
||||
onScreen (view i) (FocusTag i) sid
|
||||
|
||||
-- | Switch to workspace @i@ on screen @sc@. If @i@ is visible use @greedyView@
|
||||
-- to switch the current workspace with workspace @i@.
|
||||
greedyViewOnScreen :: ScreenId -- ^ screen id
|
||||
-> WorkspaceId -- ^ index of the workspace
|
||||
-> WindowSet -- ^ current stack
|
||||
-> WindowSet
|
||||
greedyViewOnScreen ::
|
||||
-- | screen id
|
||||
ScreenId ->
|
||||
-- | index of the workspace
|
||||
WorkspaceId ->
|
||||
-- | current stack
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
greedyViewOnScreen sid i =
|
||||
onScreen (greedyView i) (FocusTagVisible i) sid
|
||||
onScreen (greedyView i) (FocusTagVisible i) sid
|
||||
|
||||
-- | Switch to workspace @i@ on screen @sc@. If @i@ is visible do nothing.
|
||||
onlyOnScreen :: ScreenId -- ^ screen id
|
||||
-> WorkspaceId -- ^ index of the workspace
|
||||
-> WindowSet -- ^ current stack
|
||||
-> WindowSet
|
||||
onlyOnScreen ::
|
||||
-- | screen id
|
||||
ScreenId ->
|
||||
-- | index of the workspace
|
||||
WorkspaceId ->
|
||||
-- | current stack
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
onlyOnScreen sid i =
|
||||
onScreen (view i) FocusCurrent sid
|
||||
onScreen (view i) FocusCurrent sid
|
||||
|
||||
-- | @toggleOrView@ as in "XMonad.Actions.CycleWS" for @onScreen@ with view
|
||||
toggleOnScreen :: ScreenId -- ^ screen id
|
||||
-> WorkspaceId -- ^ index of the workspace
|
||||
-> WindowSet -- ^ current stack
|
||||
-> WindowSet
|
||||
toggleOnScreen ::
|
||||
-- | screen id
|
||||
ScreenId ->
|
||||
-- | index of the workspace
|
||||
WorkspaceId ->
|
||||
-- | current stack
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
toggleOnScreen sid i =
|
||||
onScreen (toggleOrView' view i) FocusCurrent sid
|
||||
onScreen (toggleOrView' view i) FocusCurrent sid
|
||||
|
||||
-- | @toggleOrView@ from "XMonad.Actions.CycleWS" for @onScreen@ with greedyView
|
||||
toggleGreedyOnScreen :: ScreenId -- ^ screen id
|
||||
-> WorkspaceId -- ^ index of the workspace
|
||||
-> WindowSet -- ^ current stack
|
||||
-> WindowSet
|
||||
toggleGreedyOnScreen ::
|
||||
-- | screen id
|
||||
ScreenId ->
|
||||
-- | index of the workspace
|
||||
WorkspaceId ->
|
||||
-- | current stack
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
toggleGreedyOnScreen sid i =
|
||||
onScreen (toggleOrView' greedyView i) FocusCurrent sid
|
||||
|
||||
onScreen (toggleOrView' greedyView i) FocusCurrent sid
|
||||
|
||||
-- a \"pure\" version of X.A.CycleWS.toggleOrDoSkip
|
||||
toggleOrView' :: (WorkspaceId -> WindowSet -> WindowSet) -- ^ function to run
|
||||
-> WorkspaceId -- ^ tag to look for
|
||||
-> WindowSet -- ^ current stackset
|
||||
-> WindowSet
|
||||
toggleOrView' ::
|
||||
-- | function to run
|
||||
(WorkspaceId -> WindowSet -> WindowSet) ->
|
||||
-- | tag to look for
|
||||
WorkspaceId ->
|
||||
-- | current stackset
|
||||
WindowSet ->
|
||||
WindowSet
|
||||
toggleOrView' f i st = fromMaybe (f i st) $ do
|
||||
let st' = hidden st
|
||||
-- make sure we actually have to do something
|
||||
guard $ i == (tag . workspace $ current st)
|
||||
case st' of
|
||||
[] -> empty
|
||||
(h : _) -> return $ f (tag h) st -- finally, toggle!
|
||||
let st' = hidden st
|
||||
-- make sure we actually have to do something
|
||||
guard $ i == (tag . workspace $ current st)
|
||||
case st' of
|
||||
[] -> empty
|
||||
(h : _) -> return $ f (tag h) st -- finally, toggle!
|
||||
|
||||
-- $usage
|
||||
--
|
||||
|
Reference in New Issue
Block a user