{-# LANGUAGE ForeignFunctionInterface #-} -- whim: a window manager -- Copyright (C) 2006 Evan Martin -- | Extra functions that the built-in X11 module lacks. module Whim.Xlib where import Graphics.X11.Xlib import Foreign foreign import ccall "X11/Xlib.h XFree" x_free :: Ptr a -> IO () foreign import ccall "X11/Xlib.h XQueryTree" x_query_tree :: Display -> Window -> Ptr Window -> Ptr Window -> Ptr (Ptr Window) -> Ptr Int -> IO Int queryTree :: Display -> Window -> IO [Window] queryTree dpy win = with 0 $ \proot -> with 0 $ \pparent -> with nullPtr $ \ppchildren -> with 0 $ \pnchildren -> do throwIf (== 0) (const "XQueryTree failed") $ x_query_tree dpy win proot pparent ppchildren pnchildren nchildren <- peek pnchildren pchildren <- peek ppchildren children <- peekArray nchildren pchildren x_free pchildren return children type WindowAttributes = (Int, Int, Int, Int) foreign import ccall "X11/Xlib.h XGetWindowAttributes" x_get_window_attributes :: Display -> Window -> Ptr Int -> IO Int getWindowAttributes :: Display -> Window -> IO WindowAttributes getWindowAttributes dpy win = do let structSize = 23 allocaArray (structSize*4) $ \carr -> do throwIf (== 0) (const "XGetWindowAttributes failed") $ x_get_window_attributes dpy win carr arr <- peekArray structSize carr let (x:y:w:h:_) = map fromIntegral arr return (x, y, w, h) get_MapRequestEvent :: XEventPtr -> IO Window get_MapRequestEvent ptr = peekElemOff (castPtr ptr) 5