{-# LANGUAGE LambdaCase #-}
-----------------------------------------------------------------------------
-- |
-- Module       : XMonad.Hooks.ManageHelpers
-- Description  : Helper functions to be used in manageHook.
-- Copyright    : (c) Lukas Mai
-- License      : BSD
--
-- Maintainer   : Lukas Mai <l.mai@web.de>
-- Stability    : unstable
-- Portability  : unportable
--
-- This module provides helper functions to be used in @manageHook@. Here's
-- how you might use this:
--
-- > import XMonad.Hooks.ManageHelpers
-- > main =
-- >     xmonad def{
-- >         ...
-- >         manageHook = composeOne [
-- >             isKDETrayWindow -?> doIgnore,
-- >             transience,
-- >             isFullscreen -?> doFullFloat,
-- >             resource =? "stalonetray" -?> doIgnore
-- >         ],
-- >         ...
-- >     }
--
-- Here's how you can define more helpers like the ones from this module:
--
-- > -- some function you want to transform into an infix operator
-- > f :: a -> b -> Bool
-- >
-- > -- a new helper
-- > q ***? x = fmap (\a -> f a x) q
-- > -- or
-- > q ***? x = fmap (`f` x) q
--
-- Any existing operator can be "lifted" in the same way:
--
-- > q ++? x = fmap (++ x) q

module XMonad.Hooks.ManageHelpers (
    Side(..),
    composeOne,
    (-?>), (/=?), (^?), (~?), ($?), (<==?), (</=?), (-->>), (-?>>),
    currentWs,
    windowTag,
    isInProperty,
    isKDETrayWindow,
    isFullscreen,
    isDialog,
    pid,
    transientTo,
    maybeToDefinite,
    MaybeManageHook,
    transience,
    transience',
    clientLeader,
    sameBy,
    shiftToSame,
    shiftToSame',
    doRectFloat,
    doFullFloat,
    doCenterFloat,
    doSideFloat,
    doFloatAt,
    doFloatDep,
    doHideIgnore,
    doSink,
    doLower,
    doRaise,
    doFocus,
    Match,
) where

import XMonad
import XMonad.Prelude
import qualified XMonad.StackSet as W
import XMonad.Util.WindowProperties (getProp32s)

import System.Posix (ProcessID)

-- | Denotes a side of a screen. @S@ stands for South, @NE@ for Northeast
-- etc. @C@ stands for Center.
data Side = SC | NC | CE | CW | SE | SW | NE | NW | C
    deriving (ReadPrec [Side]
ReadPrec Side
Int -> ReadS Side
ReadS [Side]
(Int -> ReadS Side)
-> ReadS [Side] -> ReadPrec Side -> ReadPrec [Side] -> Read Side
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Side]
$creadListPrec :: ReadPrec [Side]
readPrec :: ReadPrec Side
$creadPrec :: ReadPrec Side
readList :: ReadS [Side]
$creadList :: ReadS [Side]
readsPrec :: Int -> ReadS Side
$creadsPrec :: Int -> ReadS Side
Read, Int -> Side -> ShowS
[Side] -> ShowS
Side -> String
(Int -> Side -> ShowS)
-> (Side -> String) -> ([Side] -> ShowS) -> Show Side
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Side] -> ShowS
$cshowList :: [Side] -> ShowS
show :: Side -> String
$cshow :: Side -> String
showsPrec :: Int -> Side -> ShowS
$cshowsPrec :: Int -> Side -> ShowS
Show, Side -> Side -> Bool
(Side -> Side -> Bool) -> (Side -> Side -> Bool) -> Eq Side
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Side -> Side -> Bool
$c/= :: Side -> Side -> Bool
== :: Side -> Side -> Bool
$c== :: Side -> Side -> Bool
Eq)

-- | A ManageHook that may or may not have been executed; the outcome is embedded in the Maybe
type MaybeManageHook = Query (Maybe (Endo WindowSet))
-- | A grouping type, which can hold the outcome of a predicate Query.
-- This is analogous to group types in regular expressions.
-- TODO: create a better API for aggregating multiple Matches logically
data Match a = Match Bool a

-- | An alternative 'ManageHook' composer. Unlike 'composeAll' it stops as soon as
-- a candidate returns a 'Just' value, effectively running only the first match
-- (whereas 'composeAll' continues and executes all matching rules).
composeOne :: (Monoid a, Monad m) => [m (Maybe a)] -> m a
composeOne :: [m (Maybe a)] -> m a
composeOne = (m (Maybe a) -> m a -> m a) -> m a -> [m (Maybe a)] -> m a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr m (Maybe a) -> m a -> m a
forall (m :: * -> *) b. Monad m => m (Maybe b) -> m b -> m b
try (a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty)
    where
    try :: m (Maybe b) -> m b -> m b
try m (Maybe b)
q m b
z = do
        Maybe b
x <- m (Maybe b)
q
        m b -> (b -> m b) -> Maybe b -> m b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m b
z b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe b
x

infixr 0 -?>, -->>, -?>>

-- | q \/=? x. if the result of q equals x, return False
(/=?) :: (Eq a, Functor m) => m a -> a -> m Bool
m a
q /=? :: m a -> a -> m Bool
/=? a
x = (a -> Bool) -> m a -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
x) m a
q

-- | q ^? x. if the result of q 'isPrefixOf' x, return True
(^?) :: (Eq a, Functor m) => m [a] -> [a] -> m Bool
m [a]
q ^? :: m [a] -> [a] -> m Bool
^? [a]
x = ([a] -> Bool) -> m [a] -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [a]
x) m [a]
q

-- | q ~? x. if the result of q 'isSuffixOf' x, return True
(~?) :: (Eq a, Functor m) => m [a] -> [a] -> m Bool
m [a]
q ~? :: m [a] -> [a] -> m Bool
~? [a]
x = ([a] -> Bool) -> m [a] -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` [a]
x) m [a]
q

-- | q $? x. if the result of q 'isSuffixOf' x, return True
($?) :: (Eq a, Functor m) => m [a] -> [a] -> m Bool
m [a]
q $? :: m [a] -> [a] -> m Bool
$? [a]
x = ([a] -> Bool) -> m [a] -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([a] -> [a] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` [a]
x) m [a]
q

-- | q <==? x. if the result of q equals x, return True grouped with q
(<==?) :: (Eq a, Functor m) => m a -> a -> m (Match a)
m a
q <==? :: m a -> a -> m (Match a)
<==? a
x = (a -> Match a) -> m a -> m (Match a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> a -> Match a
forall a. Eq a => a -> a -> Match a
`eq` a
x) m a
q
    where
    eq :: a -> a -> Match a
eq a
q' a
x' = Bool -> a -> Match a
forall a. Bool -> a -> Match a
Match (a
q' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x') a
q'

-- | q <\/=? x. if the result of q notequals x, return True grouped with q
(</=?) :: (Eq a, Functor m) => m a -> a -> m (Match a)
m a
q </=? :: m a -> a -> m (Match a)
</=? a
x = (a -> Match a) -> m a -> m (Match a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> a -> Match a
forall a. Eq a => a -> a -> Match a
`neq` a
x) m a
q
    where
    neq :: a -> a -> Match a
neq a
q' a
x' = Bool -> a -> Match a
forall a. Bool -> a -> Match a
Match (a
q' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
x') a
q'

-- | A helper operator for use in 'composeOne'. It takes a condition and an action;
-- if the condition fails, it returns 'Nothing' from the 'Query' so 'composeOne' will
-- go on and try the next rule.
(-?>) :: (Functor m, Monad m) => m Bool -> m a -> m (Maybe a)
m Bool
p -?> :: m Bool -> m a -> m (Maybe a)
-?> m a
f = do
    Bool
x <- m Bool
p
    if Bool
x then (a -> Maybe a) -> m a -> m (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe a
forall a. a -> Maybe a
Just m a
f else Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing

-- | A helper operator for use in 'composeAll'. It takes a condition and a function taking a grouped datum to action.  If 'p' is true, it executes the resulting action.
(-->>) :: (Monoid b, Monad m) => m (Match a) -> (a -> m b) -> m b
m (Match a)
p -->> :: m (Match a) -> (a -> m b) -> m b
-->> a -> m b
f = do
    Match Bool
b a
m <- m (Match a)
p
    if Bool
b then a -> m b
f a
m else b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
forall a. Monoid a => a
mempty

-- | A helper operator for use in 'composeOne'.  It takes a condition and a function taking a groupdatum to action.  If 'p' is true, it executes the resulting action.  If it fails, it returns 'Nothing' from the 'Query' so 'composeOne' will go on and try the next rule.
(-?>>) :: (Functor m, Monad m) => m (Match a) -> (a -> m b) -> m (Maybe b)
m (Match a)
p -?>> :: m (Match a) -> (a -> m b) -> m (Maybe b)
-?>> a -> m b
f = do
    Match Bool
b a
m <- m (Match a)
p
    if Bool
b then (b -> Maybe b) -> m b -> m (Maybe b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap  b -> Maybe b
forall a. a -> Maybe a
Just (a -> m b
f a
m) else Maybe b -> m (Maybe b)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe b
forall a. Maybe a
Nothing

-- | Return the current workspace
currentWs :: Query WorkspaceId
currentWs :: Query String
currentWs = X String -> Query String
forall a. X a -> Query a
liftX ((WindowSet -> X String) -> X String
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X String) -> X String)
-> (WindowSet -> X String) -> X String
forall a b. (a -> b) -> a -> b
$ String -> X String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> X String)
-> (WindowSet -> String) -> WindowSet -> X String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSet -> String
forall i l a s sd. StackSet i l a s sd -> i
W.currentTag)

-- | Return the workspace tag of a window, if already managed
windowTag :: Query (Maybe WorkspaceId)
windowTag :: Query (Maybe String)
windowTag = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Maybe String)) -> Query (Maybe String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X (Maybe String) -> Query (Maybe String)
forall a. X a -> Query a
liftX (X (Maybe String) -> Query (Maybe String))
-> X (Maybe String) -> Query (Maybe String)
forall a b. (a -> b) -> a -> b
$ (WindowSet -> X (Maybe String)) -> X (Maybe String)
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X (Maybe String)) -> X (Maybe String))
-> (WindowSet -> X (Maybe String)) -> X (Maybe String)
forall a b. (a -> b) -> a -> b
$ Maybe String -> X (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String -> X (Maybe String))
-> (WindowSet -> Maybe String) -> WindowSet -> X (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> Maybe String
forall a i l s sd. Eq a => a -> StackSet i l a s sd -> Maybe i
W.findTag Window
w

-- | A predicate to check whether a window is a KDE system tray icon.
isKDETrayWindow :: Query Bool
isKDETrayWindow :: Query Bool
isKDETrayWindow = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window -> (Window -> Query Bool) -> Query Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X Bool -> Query Bool
forall a. X a -> Query a
liftX (X Bool -> Query Bool) -> X Bool -> Query Bool
forall a b. (a -> b) -> a -> b
$ do
    Maybe [CLong]
r <- String -> Window -> X (Maybe [CLong])
getProp32s String
"_KDE_NET_WM_SYSTEM_TRAY_WINDOW_FOR" Window
w
    Bool -> X Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> X Bool) -> Bool -> X Bool
forall a b. (a -> b) -> a -> b
$ case Maybe [CLong]
r of
        Just [CLong
_] -> Bool
True
        Maybe [CLong]
_ -> Bool
False

-- | Helper to check if a window property contains certain value.
isInProperty :: String -> String -> Query Bool
isInProperty :: String -> String -> Query Bool
isInProperty String
p String
v = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window -> (Window -> Query Bool) -> Query Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X Bool -> Query Bool
forall a. X a -> Query a
liftX (X Bool -> Query Bool) -> X Bool -> Query Bool
forall a b. (a -> b) -> a -> b
$ do
    Window
va <- String -> X Window
getAtom String
v
    Maybe [CLong]
r <- String -> Window -> X (Maybe [CLong])
getProp32s String
p Window
w
    Bool -> X Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> X Bool) -> Bool -> X Bool
forall a b. (a -> b) -> a -> b
$ case Maybe [CLong]
r of
        Just [CLong]
xs -> Window -> CLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Window
va CLong -> [CLong] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [CLong]
xs
        Maybe [CLong]
_ -> Bool
False

-- | A predicate to check whether a window wants to fill the whole screen.
-- See also 'doFullFloat'.
isFullscreen :: Query Bool
isFullscreen :: Query Bool
isFullscreen = String -> String -> Query Bool
isInProperty String
"_NET_WM_STATE" String
"_NET_WM_STATE_FULLSCREEN"

-- | A predicate to check whether a window is a dialog.
isDialog :: Query Bool
isDialog :: Query Bool
isDialog = String -> String -> Query Bool
isInProperty String
"_NET_WM_WINDOW_TYPE" String
"_NET_WM_WINDOW_TYPE_DIALOG"

-- | This function returns 'Just' the @_NET_WM_PID@ property for a
-- particular window if set, 'Nothing' otherwise.
--
-- See <https://specifications.freedesktop.org/wm-spec/wm-spec-1.5.html#idm45623487788432>.
pid :: Query (Maybe ProcessID)
pid :: Query (Maybe ProcessID)
pid = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Maybe ProcessID)) -> Query (Maybe ProcessID)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X (Maybe ProcessID) -> Query (Maybe ProcessID)
forall a. X a -> Query a
liftX (X (Maybe ProcessID) -> Query (Maybe ProcessID))
-> X (Maybe ProcessID) -> Query (Maybe ProcessID)
forall a b. (a -> b) -> a -> b
$ String -> Window -> X (Maybe [CLong])
getProp32s String
"_NET_WM_PID" Window
w X (Maybe [CLong])
-> (Maybe [CLong] -> Maybe ProcessID) -> X (Maybe ProcessID)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
    Just [CLong
x] -> ProcessID -> Maybe ProcessID
forall a. a -> Maybe a
Just (CLong -> ProcessID
forall a b. (Integral a, Num b) => a -> b
fromIntegral CLong
x)
    Maybe [CLong]
_        -> Maybe ProcessID
forall a. Maybe a
Nothing

-- | A predicate to check whether a window is Transient.
-- It holds the result which might be the window it is transient to
-- or it might be 'Nothing'.
transientTo :: Query (Maybe Window)
transientTo :: Query (Maybe Window)
transientTo = do
    Window
w <- Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask
    Display
d <- (X Display -> Query Display
forall a. X a -> Query a
liftX (X Display -> Query Display)
-> ((XConf -> Display) -> X Display)
-> (XConf -> Display)
-> Query Display
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (XConf -> Display) -> X Display
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks) XConf -> Display
display
    IO (Maybe Window) -> Query (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> Query (Maybe Window))
-> IO (Maybe Window) -> Query (Maybe Window)
forall a b. (a -> b) -> a -> b
$ Display -> Window -> IO (Maybe Window)
getTransientForHint Display
d Window
w

-- | A convenience 'MaybeManageHook' that will check to see if a window
-- is transient, and then move it to its parent.
transience :: MaybeManageHook
transience :: MaybeManageHook
transience = Query (Maybe Window)
transientTo Query (Maybe Window)
-> Maybe Window -> Query (Match (Maybe Window))
forall a (m :: * -> *).
(Eq a, Functor m) =>
m a -> a -> m (Match a)
</=? Maybe Window
forall a. Maybe a
Nothing Query (Match (Maybe Window))
-> (Maybe Window -> Query (Endo WindowSet)) -> MaybeManageHook
forall (m :: * -> *) a b.
(Functor m, Monad m) =>
m (Match a) -> (a -> m b) -> m (Maybe b)
-?>> Query (Endo WindowSet)
-> (Window -> Query (Endo WindowSet))
-> Maybe Window
-> Query (Endo WindowSet)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Query (Endo WindowSet)
forall a. Monoid a => a
idHook Window -> Query (Endo WindowSet)
doShiftTo

-- | 'transience' set to a 'ManageHook'
transience' :: ManageHook
transience' :: Query (Endo WindowSet)
transience' = MaybeManageHook -> Query (Endo WindowSet)
forall a (m :: * -> *). (Monoid a, Functor m) => m (Maybe a) -> m a
maybeToDefinite MaybeManageHook
transience

-- | This function returns 'Just' the @WM_CLIENT_LEADER@ property for a
-- particular window if set, 'Nothing' otherwise. Note that, generally,
-- the window ID returned from this property (by firefox, for example)
-- corresponds to an unmapped or unmanaged dummy window. For this to be
-- useful in most cases, it should be used together with 'sameBy'.
--
-- See <https://tronche.com/gui/x/icccm/sec-5.html>.
clientLeader :: Query (Maybe Window)
clientLeader :: Query (Maybe Window)
clientLeader = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Maybe Window)) -> Query (Maybe Window)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X (Maybe Window) -> Query (Maybe Window)
forall a. X a -> Query a
liftX (X (Maybe Window) -> Query (Maybe Window))
-> X (Maybe Window) -> Query (Maybe Window)
forall a b. (a -> b) -> a -> b
$ String -> Window -> X (Maybe [CLong])
getProp32s String
"WM_CLIENT_LEADER" Window
w X (Maybe [CLong])
-> (Maybe [CLong] -> Maybe Window) -> X (Maybe Window)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
    Just [CLong
x] -> Window -> Maybe Window
forall a. a -> Maybe a
Just (CLong -> Window
forall a b. (Integral a, Num b) => a -> b
fromIntegral CLong
x)
    Maybe [CLong]
_        -> Maybe Window
forall a. Maybe a
Nothing

-- | For a given window, 'sameBy' returns all windows that have a matching
-- property (e.g. those obtained from Queries of 'clientLeader' and 'pid').
sameBy :: Eq prop => Query (Maybe prop) -> Query [Window]
sameBy :: Query (Maybe prop) -> Query [Window]
sameBy Query (Maybe prop)
prop = Query (Maybe prop)
prop Query (Maybe prop)
-> (Maybe prop -> Query [Window]) -> Query [Window]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Maybe prop
Nothing -> [Window] -> Query [Window]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
    Maybe prop
propVal -> Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window -> (Window -> Query [Window]) -> Query [Window]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X [Window] -> Query [Window]
forall a. X a -> Query a
liftX (X [Window] -> Query [Window])
-> ((WindowSet -> X [Window]) -> X [Window])
-> (WindowSet -> X [Window])
-> Query [Window]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WindowSet -> X [Window]) -> X [Window]
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X [Window]) -> Query [Window])
-> (WindowSet -> X [Window]) -> Query [Window]
forall a b. (a -> b) -> a -> b
$ \WindowSet
s ->
        (Window -> X Bool) -> [Window] -> X [Window]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM ((Maybe prop -> Bool) -> X (Maybe prop) -> X Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe prop
propVal Maybe prop -> Maybe prop -> Bool
forall a. Eq a => a -> a -> Bool
==) (X (Maybe prop) -> X Bool)
-> (Window -> X (Maybe prop)) -> Window -> X Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query (Maybe prop) -> Window -> X (Maybe prop)
forall a. Query a -> Window -> X a
runQuery Query (Maybe prop)
prop) (WindowSet -> [Window]
forall a i l s sd. Eq a => StackSet i l a s sd -> [a]
W.allWindows WindowSet
s [Window] -> [Window] -> [Window]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Window
w])

-- | 'MaybeManageHook' that moves the window to the same workspace as the
-- first other window that has the same value of a given 'Query'. Useful
-- Queries for this include 'clientLeader' and 'pid'.
shiftToSame :: Eq prop => Query (Maybe prop) -> MaybeManageHook
shiftToSame :: Query (Maybe prop) -> MaybeManageHook
shiftToSame Query (Maybe prop)
prop = Query (Maybe prop) -> Query [Window]
forall prop. Eq prop => Query (Maybe prop) -> Query [Window]
sameBy Query (Maybe prop)
prop Query [Window] -> [Window] -> Query (Match [Window])
forall a (m :: * -> *).
(Eq a, Functor m) =>
m a -> a -> m (Match a)
</=? [] Query (Match [Window])
-> ([Window] -> Query (Endo WindowSet)) -> MaybeManageHook
forall (m :: * -> *) a b.
(Functor m, Monad m) =>
m (Match a) -> (a -> m b) -> m (Maybe b)
-?>> Query (Endo WindowSet)
-> (Window -> Query (Endo WindowSet))
-> Maybe Window
-> Query (Endo WindowSet)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Query (Endo WindowSet)
forall a. Monoid a => a
idHook Window -> Query (Endo WindowSet)
doShiftTo (Maybe Window -> Query (Endo WindowSet))
-> ([Window] -> Maybe Window) -> [Window] -> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Window] -> Maybe Window
forall a. [a] -> Maybe a
listToMaybe

-- | 'shiftToSame' set to a 'ManageHook'
shiftToSame' :: Eq prop => Query (Maybe prop) -> ManageHook
shiftToSame' :: Query (Maybe prop) -> Query (Endo WindowSet)
shiftToSame' = MaybeManageHook -> Query (Endo WindowSet)
forall a (m :: * -> *). (Monoid a, Functor m) => m (Maybe a) -> m a
maybeToDefinite (MaybeManageHook -> Query (Endo WindowSet))
-> (Query (Maybe prop) -> MaybeManageHook)
-> Query (Maybe prop)
-> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query (Maybe prop) -> MaybeManageHook
forall prop. Eq prop => Query (Maybe prop) -> MaybeManageHook
shiftToSame

-- | converts 'MaybeManageHook's to 'ManageHook's
maybeToDefinite :: (Monoid a, Functor m) => m (Maybe a) -> m a
maybeToDefinite :: m (Maybe a) -> m a
maybeToDefinite = (Maybe a -> a) -> m (Maybe a) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
forall a. Monoid a => a
mempty)

-- | Move the window to the same workspace as another window.
doShiftTo :: Window -> ManageHook
doShiftTo :: Window -> Query (Endo WindowSet)
doShiftTo Window
target = (WindowSet -> WindowSet) -> Query (Endo WindowSet)
forall s. (s -> s) -> Query (Endo s)
doF ((WindowSet -> WindowSet) -> Query (Endo WindowSet))
-> (Window -> WindowSet -> WindowSet)
-> Window
-> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> WindowSet
forall s i l sd.
(Eq s, Eq i) =>
Window -> StackSet i l Window s sd -> StackSet i l Window s sd
shiftTo (Window -> Query (Endo WindowSet))
-> Query Window -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask
  where shiftTo :: Window -> StackSet i l Window s sd -> StackSet i l Window s sd
shiftTo Window
w StackSet i l Window s sd
s = StackSet i l Window s sd
-> (i -> StackSet i l Window s sd)
-> Maybe i
-> StackSet i l Window s sd
forall b a. b -> (a -> b) -> Maybe a -> b
maybe StackSet i l Window s sd
s (\i
t -> i -> Window -> StackSet i l Window s sd -> StackSet i l Window s sd
forall a s i l sd.
(Ord a, Eq s, Eq i) =>
i -> a -> StackSet i l a s sd -> StackSet i l a s sd
W.shiftWin i
t Window
w StackSet i l Window s sd
s) (Window -> StackSet i l Window s sd -> Maybe i
forall a i l s sd. Eq a => a -> StackSet i l a s sd -> Maybe i
W.findTag Window
target StackSet i l Window s sd
s)

-- | Floats the new window in the given rectangle.
doRectFloat :: W.RationalRect  -- ^ The rectangle to float the window in. 0 to 1; x, y, w, h.
            -> ManageHook
doRectFloat :: RationalRect -> Query (Endo WindowSet)
doRectFloat RationalRect
r = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> (WindowSet -> WindowSet) -> Query (Endo WindowSet)
forall s. (s -> s) -> Query (Endo s)
doF (Window -> RationalRect -> WindowSet -> WindowSet
forall a i l s sd.
Ord a =>
a -> RationalRect -> StackSet i l a s sd -> StackSet i l a s sd
W.float Window
w RationalRect
r)

-- | Floats the window and makes it use the whole screen. Equivalent to
-- @'doRectFloat' $ 'W.RationalRect' 0 0 1 1@.
doFullFloat :: ManageHook
doFullFloat :: Query (Endo WindowSet)
doFullFloat = RationalRect -> Query (Endo WindowSet)
doRectFloat (RationalRect -> Query (Endo WindowSet))
-> RationalRect -> Query (Endo WindowSet)
forall a b. (a -> b) -> a -> b
$ Rational -> Rational -> Rational -> Rational -> RationalRect
W.RationalRect Rational
0 Rational
0 Rational
1 Rational
1

-- | Floats a new window using a rectangle computed as a function of
--   the rectangle that it would have used by default.
doFloatDep :: (W.RationalRect -> W.RationalRect) -> ManageHook
doFloatDep :: (RationalRect -> RationalRect) -> Query (Endo WindowSet)
doFloatDep RationalRect -> RationalRect
move = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> (WindowSet -> WindowSet) -> Query (Endo WindowSet)
forall s. (s -> s) -> Query (Endo s)
doF ((WindowSet -> WindowSet) -> Query (Endo WindowSet))
-> ((ScreenId, RationalRect) -> WindowSet -> WindowSet)
-> (ScreenId, RationalRect)
-> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> RationalRect -> WindowSet -> WindowSet
forall a i l s sd.
Ord a =>
a -> RationalRect -> StackSet i l a s sd -> StackSet i l a s sd
W.float Window
w (RationalRect -> WindowSet -> WindowSet)
-> ((ScreenId, RationalRect) -> RationalRect)
-> (ScreenId, RationalRect)
-> WindowSet
-> WindowSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RationalRect -> RationalRect
move (RationalRect -> RationalRect)
-> ((ScreenId, RationalRect) -> RationalRect)
-> (ScreenId, RationalRect)
-> RationalRect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScreenId, RationalRect) -> RationalRect
forall a b. (a, b) -> b
snd ((ScreenId, RationalRect) -> Query (Endo WindowSet))
-> Query (ScreenId, RationalRect) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< X (ScreenId, RationalRect) -> Query (ScreenId, RationalRect)
forall a. X a -> Query a
liftX (Window -> X (ScreenId, RationalRect)
floatLocation Window
w)

-- | Floats a new window with its original size, and its top left
--   corner at a specific point on the screen (both coordinates should
--   be in the range 0 to 1).
doFloatAt :: Rational -> Rational -> ManageHook
doFloatAt :: Rational -> Rational -> Query (Endo WindowSet)
doFloatAt Rational
x Rational
y = (RationalRect -> RationalRect) -> Query (Endo WindowSet)
doFloatDep RationalRect -> RationalRect
move
  where
    move :: RationalRect -> RationalRect
move (W.RationalRect Rational
_ Rational
_ Rational
w Rational
h) = Rational -> Rational -> Rational -> Rational -> RationalRect
W.RationalRect Rational
x Rational
y Rational
w Rational
h

-- | Floats a new window with its original size on the specified side of a
-- screen
doSideFloat :: Side -> ManageHook
doSideFloat :: Side -> Query (Endo WindowSet)
doSideFloat Side
side = (RationalRect -> RationalRect) -> Query (Endo WindowSet)
doFloatDep RationalRect -> RationalRect
move
  where
    move :: RationalRect -> RationalRect
move (W.RationalRect Rational
_ Rational
_ Rational
w Rational
h) = Rational -> Rational -> Rational -> Rational -> RationalRect
W.RationalRect Rational
cx Rational
cy Rational
w Rational
h
      where cx :: Rational
cx
              | Side
side Side -> [Side] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Side
SC,Side
C ,Side
NC] = (Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
-Rational
w)Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
2
              | Side
side Side -> [Side] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Side
SW,Side
CW,Side
NW] = Rational
0
              | Bool
otherwise = {- side `elem` [SE,CE,NE] -} Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
-Rational
w
            cy :: Rational
cy
              | Side
side Side -> [Side] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Side
CE,Side
C ,Side
CW] = (Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
-Rational
h)Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
2
              | Side
side Side -> [Side] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Side
NE,Side
NC,Side
NW] = Rational
0
              | Bool
otherwise = {- side `elem` [SE,SC,SW] -} Rational
1Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
-Rational
h

-- | Floats a new window with its original size, but centered.
doCenterFloat :: ManageHook
doCenterFloat :: Query (Endo WindowSet)
doCenterFloat = Side -> Query (Endo WindowSet)
doSideFloat Side
C

-- | Hides window and ignores it.
doHideIgnore :: ManageHook
doHideIgnore :: Query (Endo WindowSet)
doHideIgnore = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X () -> Query ()
forall a. X a -> Query a
liftX (Window -> X ()
hide Window
w) Query () -> Query (Endo WindowSet) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (WindowSet -> WindowSet) -> Query (Endo WindowSet)
forall s. (s -> s) -> Query (Endo s)
doF (Window -> WindowSet -> WindowSet
forall a i l s sd.
Ord a =>
a -> StackSet i l a s sd -> StackSet i l a s sd
W.delete Window
w)

-- | Sinks a window
doSink :: ManageHook
doSink :: Query (Endo WindowSet)
doSink = (WindowSet -> WindowSet) -> Query (Endo WindowSet)
forall s. (s -> s) -> Query (Endo s)
doF ((WindowSet -> WindowSet) -> Query (Endo WindowSet))
-> (Window -> WindowSet -> WindowSet)
-> Window
-> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> WindowSet
forall a i l s sd.
Ord a =>
a -> StackSet i l a s sd -> StackSet i l a s sd
W.sink (Window -> Query (Endo WindowSet))
-> Query Window -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask

-- | Lower an unmanaged window. Useful together with 'doIgnore' to lower
-- special windows that for some reason don't do it themselves.
doLower :: ManageHook
doLower :: Query (Endo WindowSet)
doLower = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X (Endo WindowSet) -> Query (Endo WindowSet)
forall a. X a -> Query a
liftX (X (Endo WindowSet) -> Query (Endo WindowSet))
-> X (Endo WindowSet) -> Query (Endo WindowSet)
forall a b. (a -> b) -> a -> b
$ (Display -> X (Endo WindowSet)) -> X (Endo WindowSet)
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X (Endo WindowSet)) -> X (Endo WindowSet))
-> (Display -> X (Endo WindowSet)) -> X (Endo WindowSet)
forall a b. (a -> b) -> a -> b
$ \Display
dpy -> IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (Display -> Window -> IO ()
lowerWindow Display
dpy Window
w) X () -> X (Endo WindowSet) -> X (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> X (Endo WindowSet)
forall a. Monoid a => a
mempty

-- | Raise an unmanaged window. Useful together with 'doIgnore' to raise
-- special windows that for some reason don't do it themselves.
doRaise :: ManageHook
doRaise :: Query (Endo WindowSet)
doRaise = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Window
w -> X (Endo WindowSet) -> Query (Endo WindowSet)
forall a. X a -> Query a
liftX (X (Endo WindowSet) -> Query (Endo WindowSet))
-> X (Endo WindowSet) -> Query (Endo WindowSet)
forall a b. (a -> b) -> a -> b
$ (Display -> X (Endo WindowSet)) -> X (Endo WindowSet)
forall a. (Display -> X a) -> X a
withDisplay ((Display -> X (Endo WindowSet)) -> X (Endo WindowSet))
-> (Display -> X (Endo WindowSet)) -> X (Endo WindowSet)
forall a b. (a -> b) -> a -> b
$ \Display
dpy -> IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (Display -> Window -> IO ()
raiseWindow Display
dpy Window
w) X () -> X (Endo WindowSet) -> X (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> X (Endo WindowSet)
forall a. Monoid a => a
mempty

-- | Focus a window (useful in 'XMonad.Hooks.EwmhDesktops.setActivateHook').
doFocus :: ManageHook
doFocus :: Query (Endo WindowSet)
doFocus = (WindowSet -> WindowSet) -> Query (Endo WindowSet)
forall s. (s -> s) -> Query (Endo s)
doF ((WindowSet -> WindowSet) -> Query (Endo WindowSet))
-> (Window -> WindowSet -> WindowSet)
-> Window
-> Query (Endo WindowSet)
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
W.focusWindow (Window -> Query (Endo WindowSet))
-> Query Window -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask