On Sat, Jun 16, 2007 at 07:03:24PM +0200, Andrea Rossato wrote:
> Hi,
> 
> I'm trying, without success, to create a window with the attribute
> override_redirect set to True (this way the window manager should not
> take care of it). Obviously with Xlib (X11-1.2.2).


just for the sake of documentation, this is the solution I've been able to
find thans to the help of the guys of the xmonad comunity.

thanks for your kind attentions.

andrea

the bits:

module Main where

import Graphics.X11.Xlib
import Graphics.X11.Xlib.Misc

import Control.Concurrent
import Data.Bits

main = test

test = do
  dpy   <- openDisplay ""
  let dflt = defaultScreen dpy
  rootw  <- rootWindow dpy dflt
  win <- mkUnmanagedWindow dpy (defaultScreenOfDisplay dpy) rootw 0 0 100 100 
0x000000
  mapWindow dpy win
  sync dpy True
  threadDelay $ 2 * 1000000

mkUnmanagedWindow dpy scr rw x y h w bgcolor = do
  let visual = defaultVisualOfScreen scr
      attrmask = cWBackPixel 
                 .|. cWOverrideRedirect
  window <- allocaSetWindowAttributes $ 
            \attributes -> do
              set_background_pixel attributes bgcolor
              set_override_redirect attributes True
              createWindow dpy rw x y w h 0 (defaultDepthOfScreen scr)
  inputOutput visual attrmask attributes                                
  return window
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to