More flexible interface for X.H.FadeInactive

This patch allows setting the opacity on a per-window basis and lets the
user specify it as a percentage instead of an Integer between 0 and 2^32-1.
This commit is contained in:
Daniel Schoepe 2009-08-21 20:39:36 +00:00
parent cc2fb2c10d
commit 8fe80758a8
2 changed files with 39 additions and 35 deletions

View File

@ -19,6 +19,7 @@ module XMonad.Hooks.FadeInactive (
isUnfocused, isUnfocused,
fadeIn, fadeIn,
fadeOut, fadeOut,
fadeIf,
fadeInactiveLogHook, fadeInactiveLogHook,
fadeOutLogHook fadeOutLogHook
) where ) where
@ -35,11 +36,11 @@ import Control.Monad
-- > -- >
-- > myLogHook :: X () -- > myLogHook :: X ()
-- > myLogHook = fadeInactiveLogHook fadeAmount -- > myLogHook = fadeInactiveLogHook fadeAmount
-- > where fadeAmount = 0xdddddddd -- > where fadeAmount = 0.8
-- > -- >
-- > main = xmonad defaultConfig { logHook = myLogHook } -- > main = xmonad defaultConfig { logHook = myLogHook }
-- --
-- fadeAmount can be any integer -- fadeAmount can be any rational between 0 and 1.
-- you will need to have xcompmgr <http://freedesktop.org/wiki/Software/xapps> -- you will need to have xcompmgr <http://freedesktop.org/wiki/Software/xapps>
-- or something similar for this to do anything -- or something similar for this to do anything
-- --
@ -51,40 +52,43 @@ import Control.Monad
-- --
-- "XMonad.Doc.Extending#Editing_the_layout_hook" -- "XMonad.Doc.Extending#Editing_the_layout_hook"
-- | -- | Converts a percentage to the format required for _NET_WM_WINDOW_OPACITY
-- sets the opacity of a window rationalToOpacity :: Integral a => Rational -> a
setOpacity :: Window -> Integer -> X () rationalToOpacity perc
| perc < 0 || perc > 1 = 0xffffffff -- invalid input, default to opaque
| otherwise = round $ perc * 0xffffffff
-- | sets the opacity of a window
setOpacity :: Window -> Rational -> X ()
setOpacity w t = withDisplay $ \dpy -> do setOpacity w t = withDisplay $ \dpy -> do
a <- getAtom "_NET_WM_WINDOW_OPACITY" a <- getAtom "_NET_WM_WINDOW_OPACITY"
c <- getAtom "CARDINAL" c <- getAtom "CARDINAL"
io $ changeProperty32 dpy w a c propModeReplace [fromIntegral t] 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 :: Integer -> Window -> X () fadeOut = flip setOpacity
fadeOut amt = flip setOpacity amt
-- | -- | makes a window completely opaque
-- makes a window completely opaque
fadeIn :: Window -> X () fadeIn :: Window -> X ()
fadeIn = flip setOpacity 0xffffffff fadeIn = fadeOut 1
-- | -- | Fades a window by the specified amount if it satisfies the first query, otherwise
-- lowers the opacity of inactive windows to the specified amount -- makes it opaque.
fadeInactiveLogHook :: Integer -> X () fadeIf :: Query Bool -> Rational -> Query Rational
fadeInactiveLogHook amt = fadeOutLogHook isUnfocused amt fadeIf qry amt = qry >>= \b -> return $ if b then amt else 1
-- | 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. -- | returns True if the window doesn't have the focus.
isUnfocused :: Window -> X Bool isUnfocused :: Query Bool
isUnfocused w = withWindowSet $ \s -> return $ isUnfocused = ask >>= \w -> liftX . gets $ maybe False (w /=) . W.peek . windowset
case W.stack . W.workspace . W.current $ s of
Nothing -> False
Just stack -> W.focus stack /= w
-- | fades out every window that satisfies a given property. -- | fades out every window by the amount returned by the query.
fadeOutLogHook :: (Window -> X Bool) -> Integer -> X () fadeOutLogHook :: Query Rational -> X ()
fadeOutLogHook p amt = withWindowSet $ \s -> do fadeOutLogHook qry = withWindowSet $ \s -> do
let visibleWins = (W.integrate' . W.stack . W.workspace . W.current $ s) ++ let visibleWins = (W.integrate' . W.stack . W.workspace . W.current $ s) ++
concatMap (W.integrate' . W.stack . W.workspace) (W.visible s) concatMap (W.integrate' . W.stack . W.workspace) (W.visible s)
mapM_ fadeIn =<< filterM (fmap not . p) visibleWins forM_ visibleWins $ liftM2 (=<<) setOpacity (runQuery qry)
mapM_ (fadeOut amt) =<< filterM p visibleWins

View File

@ -63,7 +63,7 @@ import Control.Monad
-- > -- avoid flickering -- > -- avoid flickering
-- > , persistent = True -- > , persistent = True
-- > -- make the window transparent -- > -- make the window transparent
-- > , opacity = 0xAAAAAAAA -- > , opacity = 0.6
-- > -- hide on start -- > -- hide on start
-- > , visible = False -- > , visible = False
-- > -- assign it a name to be able to toggle it independently of others -- > -- assign it a name to be able to toggle it independently of others
@ -89,12 +89,12 @@ import Control.Monad
-- Screenshot: <http://www.haskell.org/haskellwiki/Image:Xmonad-clock.png> -- Screenshot: <http://www.haskell.org/haskellwiki/Image:Xmonad-clock.png>
data Monitor a = Monitor data Monitor a = Monitor
{ prop :: Property -- ^ property which uniquely identifies monitor window { prop :: Property -- ^ property which uniquely identifies monitor window
, rect :: Rectangle -- ^ specifies where to put monitor , rect :: Rectangle -- ^ specifies where to put monitor
, visible :: Bool -- ^ is it visible by default? , visible :: Bool -- ^ is it visible by default?
, name :: String -- ^ name of monitor (useful when we have many of them) , name :: String -- ^ name of monitor (useful when we have many of them)
, persistent :: Bool -- ^ is it shown on all layouts? , persistent :: Bool -- ^ is it shown on all layouts?
, opacity :: Integer -- ^ opacity level , opacity :: Rational -- ^ opacity level
} deriving (Read, Show) } deriving (Read, Show)
-- | Template for 'Monitor' record. At least 'prop' and 'rect' should be -- | Template for 'Monitor' record. At least 'prop' and 'rect' should be
@ -106,7 +106,7 @@ monitor = Monitor
, visible = True , visible = True
, name = "" , name = ""
, persistent = False , persistent = False
, opacity = 0xFFFFFFFF , opacity = 1
} }
-- | Messages without names affect all monitors. Messages with names affect only -- | Messages without names affect all monitors. Messages with names affect only