aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-10-16 23:33:16 +0200
committerDavid Roundy <droundy@darcs.net>2007-10-16 23:33:16 +0200
commit7cd00f42deda004cc20d2335a0934bef8c295213 (patch)
tree8a3dd1c8ae8d1c287431c31d32ca11981c8cb2f4
parentcaea63525baff07f90e60bea56029bcf4bf62c1c (diff)
downloadXMonadContrib-7cd00f42deda004cc20d2335a0934bef8c295213.tar.gz
XMonadContrib-7cd00f42deda004cc20d2335a0934bef8c295213.tar.xz
XMonadContrib-7cd00f42deda004cc20d2335a0934bef8c295213.zip
compute nice window border for WindowNavigation properly.
darcs-hash:20071016213316-72aca-5b6ee6fcf9232935499ca9b61e29663db55a1857.gz
-rw-r--r--WindowNavigation.hs7
-rw-r--r--XUtils.hs11
2 files changed, 13 insertions, 5 deletions
diff --git a/WindowNavigation.hs b/WindowNavigation.hs
index b7f8fc9..c9977a3 100644
--- a/WindowNavigation.hs
+++ b/WindowNavigation.hs
@@ -108,11 +108,8 @@ instance LayoutModifier WindowNavigation Window where
do XConf { normalBorder = nbc, focusedBorder = fbc } <- ask
[uc,dc,lc,rc] <-
case brightness conf of
- Just frac -> return $ map round [myc,myc,myc,myc]
- -- Note: The following is a fragile crude hack... it really only
- -- works properly when the only non-zero color is blue. We should
- -- split the color into components and average *those*.
- where myc = (1-frac)*(fromIntegral nbc) + frac*(fromIntegral fbc)
+ Just frac -> do myc <- averagePixels fbc nbc frac
+ return [myc,myc,myc,myc]
Nothing -> mapM stringToPixel [upColor conf, downColor conf,
leftColor conf, rightColor conf]
let dirc U = uc
diff --git a/XUtils.hs b/XUtils.hs
index 4434c8f..f828529 100644
--- a/XUtils.hs
+++ b/XUtils.hs
@@ -16,6 +16,7 @@ module XMonadContrib.XUtils (
-- * Usage:
-- $usage
stringToPixel
+ , averagePixels
, initFont
, releaseFont
, createNewWindow
@@ -49,6 +50,16 @@ stringToPixel s = do
where getIt d = initColor d s
fallBack d = const $ return $ blackPixel d (defaultScreen d)
+-- | Compute the weighted average the colors of two given Pixel values.
+averagePixels :: Pixel -> Pixel -> Double -> X Pixel
+averagePixels p1 p2 f =
+ do d <- asks display
+ let cm = defaultColormap d (defaultScreen d)
+ [Color _ r1 g1 b1 _,Color _ r2 g2 b2 _] <- io $ queryColors d cm [Color p1 0 0 0 0,Color p2 0 0 0 0]
+ let mn x1 x2 = round (fromIntegral x1 * f + fromIntegral x2 * (1-f))
+ Color p _ _ _ _ <- io $ allocColor d cm (Color 0 (mn r1 r2) (mn g1 g2) (mn b1 b2) 0)
+ return p
+
-- | Given a fontname returns the fonstructure. If the font name is
-- not valid the default font will be loaded and returned.
initFont :: String -> X FontStruct