aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2007-12-31 14:04:41 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2007-12-31 14:04:41 +0100
commita05585596c371507a25d01bea0d597658218926c (patch)
tree5d68a80c75f642fbed356cdc6565907a29228ca0
parentfe42675cca694ebdfb08bbefc893f23c95dde9ae (diff)
downloadXMonadContrib-a05585596c371507a25d01bea0d597658218926c.tar.gz
XMonadContrib-a05585596c371507a25d01bea0d597658218926c.tar.xz
XMonadContrib-a05585596c371507a25d01bea0d597658218926c.zip
Add ShowWName a layout modifier to show the workspace name
This module requires dzen darcs-hash:20071231130441-32816-0a0c78f6cbbc2972e965096dfda66afbc05ef1da.gz
-rw-r--r--XMonad/Layout/ShowWName.hs95
-rw-r--r--xmonad-contrib.cabal1
2 files changed, 96 insertions, 0 deletions
diff --git a/XMonad/Layout/ShowWName.hs b/XMonad/Layout/ShowWName.hs
new file mode 100644
index 0000000..7eef687
--- /dev/null
+++ b/XMonad/Layout/ShowWName.hs
@@ -0,0 +1,95 @@
+{-# OPTIONS_GHC -fglasgow-exts #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.ShowWName
+-- Copyright : (c) Andrea Rossato 2007
+-- License : BSD-style (see xmonad/LICENSE)
+--
+-- Maintainer : andrea.rossato@unibz.it
+-- Stability : unstable
+-- Portability : unportable
+--
+-- This is a layout modifier that will show the workspace name using
+-- dzen.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.ShowWName
+ ( -- * Usage
+ -- $usage
+ showWName
+ , showWName'
+ , defaultSWNConfig
+ , SWNConfig(..)
+ ) where
+
+import XMonad
+import qualified XMonad.StackSet as S
+import XMonad.Layout.LayoutModifier
+import XMonad.Util.Font
+import XMonad.Util.Dzen
+
+-- $usage
+-- You can use this module with the following in your
+-- @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.ShowWName
+-- > myLayout = layoutHook defaultConfig
+-- > main = xmonad defaultConfig { layoutHook = showWName myLayout }
+--
+-- For more detailed instructions on editing the layoutHook see:
+--
+-- "XMonad.Doc.Extending#Editing_the_layout_hook"
+
+-- | XXX
+showWName :: l a -> ModifiedLayout ShowWName l a
+showWName = ModifiedLayout (SWN True defaultSWNConfig)
+
+-- | XXX
+showWName' :: SWNConfig -> l a -> ModifiedLayout ShowWName l a
+showWName' c = ModifiedLayout (SWN True c)
+
+data ShowWName a = SWN Bool SWNConfig deriving (Read, Show)
+
+data SWNConfig =
+ SWNC { swn_font :: String
+ , swn_bgcolor :: String
+ , swn_color :: String
+ , swn_fade :: Rational
+ } deriving (Read, Show)
+
+defaultSWNConfig :: SWNConfig
+defaultSWNConfig =
+ SWNC { swn_font = "-misc-fixed-*-*-*-*-20-*-*-*-*-*-*-*"
+ , swn_bgcolor = "black"
+ , swn_color = "white"
+ , swn_fade = 1
+ }
+
+instance LayoutModifier ShowWName Window where
+ redoLayout (SWN True c) r _ wrs = flashName c r >> return (wrs, Just $ SWN False c)
+ redoLayout (SWN False _) _ _ wrs = return (wrs, Nothing)
+
+ handleMess (SWN _ c) m
+ | Just Hide <- fromMessage m = return . Just $ SWN True c
+ | otherwise = return Nothing
+
+flashName :: SWNConfig -> Rectangle -> X ()
+flashName c (Rectangle _ _ wh ht) = do
+ d <- asks display
+ n <- withWindowSet (return . S.tag . S.workspace . S.current)
+ f <- initXMF (swn_font c)
+ width <- textWidthXMF d f n
+ (_,as,ds,_) <- textExtentsXMF f n
+ releaseXMF f
+ let hight = as + ds + 2
+ y = (fromIntegral ht - hight) `div` 2
+ x = (fromIntegral wh - width) `div` 2
+ args = [ "-fn", swn_font c
+ , "-fg", swn_color c
+ , "-bg", swn_bgcolor c
+ , "-x" , show x
+ , "-y" , show y
+ , "-w" , show $ 3 * (width + 2)
+ ]
+ dzenWithArgs n args ((swn_fade c) `seconds`)
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index 1e1e1ab..58fac94 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -109,6 +109,7 @@ library
XMonad.Layout.Roledex
XMonad.Layout.Spiral
XMonad.Layout.Square
+ XMonad.Layout.ShowWName
XMonad.Layout.Tabbed
XMonad.Layout.ThreeColumns
XMonad.Layout.ToggleLayouts