
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). No meter how I try I seem not to be able to get there. In test1 I try with the correct method (createWindow), but I get an error message: X Error of failed request: BadMatch (invalid parameter attributes) Major opcode of failed request: 1 (X_CreateWindow) Serial number of failed request: 7 Current serial number in output stream: 9 With test2 I can open the window, but I'm not able to set that attribute. Any help would be greatly appreciated. TIA. Andrea the example code: module Main where import Graphics.X11.Xlib import Graphics.X11.Xlib.Misc import Graphics.X11.Xlib.Extras import Control.Concurrent import Data.Bits main = test2 test1 = do dpy <- openDisplay "" let dflt = defaultScreen dpy rootw <- rootWindow dpy dflt win <- mkWindow dpy (defaultScreenOfDisplay dpy) rootw 0 0 100 100 mapWindow dpy win sync dpy True threadDelay $ 2 * 1000000 mkWindow dpy scr rw x y h w = do let attrmask = cWOverrideRedirect visual = defaultVisualOfScreen scr attributes <- allocaSetWindowAttributes (\s -> return $ s ) set_override_redirect attributes True window <- createWindow dpy rw x y -- x, y w h -- width, height 1 -- border_width 1 inputOutput visual attrmask attributes putStrLn "Done!" return window test2 = do dpy <- openDisplay "" let dflt = defaultScreen dpy rootw <- rootWindow dpy dflt win <- createSimpleWindow dpy rootw 0 0 100 100 1 0x000000 0xFFFFFF mapWindow dpy win sync dpy True threadDelay $ 2 * 1000000 wa <- getWindowAttributes dpy win allocaXEvent $ \ev -> do setEventType ev configureNotify setConfigureEvent ev win win 100 100 20 20 1 win True sendEvent dpy win False cWOverrideRedirect ev --nextEvent dpy ev getEvent ev sync dpy True a <- getWindowAttributes dpy win putStrLn $ show (wa_override_redirect a)