module XMonad.Actions.OnScreen (
onScreen
, onScreen'
, Focus(..)
, viewOnScreen
, greedyViewOnScreen
, onlyOnScreen
, toggleOnScreen
, toggleGreedyOnScreen
) where
import XMonad
import XMonad.Prelude (fromMaybe, guard, empty)
import XMonad.StackSet hiding (new)
data Focus = FocusNew
| FocusCurrent
| FocusTag WorkspaceId
| FocusTagVisible WorkspaceId
onScreen :: (WindowSet -> WindowSet)
-> Focus
-> ScreenId
-> WindowSet
-> WindowSet
onScreen :: (WindowSet -> WindowSet)
-> Focus -> ScreenId -> WindowSet -> WindowSet
onScreen WindowSet -> WindowSet
f Focus
foc ScreenId
sc WindowSet
st = WindowSet -> Maybe WindowSet -> WindowSet
forall a. a -> Maybe a -> a
fromMaybe WindowSet
st (Maybe WindowSet -> WindowSet) -> Maybe WindowSet -> WindowSet
forall a b. (a -> b) -> a -> b
$ do
WorkspaceId
ws <- ScreenId -> WindowSet -> Maybe WorkspaceId
forall s i l a sd. Eq s => s -> StackSet i l a s sd -> Maybe i
lookupWorkspace ScreenId
sc WindowSet
st
let fStack :: WindowSet
fStack = WindowSet -> WindowSet
f (WindowSet -> WindowSet) -> WindowSet -> WindowSet
forall a b. (a -> b) -> a -> b
$ WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
view WorkspaceId
ws WindowSet
st
WindowSet -> Maybe WindowSet
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (WindowSet -> Maybe WindowSet) -> WindowSet -> Maybe WindowSet
forall a b. (a -> b) -> a -> b
$ Focus -> WindowSet -> WindowSet -> WindowSet
setFocus Focus
foc WindowSet
st WindowSet
fStack
setFocus :: Focus
-> WindowSet
-> WindowSet
-> WindowSet
setFocus :: Focus -> WindowSet -> WindowSet -> WindowSet
setFocus Focus
FocusNew WindowSet
_ WindowSet
new = WindowSet
new
setFocus Focus
FocusCurrent WindowSet
old WindowSet
new =
case ScreenId -> WindowSet -> Maybe WorkspaceId
forall s i l a sd. Eq s => s -> StackSet i l a s sd -> Maybe i
lookupWorkspace (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall i l a sid sd. Screen i l a sid sd -> sid
screen (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> ScreenId)
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> ScreenId
forall a b. (a -> b) -> a -> b
$ WindowSet
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
current WindowSet
old) WindowSet
new of
Maybe WorkspaceId
Nothing -> WindowSet
new
Just WorkspaceId
i -> WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
view WorkspaceId
i WindowSet
new
setFocus (FocusTag WorkspaceId
i) WindowSet
_ WindowSet
new = WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
view WorkspaceId
i WindowSet
new
setFocus (FocusTagVisible WorkspaceId
i) WindowSet
old WindowSet
new =
if WorkspaceId
i WorkspaceId -> [WorkspaceId] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> WorkspaceId)
-> [Screen
WorkspaceId (Layout Window) Window ScreenId ScreenDetail]
-> [WorkspaceId]
forall a b. (a -> b) -> [a] -> [b]
map (Workspace WorkspaceId (Layout Window) Window -> WorkspaceId
forall i l a. Workspace i l a -> i
tag (Workspace WorkspaceId (Layout Window) Window -> WorkspaceId)
-> (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> Workspace WorkspaceId (Layout Window) Window)
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> WorkspaceId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> Workspace WorkspaceId (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
workspace) (WindowSet
-> [Screen
WorkspaceId (Layout Window) Window ScreenId ScreenDetail]
forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
visible WindowSet
old)
then Focus -> WindowSet -> WindowSet -> WindowSet
setFocus (WorkspaceId -> Focus
FocusTag WorkspaceId
i) WindowSet
old WindowSet
new
else Focus -> WindowSet -> WindowSet -> WindowSet
setFocus Focus
FocusCurrent WindowSet
old WindowSet
new
onScreen' :: X ()
-> Focus
-> ScreenId
-> X ()
onScreen' :: X () -> Focus -> ScreenId -> X ()
onScreen' X ()
x Focus
foc ScreenId
sc = do
WindowSet
st <- (XState -> WindowSet) -> X WindowSet
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
case ScreenId -> WindowSet -> Maybe WorkspaceId
forall s i l a sd. Eq s => s -> StackSet i l a s sd -> Maybe i
lookupWorkspace ScreenId
sc WindowSet
st of
Maybe WorkspaceId
Nothing -> () -> X ()
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just WorkspaceId
ws -> do
(WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WindowSet -> WindowSet) -> X ()
forall a b. (a -> b) -> a -> b
$ WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
view WorkspaceId
ws
X ()
x
(WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WindowSet -> WindowSet) -> X ()
forall a b. (a -> b) -> a -> b
$ Focus -> WindowSet -> WindowSet -> WindowSet
setFocus Focus
foc WindowSet
st
viewOnScreen :: ScreenId
-> WorkspaceId
-> WindowSet
-> WindowSet
viewOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
viewOnScreen ScreenId
sid WorkspaceId
i =
(WindowSet -> WindowSet)
-> Focus -> ScreenId -> WindowSet -> WindowSet
onScreen (WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
view WorkspaceId
i) (WorkspaceId -> Focus
FocusTag WorkspaceId
i) ScreenId
sid
greedyViewOnScreen :: ScreenId
-> WorkspaceId
-> WindowSet
-> WindowSet
greedyViewOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
greedyViewOnScreen ScreenId
sid WorkspaceId
i =
(WindowSet -> WindowSet)
-> Focus -> ScreenId -> WindowSet -> WindowSet
onScreen (WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
greedyView WorkspaceId
i) (WorkspaceId -> Focus
FocusTagVisible WorkspaceId
i) ScreenId
sid
onlyOnScreen :: ScreenId
-> WorkspaceId
-> WindowSet
-> WindowSet
onlyOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
onlyOnScreen ScreenId
sid WorkspaceId
i =
(WindowSet -> WindowSet)
-> Focus -> ScreenId -> WindowSet -> WindowSet
onScreen (WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
view WorkspaceId
i) Focus
FocusCurrent ScreenId
sid
toggleOnScreen :: ScreenId
-> WorkspaceId
-> WindowSet
-> WindowSet
toggleOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
toggleOnScreen ScreenId
sid WorkspaceId
i =
(WindowSet -> WindowSet)
-> Focus -> ScreenId -> WindowSet -> WindowSet
onScreen ((WorkspaceId -> WindowSet -> WindowSet)
-> WorkspaceId -> WindowSet -> WindowSet
toggleOrView' WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
view WorkspaceId
i) Focus
FocusCurrent ScreenId
sid
toggleGreedyOnScreen :: ScreenId
-> WorkspaceId
-> WindowSet
-> WindowSet
toggleGreedyOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet
toggleGreedyOnScreen ScreenId
sid WorkspaceId
i =
(WindowSet -> WindowSet)
-> Focus -> ScreenId -> WindowSet -> WindowSet
onScreen ((WorkspaceId -> WindowSet -> WindowSet)
-> WorkspaceId -> WindowSet -> WindowSet
toggleOrView' WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
greedyView WorkspaceId
i) Focus
FocusCurrent ScreenId
sid
toggleOrView' :: (WorkspaceId -> WindowSet -> WindowSet)
-> WorkspaceId
-> WindowSet
-> WindowSet
toggleOrView' :: (WorkspaceId -> WindowSet -> WindowSet)
-> WorkspaceId -> WindowSet -> WindowSet
toggleOrView' WorkspaceId -> WindowSet -> WindowSet
f WorkspaceId
i WindowSet
st = WindowSet -> Maybe WindowSet -> WindowSet
forall a. a -> Maybe a -> a
fromMaybe (WorkspaceId -> WindowSet -> WindowSet
f WorkspaceId
i WindowSet
st) (Maybe WindowSet -> WindowSet) -> Maybe WindowSet -> WindowSet
forall a b. (a -> b) -> a -> b
$ do
let st' :: [Workspace WorkspaceId (Layout Window) Window]
st' = WindowSet -> [Workspace WorkspaceId (Layout Window) Window]
forall i l a sid sd. StackSet i l a sid sd -> [Workspace i l a]
hidden WindowSet
st
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ WorkspaceId
i WorkspaceId -> WorkspaceId -> Bool
forall a. Eq a => a -> a -> Bool
== (Workspace WorkspaceId (Layout Window) Window -> WorkspaceId
forall i l a. Workspace i l a -> i
tag (Workspace WorkspaceId (Layout Window) Window -> WorkspaceId)
-> (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> Workspace WorkspaceId (Layout Window) Window)
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> WorkspaceId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> Workspace WorkspaceId (Layout Window) Window
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
workspace (Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> WorkspaceId)
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
-> WorkspaceId
forall a b. (a -> b) -> a -> b
$ WindowSet
-> Screen WorkspaceId (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
current WindowSet
st)
case [Workspace WorkspaceId (Layout Window) Window]
st' of
[] -> Maybe WindowSet
forall a. Maybe a
forall (f :: * -> *) a. Alternative f => f a
empty
(Workspace WorkspaceId (Layout Window) Window
h : [Workspace WorkspaceId (Layout Window) Window]
_) -> WindowSet -> Maybe WindowSet
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (WindowSet -> Maybe WindowSet) -> WindowSet -> Maybe WindowSet
forall a b. (a -> b) -> a -> b
$ WorkspaceId -> WindowSet -> WindowSet
f (Workspace WorkspaceId (Layout Window) Window -> WorkspaceId
forall i l a. Workspace i l a -> i
tag Workspace WorkspaceId (Layout Window) Window
h) WindowSet
st