[Xmonad] Patch: auto float windows with specific window class hints

Donald Bruce Stewart dons at cse.unsw.edu.au
Sun Jul 1 22:29:14 EDT 2007


lucky:
> Hi!
> 
> This is another hack that makes dialog and dock windows floating by
> default too.
> 
> I suppose, this code is not ready for including into the mainstream.
> It's just set of dirty hacks, what makes Xmonad more comfortable for me.
> 
> > This is nice, perhaps it should go in a contrib module, ahead of the
> > generic 'rules' support -- this would be usefu for user rules.
> > 


Ok. I'll leave this for now then, and use it as the basis for proper
rules support.

Thanks for the patch!

-- Don

> I'm n00b in the haskell and my skills is too scanty for such task now.
> sorry. :(
> 
> --
> Lucky

> diff -rN -u old-xmonad/Operations.hs new-xmonad/Operations.hs
> --- old-xmonad/Operations.hs	2007-06-29 00:07:17.000000000 +0600
> +++ new-xmonad/Operations.hs	2007-06-29 00:07:17.000000000 +0600
> @@ -38,6 +38,9 @@
>  
>  import qualified Data.Traversable as T
>  
> +import Text.Regex.Posix
> +
> +
>  -- ---------------------------------------------------------------------
>  -- |
>  -- Window manager operations
> @@ -58,7 +61,16 @@
>      sh <- io $ getWMNormalHints d w
>      let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
>      isTransient <- isJust `liftM` io (getTransientForHint d w)
> -    if isFixedSize || isTransient
> +
> +    -- float windows with specific class name
> +    cs <- io $ getClassHint d w
> +    let isFloatByClass = resClass cs =~ "Gajim|Gnome-keyring-ask|Stardict" :: Bool
> +
> +    -- float Dock or Dialog windows 
> +    isDock   <- isDockWindow d w
> +    isDialog <- isDialogWindow d w
> +
> +    if isFixedSize || isTransient || isFloatByClass || isDock || isDialog
>          then do modify $ \s -> s { windowset = W.insertUp w (windowset s) }
>                  float w -- \^^ now go the refresh.
>          else windows $ W.insertUp w
> diff -rN -u old-xmonad/xmonad.cabal new-xmonad/xmonad.cabal
> --- old-xmonad/xmonad.cabal	2007-06-29 00:07:17.000000000 +0600
> +++ new-xmonad/xmonad.cabal	2007-06-29 00:07:17.000000000 +0600
> @@ -18,7 +18,7 @@
>  license-file:       LICENSE
>  author:             Spencer Janssen
>  maintainer:         sjanssen at cse.unl.edu
> -build-depends:      base>=2.0, X11>=1.2.1, X11-extras>=0.2, mtl>=1.0, unix>=1.0
> +build-depends:      base>=2.0, X11>=1.2.1, X11-extras>=0.2, mtl>=1.0, unix>=1.0, regex-posix>=0.71
>  extra-source-files: README TODO tests/loc.hs tests/Properties.hs man/xmonad.1.in
>                      Config.hs-boot util/GenerateManpage.hs man/xmonad.1 man/xmonad.html
>  
> diff -rN -u old-xmonad/XMonad.hs new-xmonad/XMonad.hs
> --- old-xmonad/XMonad.hs	2007-06-29 00:07:17.000000000 +0600
> +++ new-xmonad/XMonad.hs	2007-06-29 00:07:17.000000000 +0600
> @@ -19,6 +19,12 @@
>      Typeable, Message, SomeMessage(..), fromMessage, runLayout,
>      runX, catchX, io, catchIO, withDisplay, withWindowSet, isRoot, spawn, restart, trace, whenJust, whenX,
>      atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW
> +    , atom__NET_WM_WINDOW_TYPE
> +    , atom__NET_WM_WINDOW_TYPE_DOCK
> +    , atom__NET_WM_WINDOW_TYPE_DIALOG
> +    , isDockWindow
> +    , isDialogWindow
> +
>    ) where
>  
>  import StackSet
> @@ -30,6 +36,7 @@
>  import System.Exit
>  import System.Environment
>  import Graphics.X11.Xlib
> +import Graphics.X11.Xlib.Extras
>  import Data.Typeable
>  
>  import qualified Data.Map as M
> @@ -112,6 +119,15 @@
>  atom_WM_DELETE_WINDOW   = getAtom "WM_DELETE_WINDOW"
>  atom_WM_STATE           = getAtom "WM_STATE"
>  
> +-- | Window type atoms
> +atom__NET_WM_WINDOW_TYPE
> +    , atom__NET_WM_WINDOW_TYPE_DOCK
> +    , atom__NET_WM_WINDOW_TYPE_DIALOG 
> +    :: X Atom
> +atom__NET_WM_WINDOW_TYPE          = getAtom "_NET_WM_WINDOW_TYPE"
> +atom__NET_WM_WINDOW_TYPE_DOCK     = getAtom "_NET_WM_WINDOW_TYPE_DOCK"
> +atom__NET_WM_WINDOW_TYPE_DIALOG   = getAtom "_NET_WM_WINDOW_TYPE_DIALOG"
> +
>  ------------------------------------------------------------------------
>  -- | Layout handling
>  
> @@ -205,3 +221,32 @@
>  -- be found in your .xsession-errors file
>  trace :: String -> X ()
>  trace msg = io $! do hPutStrLn stderr msg; hFlush stderr
> +
> +
> +
> +isDockWindow ::  Display -> Window -> X Bool
> +isDockWindow d w = windowTypeHasAtom d w atom__NET_WM_WINDOW_TYPE_DOCK
> +
> +isDialogWindow ::  Display -> Window -> X Bool
> +isDialogWindow d w = windowTypeHasAtom d w atom__NET_WM_WINDOW_TYPE_DIALOG
> +
> +windowTypeHasAtom ::  Display -> Window -> X Atom -> X Bool
> +windowTypeHasAtom d w a = do
> +    wtas <- getWindowTypeAtoms d w
> +    atom <- a
> +    return $ atom `justElem` wtas
> +
> +getWindowTypeAtoms ::  Display -> Window -> X (Maybe [Atom])
> +getWindowTypeAtoms d w = do   
> +    aWindowType <- atom__NET_WM_WINDOW_TYPE
> +    wTypes	    <- io $ getWindowPropertyAtom d aWindowType w
> +    return wTypes
> +
> +-- FIXME: Just type casting Word32 to Atom
> +getWindowPropertyAtom :: Display -> Atom -> Window -> IO (Maybe [Atom])
> +getWindowPropertyAtom = rawGetWindowProperty 32
> +
> +justElem ::  (Eq a) => a -> Maybe [a] -> Bool
> +justElem y (Just xs)    = y `elem` xs
> +justElem _ Nothing      = False
> +
> 

> _______________________________________________
> Xmonad mailing list
> Xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad



More information about the Xmonad mailing list