module XMonad.Actions.GroupNavigation (
Direction (..)
, nextMatch
, nextMatchOrDo
, nextMatchWithThis
, historyHook
, isOnAnyVisibleWS
) where
import Control.Monad.Reader
import Control.Monad.State
import Data.Map ((!))
import qualified Data.Map as Map
import Data.Sequence (Seq, ViewL (EmptyL, (:<)), viewl, (<|), (><), (|>))
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import Graphics.X11.Types
import Prelude hiding (concatMap, drop, elem, filter, null, reverse)
import XMonad.Core
import XMonad.ManageHook
import XMonad.Operations (windows, withFocused)
import XMonad.Prelude (elem, foldl')
import qualified XMonad.StackSet as SS
import qualified XMonad.Util.ExtensibleState as XS
data Direction = Forward
| Backward
| History
nextMatchWithThis :: Eq a => Direction -> Query a -> X ()
nextMatchWithThis :: Direction -> Query a -> X ()
nextMatchWithThis Direction
dir Query a
qry = (Window -> X ()) -> X ()
withFocused ((Window -> X ()) -> X ()) -> (Window -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \Window
win -> do
a
prop <- Query a -> Window -> X a
forall a. Query a -> Window -> X a
runQuery Query a
qry Window
win
Direction -> Query Bool -> X ()
nextMatch Direction
dir (Query a
qry Query a -> a -> Query Bool
forall a. Eq a => Query a -> a -> Query Bool
=? a
prop)
nextMatch :: Direction -> Query Bool -> X ()
nextMatch :: Direction -> Query Bool -> X ()
nextMatch Direction
dir Query Bool
qry = Direction -> Query Bool -> X () -> X ()
nextMatchOrDo Direction
dir Query Bool
qry (() -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
nextMatchOrDo :: Direction -> Query Bool -> X () -> X ()
nextMatchOrDo :: Direction -> Query Bool -> X () -> X ()
nextMatchOrDo Direction
dir Query Bool
qry X ()
act = Direction -> X (Seq Window)
orderedWindowList Direction
dir
X (Seq Window) -> (Seq Window -> X ()) -> X ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Query Bool -> X () -> Seq Window -> X ()
focusNextMatchOrDo Query Bool
qry X ()
act
focusNextMatchOrDo :: Query Bool -> X () -> Seq Window -> X ()
focusNextMatchOrDo :: Query Bool -> X () -> Seq Window -> X ()
focusNextMatchOrDo Query Bool
qry X ()
act = (Window -> X Bool) -> Seq Window -> X (Maybe Window)
forall (m :: * -> *) a.
Monad m =>
(a -> m Bool) -> Seq a -> m (Maybe a)
findM (Query Bool -> Window -> X Bool
forall a. Query a -> Window -> X a
runQuery Query Bool
qry)
(Seq Window -> X (Maybe Window))
-> (Maybe Window -> X ()) -> Seq Window -> X ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> X () -> (Window -> X ()) -> Maybe Window -> X ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe X ()
act ((WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Window -> WindowSet -> WindowSet) -> Window -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> WindowSet
forall s a i l sd.
(Eq s, Eq a, Eq i) =>
a -> StackSet i l a s sd -> StackSet i l a s sd
SS.focusWindow)
orderedWindowList :: Direction -> X (Seq Window)
orderedWindowList :: Direction -> X (Seq Window)
orderedWindowList Direction
History = (HistoryDB -> Seq Window) -> X HistoryDB -> X (Seq Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(HistoryDB Maybe Window
w Seq Window
ws) -> Seq Window -> (Window -> Seq Window) -> Maybe Window -> Seq Window
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seq Window
ws (Seq Window
ws Seq Window -> Window -> Seq Window
forall a. Seq a -> a -> Seq a
|>) Maybe Window
w) X HistoryDB
forall a (m :: * -> *). (ExtensionClass a, XLike m) => m a
XS.get
orderedWindowList Direction
dir = (WindowSet -> X (Seq Window)) -> X (Seq Window)
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X (Seq Window)) -> X (Seq Window))
-> (WindowSet -> X (Seq Window)) -> X (Seq Window)
forall a b. (a -> b) -> a -> b
$ \WindowSet
ss -> do
Seq String
wsids <- (XConf -> Seq String) -> X (Seq String)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ([String] -> Seq String
forall a. [a] -> Seq a
Seq.fromList ([String] -> Seq String)
-> (XConf -> [String]) -> XConf -> Seq String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConfig Layout -> [String]
forall (l :: * -> *). XConfig l -> [String]
workspaces (XConfig Layout -> [String])
-> (XConf -> XConfig Layout) -> XConf -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XConf -> XConfig Layout
config)
let wspcs :: Seq WindowSpace
wspcs = WindowSet -> Seq String -> Seq WindowSpace
orderedWorkspaceList WindowSet
ss Seq String
wsids
wins :: Seq Window
wins = Direction -> Seq Window -> Seq Window
forall a. Direction -> Seq a -> Seq a
dirfun Direction
dir
(Seq Window -> Seq Window) -> Seq Window -> Seq Window
forall a b. (a -> b) -> a -> b
$ (Seq Window -> Seq Window -> Seq Window)
-> Seq Window -> Seq (Seq Window) -> Seq Window
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Seq Window -> Seq Window -> Seq Window
forall a. Seq a -> Seq a -> Seq a
(><) Seq Window
forall a. Seq a
Seq.empty
(Seq (Seq Window) -> Seq Window) -> Seq (Seq Window) -> Seq Window
forall a b. (a -> b) -> a -> b
$ (WindowSpace -> Seq Window) -> Seq WindowSpace -> Seq (Seq Window)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Window] -> Seq Window
forall a. [a] -> Seq a
Seq.fromList ([Window] -> Seq Window)
-> (WindowSpace -> [Window]) -> WindowSpace -> Seq Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Stack Window) -> [Window]
forall a. Maybe (Stack a) -> [a]
SS.integrate' (Maybe (Stack Window) -> [Window])
-> (WindowSpace -> Maybe (Stack Window)) -> WindowSpace -> [Window]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSpace -> Maybe (Stack Window)
forall i l a. Workspace i l a -> Maybe (Stack a)
SS.stack) Seq WindowSpace
wspcs
cur :: Maybe Window
cur = WindowSet -> Maybe Window
forall i l a s sd. StackSet i l a s sd -> Maybe a
SS.peek WindowSet
ss
Seq Window -> X (Seq Window)
forall (m :: * -> *) a. Monad m => a -> m a
return (Seq Window -> X (Seq Window)) -> Seq Window -> X (Seq Window)
forall a b. (a -> b) -> a -> b
$ Seq Window -> (Window -> Seq Window) -> Maybe Window -> Seq Window
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seq Window
wins (Seq Window -> Window -> Seq Window
forall a. Eq a => Seq a -> a -> Seq a
rotfun Seq Window
wins) Maybe Window
cur
where
dirfun :: Direction -> Seq a -> Seq a
dirfun Direction
Backward = Seq a -> Seq a
forall a. Seq a -> Seq a
Seq.reverse
dirfun Direction
_ = Seq a -> Seq a
forall a. a -> a
id
rotfun :: Seq a -> a -> Seq a
rotfun Seq a
wins a
x = Seq a -> Seq a
forall a. Seq a -> Seq a
rotate (Seq a -> Seq a) -> Seq a -> Seq a
forall a b. (a -> b) -> a -> b
$ (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
rotateTo (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x) Seq a
wins
orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace
orderedWorkspaceList :: WindowSet -> Seq String -> Seq WindowSpace
orderedWorkspaceList WindowSet
ss Seq String
wsids = (WindowSpace -> Bool) -> Seq WindowSpace -> Seq WindowSpace
forall a. (a -> Bool) -> Seq a -> Seq a
rotateTo WindowSpace -> Bool
forall l a. Workspace String l a -> Bool
isCurWS Seq WindowSpace
wspcs'
where
wspcs :: [WindowSpace]
wspcs = WindowSet -> [WindowSpace]
forall i l a s sd. StackSet i l a s sd -> [Workspace i l a]
SS.workspaces WindowSet
ss
wspcsMap :: Map String WindowSpace
wspcsMap = (Map String WindowSpace -> WindowSpace -> Map String WindowSpace)
-> Map String WindowSpace
-> [WindowSpace]
-> Map String WindowSpace
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Map String WindowSpace
m WindowSpace
ws -> String
-> WindowSpace -> Map String WindowSpace -> Map String WindowSpace
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (WindowSpace -> String
forall i l a. Workspace i l a -> i
SS.tag WindowSpace
ws) WindowSpace
ws Map String WindowSpace
m) Map String WindowSpace
forall k a. Map k a
Map.empty [WindowSpace]
wspcs
wspcs' :: Seq WindowSpace
wspcs' = (String -> WindowSpace) -> Seq String -> Seq WindowSpace
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Map String WindowSpace
wspcsMap Map String WindowSpace -> String -> WindowSpace
forall k a. Ord k => Map k a -> k -> a
!) Seq String
wsids
isCurWS :: Workspace String l a -> Bool
isCurWS Workspace String l a
ws = Workspace String l a -> String
forall i l a. Workspace i l a -> i
SS.tag Workspace String l a
ws String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== WindowSpace -> String
forall i l a. Workspace i l a -> i
SS.tag (Screen String (Layout Window) Window ScreenId ScreenDetail
-> WindowSpace
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
SS.workspace (Screen String (Layout Window) Window ScreenId ScreenDetail
-> WindowSpace)
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> WindowSpace
forall a b. (a -> b) -> a -> b
$ WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
SS.current WindowSet
ss)
data HistoryDB = HistoryDB (Maybe Window)
(Seq Window)
deriving (ReadPrec [HistoryDB]
ReadPrec HistoryDB
Int -> ReadS HistoryDB
ReadS [HistoryDB]
(Int -> ReadS HistoryDB)
-> ReadS [HistoryDB]
-> ReadPrec HistoryDB
-> ReadPrec [HistoryDB]
-> Read HistoryDB
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HistoryDB]
$creadListPrec :: ReadPrec [HistoryDB]
readPrec :: ReadPrec HistoryDB
$creadPrec :: ReadPrec HistoryDB
readList :: ReadS [HistoryDB]
$creadList :: ReadS [HistoryDB]
readsPrec :: Int -> ReadS HistoryDB
$creadsPrec :: Int -> ReadS HistoryDB
Read, Int -> HistoryDB -> ShowS
[HistoryDB] -> ShowS
HistoryDB -> String
(Int -> HistoryDB -> ShowS)
-> (HistoryDB -> String)
-> ([HistoryDB] -> ShowS)
-> Show HistoryDB
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HistoryDB] -> ShowS
$cshowList :: [HistoryDB] -> ShowS
show :: HistoryDB -> String
$cshow :: HistoryDB -> String
showsPrec :: Int -> HistoryDB -> ShowS
$cshowsPrec :: Int -> HistoryDB -> ShowS
Show)
instance ExtensionClass HistoryDB where
initialValue :: HistoryDB
initialValue = Maybe Window -> Seq Window -> HistoryDB
HistoryDB Maybe Window
forall a. Maybe a
Nothing Seq Window
forall a. Seq a
Seq.empty
extensionType :: HistoryDB -> StateExtension
extensionType = HistoryDB -> StateExtension
forall a. (Read a, Show a, ExtensionClass a) => a -> StateExtension
PersistentExtension
historyHook :: X ()
historyHook :: X ()
historyHook = X HistoryDB
forall a (m :: * -> *). (ExtensionClass a, XLike m) => m a
XS.get X HistoryDB -> (HistoryDB -> X HistoryDB) -> X HistoryDB
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HistoryDB -> X HistoryDB
updateHistory X HistoryDB -> (HistoryDB -> X ()) -> X ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HistoryDB -> X ()
forall a (m :: * -> *). (ExtensionClass a, XLike m) => a -> m ()
XS.put
updateHistory :: HistoryDB -> X HistoryDB
updateHistory :: HistoryDB -> X HistoryDB
updateHistory (HistoryDB Maybe Window
oldcur Seq Window
oldhist) = (WindowSet -> X HistoryDB) -> X HistoryDB
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X HistoryDB) -> X HistoryDB)
-> (WindowSet -> X HistoryDB) -> X HistoryDB
forall a b. (a -> b) -> a -> b
$ \WindowSet
ss -> do
let newcur :: Maybe Window
newcur = WindowSet -> Maybe Window
forall i l a s sd. StackSet i l a s sd -> Maybe a
SS.peek WindowSet
ss
wins :: Set Window
wins = [Window] -> Set Window
forall a. Ord a => [a] -> Set a
Set.fromList ([Window] -> Set Window) -> [Window] -> Set Window
forall a b. (a -> b) -> a -> b
$ WindowSet -> [Window]
forall a i l s sd. Eq a => StackSet i l a s sd -> [a]
SS.allWindows WindowSet
ss
newhist :: Seq Window
newhist = (Window -> Bool) -> Seq Window -> Seq Window
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.filter (Window -> Set Window -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Window
wins) (Maybe Window -> Seq Window -> Seq Window
forall a. Maybe a -> Seq a -> Seq a
ins Maybe Window
oldcur Seq Window
oldhist)
HistoryDB -> X HistoryDB
forall (m :: * -> *) a. Monad m => a -> m a
return (HistoryDB -> X HistoryDB) -> HistoryDB -> X HistoryDB
forall a b. (a -> b) -> a -> b
$ Maybe Window -> Seq Window -> HistoryDB
HistoryDB Maybe Window
newcur (Maybe Window -> Seq Window -> Seq Window
forall a. Eq a => Maybe a -> Seq a -> Seq a
del Maybe Window
newcur Seq Window
newhist)
where
ins :: Maybe a -> Seq a -> Seq a
ins Maybe a
x Seq a
xs = Seq a -> (a -> Seq a) -> Maybe a -> Seq a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seq a
xs (a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
<| Seq a
xs) Maybe a
x
del :: Maybe a -> Seq a -> Seq a
del Maybe a
x Seq a
xs = Seq a -> (a -> Seq a) -> Maybe a -> Seq a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seq a
xs (\a
x' -> (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.filter (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
x') Seq a
xs) Maybe a
x
rotate :: Seq a -> Seq a
rotate :: Seq a -> Seq a
rotate Seq a
xs = ViewL a -> Seq a
forall a. ViewL a -> Seq a
rotate' (Seq a -> ViewL a
forall a. Seq a -> ViewL a
viewl Seq a
xs)
where
rotate' :: ViewL a -> Seq a
rotate' ViewL a
EmptyL = Seq a
forall a. Seq a
Seq.empty
rotate' (a
x' :< Seq a
xs') = Seq a
xs' Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
|> a
x'
rotateTo :: (a -> Bool) -> Seq a -> Seq a
rotateTo :: (a -> Bool) -> Seq a -> Seq a
rotateTo a -> Bool
cond Seq a
xs = let (Seq a
lxs, Seq a
rxs) = (a -> Bool) -> Seq a -> (Seq a, Seq a)
forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
Seq.breakl a -> Bool
cond Seq a
xs in Seq a
rxs Seq a -> Seq a -> Seq a
forall a. Seq a -> Seq a -> Seq a
>< Seq a
lxs
findM :: Monad m => (a -> m Bool) -> Seq a -> m (Maybe a)
findM :: (a -> m Bool) -> Seq a -> m (Maybe a)
findM a -> m Bool
cond Seq a
xs = (a -> m Bool) -> ViewL a -> m (Maybe a)
forall (m :: * -> *) a.
Monad m =>
(a -> m Bool) -> ViewL a -> m (Maybe a)
findM' a -> m Bool
cond (Seq a -> ViewL a
forall a. Seq a -> ViewL a
viewl Seq a
xs)
where
findM' :: (a -> m Bool) -> ViewL a -> m (Maybe a)
findM' a -> m Bool
_ ViewL a
EmptyL = Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
findM' a -> m Bool
qry (a
x' :< Seq a
xs') = do
Bool
isMatch <- a -> m Bool
qry a
x'
if Bool
isMatch
then Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a
forall a. a -> Maybe a
Just a
x')
else (a -> m Bool) -> Seq a -> m (Maybe a)
forall (m :: * -> *) a.
Monad m =>
(a -> m Bool) -> Seq a -> m (Maybe a)
findM a -> m Bool
qry Seq a
xs'
isOnAnyVisibleWS :: Query Bool
isOnAnyVisibleWS :: Query Bool
isOnAnyVisibleWS = do
Window
w <- Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask
WindowSet
ws <- X WindowSet -> Query WindowSet
forall a. X a -> Query a
liftX (X WindowSet -> Query WindowSet) -> X WindowSet -> Query WindowSet
forall a b. (a -> b) -> a -> b
$ (XState -> WindowSet) -> X WindowSet
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets XState -> WindowSet
windowset
let allVisible :: [Window]
allVisible = [[Window]] -> [Window]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Window]] -> [Window]) -> [[Window]] -> [Window]
forall a b. (a -> b) -> a -> b
$ [Window]
-> (Stack Window -> [Window]) -> Maybe (Stack Window) -> [Window]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Stack Window -> [Window]
forall a. Stack a -> [a]
SS.integrate (Maybe (Stack Window) -> [Window])
-> (Screen String (Layout Window) Window ScreenId ScreenDetail
-> Maybe (Stack Window))
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSpace -> Maybe (Stack Window)
forall i l a. Workspace i l a -> Maybe (Stack a)
SS.stack (WindowSpace -> Maybe (Stack Window))
-> (Screen String (Layout Window) Window ScreenId ScreenDetail
-> WindowSpace)
-> Screen String (Layout Window) Window ScreenId ScreenDetail
-> Maybe (Stack Window)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Screen String (Layout Window) Window ScreenId ScreenDetail
-> WindowSpace
forall i l a sid sd. Screen i l a sid sd -> Workspace i l a
SS.workspace (Screen String (Layout Window) Window ScreenId ScreenDetail
-> [Window])
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [[Window]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WindowSet
-> Screen String (Layout Window) Window ScreenId ScreenDetail
forall i l a sid sd. StackSet i l a sid sd -> Screen i l a sid sd
SS.current WindowSet
wsScreen String (Layout Window) Window ScreenId ScreenDetail
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall a. a -> [a] -> [a]
:WindowSet
-> [Screen String (Layout Window) Window ScreenId ScreenDetail]
forall i l a sid sd. StackSet i l a sid sd -> [Screen i l a sid sd]
SS.visible WindowSet
ws
visibleWs :: Bool
visibleWs = Window
w Window -> [Window] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Window]
allVisible
unfocused :: Bool
unfocused = Window -> Maybe Window
forall a. a -> Maybe a
Just Window
w Maybe Window -> Maybe Window -> Bool
forall a. Eq a => a -> a -> Bool
/= WindowSet -> Maybe Window
forall i l a s sd. StackSet i l a s sd -> Maybe a
SS.peek WindowSet
ws
Bool -> Query Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Query Bool) -> Bool -> Query Bool
forall a b. (a -> b) -> a -> b
$ Bool
visibleWs Bool -> Bool -> Bool
&& Bool
unfocused