aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks
diff options
context:
space:
mode:
authorJesper Reenberg <jesper.reenberg@gmail.com>2012-03-29 16:18:18 +0200
committerJesper Reenberg <jesper.reenberg@gmail.com>2012-03-29 16:18:18 +0200
commit07546e62d563a36d6396672182312392486c7203 (patch)
tree3ba7adccbbb51da401ebbf5901e3943647b7dc95 /XMonad/Hooks
parent0bbab45981d086e205a76d715555fbfcfbf3b038 (diff)
downloadXMonadContrib-07546e62d563a36d6396672182312392486c7203.tar.gz
XMonadContrib-07546e62d563a36d6396672182312392486c7203.tar.xz
XMonadContrib-07546e62d563a36d6396672182312392486c7203.zip
Added isUnfocusedOnCurrentWS and fadeInactiveCurrentWSLogHook for better support of fading/opacity on multi monitor setups
Ignore-this: d001a8aafbcdedae21ccd1d18f019185 darcs-hash:20120329141818-abfbf-4f0fac861df397ce6cb97fe10a3a7a4f9dd0e416.gz
Diffstat (limited to 'XMonad/Hooks')
-rw-r--r--XMonad/Hooks/FadeInactive.hs33
1 files changed, 27 insertions, 6 deletions
diff --git a/XMonad/Hooks/FadeInactive.hs b/XMonad/Hooks/FadeInactive.hs
index 64590d4..71a6fcd 100644
--- a/XMonad/Hooks/FadeInactive.hs
+++ b/XMonad/Hooks/FadeInactive.hs
@@ -17,10 +17,12 @@ module XMonad.Hooks.FadeInactive (
-- $usage
setOpacity,
isUnfocused,
+ isUnfocusedOnCurrentWS,
fadeIn,
fadeOut,
fadeIf,
fadeInactiveLogHook,
+ fadeInactiveCurrentWSLogHook,
fadeOutLogHook
) where
@@ -58,18 +60,18 @@ rationalToOpacity perc
| perc < 0 || perc > 1 = round perc -- to maintain backwards-compatability
| otherwise = round $ perc * 0xffffffff
--- | sets the opacity of a window
+-- | Sets the opacity of a window
setOpacity :: Window -> Rational -> X ()
setOpacity w t = withDisplay $ \dpy -> do
a <- getAtom "_NET_WM_WINDOW_OPACITY"
c <- getAtom "CARDINAL"
io $ changeProperty32 dpy w a c propModeReplace [rationalToOpacity t]
--- | fades a window out by setting the opacity
+-- | Fades a window out by setting the opacity
fadeOut :: Rational -> Window -> X ()
fadeOut = flip setOpacity
--- | makes a window completely opaque
+-- | Makes a window completely opaque
fadeIn :: Window -> X ()
fadeIn = fadeOut 1
@@ -78,15 +80,34 @@ fadeIn = fadeOut 1
fadeIf :: Query Bool -> Rational -> Query Rational
fadeIf qry amt = qry >>= \b -> return $ if b then amt else 1
--- | sets the opacity of inactive windows to the specified amount
+-- | Sets the opacity of inactive windows to the specified amount
fadeInactiveLogHook :: Rational -> X ()
fadeInactiveLogHook = fadeOutLogHook . fadeIf isUnfocused
--- | returns True if the window doesn't have the focus.
+-- | Set the opacity of inactive windows, on the current workspace, to the
+-- specified amount. This is specifically usefull in a multi monitor setup. See
+-- 'isUnfocusedOnCurrentWS'.
+fadeInactiveCurrentWSLogHook :: Rational -> X ()
+fadeInactiveCurrentWSLogHook = fadeOutLogHook . fadeIf isUnfocusedOnCurrentWS
+
+-- | Returns True if the window doesn't have the focus.
isUnfocused :: Query Bool
isUnfocused = ask >>= \w -> liftX . gets $ maybe True (w /=) . W.peek . windowset
--- | fades out every window by the amount returned by the query.
+-- | Returns True if the window doesn't have the focus, and the window is on the
+-- current workspace. This is specifically handy in a multi monitor setup
+-- (xinerama) where multiple workspaces are visible. Using this, non-focused
+-- workspaces are are not faded out making it easier to look and read the
+-- content on them.
+isUnfocusedOnCurrentWS :: Query Bool
+isUnfocusedOnCurrentWS = do
+ w <- ask
+ ws <- liftX $ gets windowset
+ let thisWS = w `elem` W.index ws
+ unfocused = maybe True (w /=) $ W.peek ws
+ return $ thisWS && unfocused
+
+-- | Fades out every window by the amount returned by the query.
fadeOutLogHook :: Query Rational -> X ()
fadeOutLogHook qry = withWindowSet $ \s -> do
let visibleWins = (W.integrate' . W.stack . W.workspace . W.current $ s) ++