[xmonad] xmonad user survey!

Andrea Rossato mailing_list at istitutocolli.org
Wed Dec 26 07:31:29 EST 2007


On Mon, Dec 24, 2007 at 08:28:18AM -0500, David Roundy wrote:
> On Sun, Dec 23, 2007 at 02:26:08PM -0800, David Benbennick wrote:
> > In XMonad, I often get lost, and don't know what workspace I'm in
> > (since I use Ctrl+Alt+Left/Right to switch more than Alt-1/2/3).  I'd
> > love to have XMonad briefly flash the workspace name when switching
> > workspaces.
> 
> This would make a nice little contrib extension, and should actually be
> relatively easy as a layout modifier, except that it'd necessarily involve
> creating a little window (which is always tedious).


I was playing with this idea, but it doesn't seem so easy to me
actually... doLayout is called not just when you move to a new
workspace, but every time XMonad.Operations.windows is called... which
probably makes this approach quite troublesome and probably
impossible...

btw if someone wants to give it a try, he/she can start playing with
the code below. Xnest doesn't play nicely with it, but I have my swap
and phisical memory full, now, so...

andrea

module XMonad.Layout.ShowWName
    ( -- * Usage
      -- $usage
      showWName
    ) where

import XMonad
import qualified XMonad.StackSet as S
import XMonad.Layout.LayoutModifier
import XMonad.Util.Font
import XMonad.Util.XUtils

import Control.Concurrent

showWName :: l a -> ModifiedLayout ShowWName l a
showWName = ModifiedLayout ShowWName

-- should be data ShowWName a = ShowWName String String String Align deriving...
-- this way we can specify font and colors and text alignment
data ShowWName a = ShowWName deriving (Read, Show)

instance LayoutModifier ShowWName Window where
    -- I'm using redoLayout because we need the Rectangle
    -- to calculate where to place the window
    redoLayout ShowWName = flashName

flashName :: Rectangle -> t -> [(Window, Rectangle)] -> X ([(Window, Rectangle)], Maybe a)
flashName _ _ wrs = do 
  n <- withWindowSet (return . S.tag . S.workspace . S.current)
  f <- initXMF "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
  w <- createNewWindow (Rectangle 350 400 600 400) Nothing "white" True
  showWindow w
  paintAndWrite w f 600 400 10 "red" "white" "black" "blue" AlignCenter n
  io $ threadDelay (3 * 1000000)
  deleteWindow w
  releaseXMF f
  return (wrs, Nothing)



More information about the xmonad mailing list