{-# LINE 1 "Graphics/X11/Xlib/Misc.hsc" #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.X11.Xlib.Misc
-- Copyright   :  (c) Alastair Reid, 1999-2003
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- A collection of FFI declarations for interfacing with Xlib.
--
-----------------------------------------------------------------------------

module Graphics.X11.Xlib.Misc(

        rmInitialize,
        autoRepeatOff,
        autoRepeatOn,
        bell,
        setCloseDownMode,
        lastKnownRequestProcessed,
        getInputFocus,
        setInputFocus,
        grabButton,
        ungrabButton,
        grabPointer,
        ungrabPointer,
        grabKey,
        ungrabKey,
        grabKeyboard,
        ungrabKeyboard,
        grabServer,
        ungrabServer,
        queryBestTile,
        queryBestStipple,
        queryBestCursor,
        queryBestSize,
        queryPointer,

        -- * Error reporting
        displayName,
        setDefaultErrorHandler,

        -- * Geometry
        geometry,
        getGeometry,

        -- * Locale
        supportsLocale,
        setLocaleModifiers,

        -- * Screen saver
        AllowExposuresMode,
        dontAllowExposures,
        allowExposures,
        defaultExposures,
        PreferBlankingMode,
        dontPreferBlanking,
        preferBlanking,
        defaultBlanking,
        ScreenSaverMode,
        screenSaverActive,
        screenSaverReset,
        getScreenSaver,
        setScreenSaver,
        activateScreenSaver,
        resetScreenSaver,
        forceScreenSaver,

        -- * Pointer
        getPointerControl,
        warpPointer,

        -- * Visuals
        visualIDFromVisual,
        VisualInfoMask,
        visualNoMask,
        visualIDMask,
        visualScreenMask,
        visualDepthMask,
        visualClassMask,
        visualRedMaskMask,
        visualGreenMaskMask,
        visualBlueMaskMask,
        visualColormapSizeMask,
        visualBitsPerRGBMask,
        visualAllMask,
        getVisualInfo,
        matchVisualInfo,

        -- * Threads
        initThreads,
        lockDisplay,
        unlockDisplay,

        -- * Pixmaps
        createPixmap,
        freePixmap,
        bitmapBitOrder,
        bitmapUnit,
        bitmapPad,
        readBitmapFile,

        -- * Keycodes
        displayKeycodes,
        lookupKeysym,
        keycodeToKeysym,
        keysymToKeycode,
        keysymToString,
        stringToKeysym,
        noSymbol,
        lookupString,

        -- * Icons
        getIconName,
        setIconName,

        -- * Cursors
        defineCursor,
        undefineCursor,
        createPixmapCursor,
        createGlyphCursor,
        createFontCursor,
        freeCursor,
        recolorCursor,

        -- * Window manager stuff
        setWMProtocols,

        -- * Set window attributes
        allocaSetWindowAttributes,
        set_background_pixmap,
        set_background_pixel,
        set_border_pixmap,
        set_border_pixel,
        set_bit_gravity,
        set_win_gravity,
        set_backing_store,
        set_backing_planes,
        set_backing_pixel,
        set_save_under,
        set_event_mask,
        set_do_not_propagate_mask,
        set_override_redirect,
        set_colormap,
        set_cursor,

        -- * Drawing
        drawPoint,
        drawPoints,
        drawLine,
        drawLines,
        drawSegments,
        drawRectangle,
        drawRectangles,
        drawArc,
        drawArcs,
        fillRectangle,
        fillRectangles,
        fillPolygon,
        fillArc,
        fillArcs,
        copyArea,
        copyPlane,
        drawString,
        drawImageString,

        -- * Cut and paste buffers
        storeBuffer,
        storeBytes,
        fetchBuffer,
        fetchBytes,
        rotateBuffers,

        -- * Window properties
        setTextProperty,

        ) where

import Graphics.X11.Types
import Graphics.X11.Xlib.Types
import Graphics.X11.Xlib.Atom
import Graphics.X11.Xlib.Event
import Graphics.X11.Xlib.Font
import Graphics.X11.Xlib.Internal

import Foreign (Storable, Ptr, alloca, peek, throwIfNull, with, withArrayLen, allocaBytes, pokeByteOff, withArray, FunPtr, nullPtr, Word32, peekArray)
import Foreign.C

import System.IO.Unsafe


{-# LINE 195 "Graphics/X11/Xlib/Misc.hsc" #-}
import Data.Data

{-# LINE 197 "Graphics/X11/Xlib/Misc.hsc" #-}



-- I'm not sure why I added this since I don't have any of the related
-- functions.

-- | interface to the X11 library function @XrmInitialize()@.
foreign import ccall unsafe "HsXlib.h XrmInitialize"
        rmInitialize :: IO ()

-- %fun XGetDefault :: Display -> String -> String -> IO ()

-- | interface to the X11 library function @XAutoRepeatOff()@.
foreign import ccall unsafe "HsXlib.h XAutoRepeatOff"
        autoRepeatOff    :: Display -> IO ()

-- | interface to the X11 library function @XAutoRepeatOn()@.
foreign import ccall unsafe "HsXlib.h XAutoRepeatOn"
        autoRepeatOn     :: Display -> IO ()

-- | interface to the X11 library function @XBell()@.
foreign import ccall unsafe "HsXlib.h XBell"
        bell             :: Display -> CInt -> IO ()

-- | interface to the X11 library function @XSetCloseDownMode()@.
foreign import ccall unsafe "HsXlib.h XSetCloseDownMode"
        setCloseDownMode :: Display -> CloseDownMode -> IO ()

-- | interface to the X11 library function @XLastKnownRequestProcessed()@.
foreign import ccall unsafe "HsXlib.h XLastKnownRequestProcessed"
        lastKnownRequestProcessed :: Display -> IO CInt

-- | interface to the X11 library function @XGetInputFocus()@.
getInputFocus :: Display -> IO (Window, FocusMode)
getInputFocus :: Display -> IO (Atom, CInt)
getInputFocus Display
display =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
focus_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
revert_to_return -> do
        Display -> Ptr Atom -> Ptr CInt -> IO ()
xGetInputFocus Display
display Ptr Atom
focus_return Ptr CInt
revert_to_return
        Atom
focus <- forall a. Storable a => Ptr a -> IO a
peek Ptr Atom
focus_return
        CInt
revert_to <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
revert_to_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (Atom
focus, CInt
revert_to)
foreign import ccall unsafe "HsXlib.h XGetInputFocus"
        xGetInputFocus :: Display -> Ptr Window -> Ptr FocusMode -> IO ()

-- | interface to the X11 library function @XSetInputFocus()@.
foreign import ccall unsafe "HsXlib.h XSetInputFocus"
        setInputFocus   :: Display -> Window -> FocusMode -> Time -> IO ()

-- XAllocID omitted
-- XKillClient omitted
-- XFetchName omitted
-- XGetKeyboardControl omitted
-- XChangeKeyboardControl omitted
-- XChangeKeyboardMapping omitted
-- XChangePointerControl omitted

-- | interface to the X11 library function @XGrabButton()@.
foreign import ccall unsafe "HsXlib.h XGrabButton"
        grabButton     :: Display -> Button -> ButtonMask -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> IO ()

-- | interface to the X11 library function @XUngrabButton()@.
foreign import ccall unsafe "HsXlib.h XUngrabButton"
        ungrabButton   :: Display -> Button -> ButtonMask -> Window -> IO ()

-- | interface to the X11 library function @XGrabPointer()@.
foreign import ccall unsafe "HsXlib.h XGrabPointer"
        grabPointer    :: Display -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> Time -> IO GrabStatus

-- | interface to the X11 library function @XUngrabPointer()@.
foreign import ccall unsafe "HsXlib.h XUngrabPointer"
        ungrabPointer  :: Display -> Time -> IO ()

-- | interface to the X11 library function @XGrabKey()@.
foreign import ccall unsafe "HsXlib.h XGrabKey"
        grabKey        :: Display -> KeyCode -> KeyMask -> Window -> Bool -> GrabMode -> GrabMode -> IO ()

-- | interface to the X11 library function @XUngrabKey()@.
foreign import ccall unsafe "HsXlib.h XUngrabKey"
        ungrabKey      :: Display -> KeyCode -> KeyMask -> Window -> IO ()

-- | interface to the X11 library function @XGrabKeyboard()@.
foreign import ccall unsafe "HsXlib.h XGrabKeyboard"
        grabKeyboard   :: Display -> Window -> Bool -> GrabMode -> GrabMode -> Time -> IO GrabStatus

-- | interface to the X11 library function @XUngrabKeyboard()@.
foreign import ccall unsafe "HsXlib.h XUngrabKeyboard"
        ungrabKeyboard :: Display -> Time -> IO ()

-- | interface to the X11 library function @XGrabServer()@.
foreign import ccall unsafe "HsXlib.h XGrabServer"
        grabServer   :: Display -> IO ()

-- | interface to the X11 library function @XUngrabServer()@.
foreign import ccall unsafe "HsXlib.h XUngrabServer"
        ungrabServer :: Display -> IO ()

-- XChangeActivePointerGrab omitted

-- XFreeStringList omitted

-- | interface to the X11 library function @XQueryBestTile()@.
queryBestTile    :: Display -> Drawable -> Dimension -> Dimension ->
                        IO (Dimension, Dimension)
queryBestTile :: Display -> Atom -> Word32 -> Word32 -> IO (Word32, Word32)
queryBestTile Display
display Atom
which_screen Word32
width Word32
height =
        forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO CInt -> IO ()
throwIfZero String
"queryBestTile") forall a b. (a -> b) -> a -> b
$
                Display
-> Atom -> Word32 -> Word32 -> Ptr Word32 -> Ptr Word32 -> IO CInt
xQueryBestTile Display
display Atom
which_screen Word32
width Word32
height
foreign import ccall unsafe "HsXlib.h XQueryBestTile"
        xQueryBestTile    :: Display -> Drawable -> Dimension -> Dimension ->
                                Ptr Dimension -> Ptr Dimension -> IO Status

-- | interface to the X11 library function @XQueryBestStipple()@.
queryBestStipple :: Display -> Drawable -> Dimension -> Dimension ->
                        IO (Dimension, Dimension)
queryBestStipple :: Display -> Atom -> Word32 -> Word32 -> IO (Word32, Word32)
queryBestStipple Display
display Atom
which_screen Word32
width Word32
height =
        forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO CInt -> IO ()
throwIfZero String
"queryBestStipple") forall a b. (a -> b) -> a -> b
$
                Display
-> Atom -> Word32 -> Word32 -> Ptr Word32 -> Ptr Word32 -> IO CInt
xQueryBestStipple Display
display Atom
which_screen Word32
width Word32
height
foreign import ccall unsafe "HsXlib.h XQueryBestStipple"
        xQueryBestStipple :: Display -> Drawable -> Dimension -> Dimension ->
                                Ptr Dimension -> Ptr Dimension -> IO Status

-- | interface to the X11 library function @XQueryBestCursor()@.
queryBestCursor  :: Display -> Drawable -> Dimension -> Dimension ->
                        IO (Dimension, Dimension)
queryBestCursor :: Display -> Atom -> Word32 -> Word32 -> IO (Word32, Word32)
queryBestCursor Display
display Atom
d Word32
width Word32
height =
        forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO CInt -> IO ()
throwIfZero String
"queryBestCursor") forall a b. (a -> b) -> a -> b
$
                Display
-> Atom -> Word32 -> Word32 -> Ptr Word32 -> Ptr Word32 -> IO CInt
xQueryBestCursor Display
display Atom
d Word32
width Word32
height
foreign import ccall unsafe "HsXlib.h XQueryBestCursor"
        xQueryBestCursor  :: Display -> Drawable -> Dimension -> Dimension ->
                                Ptr Dimension -> Ptr Dimension -> IO Status

-- | interface to the X11 library function @XQueryBestSize()@.
queryBestSize    :: Display -> QueryBestSizeClass -> Drawable ->
                        Dimension -> Dimension -> IO (Dimension, Dimension)
queryBestSize :: Display -> CInt -> Atom -> Word32 -> Word32 -> IO (Word32, Word32)
queryBestSize Display
display CInt
shape_class Atom
which_screen Word32
width Word32
height =
        forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO CInt -> IO ()
throwIfZero String
"queryBestSize") forall a b. (a -> b) -> a -> b
$
                Display
-> CInt
-> Atom
-> Word32
-> Word32
-> Ptr Word32
-> Ptr Word32
-> IO CInt
xQueryBestSize Display
display CInt
shape_class Atom
which_screen Word32
width Word32
height
foreign import ccall unsafe "HsXlib.h XQueryBestSize"
        xQueryBestSize    :: Display -> QueryBestSizeClass -> Drawable ->
                                Dimension -> Dimension ->
                                Ptr Dimension -> Ptr Dimension -> IO Status

-- Note: Returns false if pointer not in window w (and win_x = win_y = 0)
-- ToDo: more effective use of Maybes?

-- | interface to the X11 library function @XQueryPointer()@.
queryPointer :: Display -> Window ->
                IO (Bool, Window, Window, CInt, CInt, CInt, CInt, Modifier)
queryPointer :: Display
-> Atom -> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
queryPointer Display
display Atom
w =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
root_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
child_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
root_x_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
root_y_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
win_x_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
win_y_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Modifier
mask_return -> do
        Bool
rel <- Display
-> Atom
-> Ptr Atom
-> Ptr Atom
-> Ptr CInt
-> Ptr CInt
-> Ptr CInt
-> Ptr CInt
-> Ptr Modifier
-> IO Bool
xQueryPointer Display
display Atom
w Ptr Atom
root_return Ptr Atom
child_return Ptr CInt
root_x_return
                Ptr CInt
root_y_return Ptr CInt
win_x_return Ptr CInt
win_y_return Ptr Modifier
mask_return
        Atom
root <- forall a. Storable a => Ptr a -> IO a
peek Ptr Atom
root_return
        Atom
child <- forall a. Storable a => Ptr a -> IO a
peek Ptr Atom
child_return
        CInt
root_x <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
root_x_return
        CInt
root_y <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
root_y_return
        CInt
win_x <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
win_x_return
        CInt
win_y <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
win_y_return
        Modifier
mask <- forall a. Storable a => Ptr a -> IO a
peek Ptr Modifier
mask_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
rel, Atom
root, Atom
child, CInt
root_x, CInt
root_y, CInt
win_x, CInt
win_y, Modifier
mask)
foreign import ccall unsafe "HsXlib.h XQueryPointer"
        xQueryPointer :: Display -> Window ->
                Ptr Window -> Ptr Window -> Ptr CInt -> Ptr CInt ->
                Ptr CInt -> Ptr CInt -> Ptr Modifier -> IO Bool

-- XSetSelectionOwner omitted

-- XOpenOM omitted
-- XCloseOM omitted
-- XSetOMValues omitted
-- XGetOMValues omitted
-- DisplayOfOM omitted
-- XLocaleOfOM omitted

-- XCreateOC omitted
-- XDestroyOC omitted
-- XOMOfOC omitted
-- XSetOCValues omitted
-- XGetOCValues omitted

-- XVaCreateNestedList omitted

----------------------------------------------------------------
-- Error reporting
----------------------------------------------------------------

-- | interface to the X11 library function @XDisplayName()@.
displayName :: String -> String
displayName :: String -> String
displayName String
str = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$
        forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
str forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_str -> do
        Ptr CChar
c_name <- Ptr CChar -> IO (Ptr CChar)
xDisplayName Ptr CChar
c_str
        Ptr CChar -> IO String
peekCString Ptr CChar
c_name
foreign import ccall unsafe "HsXlib.h XDisplayName"
        xDisplayName :: CString -> IO CString

-- type ErrorHandler   = Display -> ErrorEvent -> IO CInt
-- %dis errorHandler x = (stable x)
--
-- type IOErrorHandler = Display ->                IO CInt
-- %dis ioErrorHandler x = (stable x)

-- Sadly, this code doesn't work because hugs->runIO creates a fresh
-- stack of exception handlers so the exception gets thrown to the
-- wrong place.
--
-- %C
-- % static HugsStablePtr ioErrorHandlerPtr;
-- %
-- % int genericIOErrorHandler(Display *d)
-- % {
-- %     if (ioErrorHandlerPtr >= 0) {
-- %              hugs->putStablePtr(ioErrorHandlerPtr);
-- %              hugs->putAddr(d);
-- %              if (hugs->runIO(1)) { /* exitWith value returned */
-- %               return hugs->getInt();
-- %              } else {
-- %               return hugs->getWord();
-- %              }
-- %     }
-- %     return 1;
-- % }

-- Here's what we might do instead.  The two error handlers set flags
-- when they fire and every single call to X contains the line:
--
--   %fail { errorFlags != 0 } { XError(errorFlags) }
--
-- This really sucks.
-- Oh, and it won't even work with IOErrors since they terminate
-- the process if the handler returns.  I don't know what the hell they
-- think they're doing taking it upon themselves to terminate MY
-- process when THEIR library has a problem but I don't think anyone
-- ever accused X of being well-designed.
--
-- % static int genericIOErrorHandler(Display *d)
-- % {
-- %     if (ioErrorHandlerPtr >= 0) {
-- %              hugs->putStablePtr(ioErrorHandlerPtr);
-- %              hugs->putAddr(d);
-- %              if (hugs->runIO(1)) { /* exitWith value returned */
-- %               return hugs->getInt();
-- %              } else {
-- %               return hugs->getWord();
-- %              }
-- %     }
-- %     return 1;
-- % }

-- HN 2001-02-06
-- Moved to auxiliaries.c to make it easier to use the inlining option.
-- -- Sigh, for now we just use an error handler that prints an error
-- -- message on the screen
-- %C
-- % static int defaultErrorHandler(Display *d, XErrorEvent *ev)
-- % {
-- %      char buffer[1000];
-- %      XGetErrorText(d,ev->error_code,buffer,1000);
-- %      printf("Error: %s\n", buffer);
-- %      return 0;
-- % }

{-# CFILES cbits/auxiliaries.c #-}

newtype XErrorEvent = XErrorEvent (Ptr XErrorEvent)

{-# LINE 467 "Graphics/X11/Xlib/Misc.hsc" #-}
        deriving (XErrorEvent -> XErrorEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XErrorEvent -> XErrorEvent -> Bool
$c/= :: XErrorEvent -> XErrorEvent -> Bool
== :: XErrorEvent -> XErrorEvent -> Bool
$c== :: XErrorEvent -> XErrorEvent -> Bool
Eq, Eq XErrorEvent
XErrorEvent -> XErrorEvent -> Bool
XErrorEvent -> XErrorEvent -> Ordering
XErrorEvent -> XErrorEvent -> XErrorEvent
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: XErrorEvent -> XErrorEvent -> XErrorEvent
$cmin :: XErrorEvent -> XErrorEvent -> XErrorEvent
max :: XErrorEvent -> XErrorEvent -> XErrorEvent
$cmax :: XErrorEvent -> XErrorEvent -> XErrorEvent
>= :: XErrorEvent -> XErrorEvent -> Bool
$c>= :: XErrorEvent -> XErrorEvent -> Bool
> :: XErrorEvent -> XErrorEvent -> Bool
$c> :: XErrorEvent -> XErrorEvent -> Bool
<= :: XErrorEvent -> XErrorEvent -> Bool
$c<= :: XErrorEvent -> XErrorEvent -> Bool
< :: XErrorEvent -> XErrorEvent -> Bool
$c< :: XErrorEvent -> XErrorEvent -> Bool
compare :: XErrorEvent -> XErrorEvent -> Ordering
$ccompare :: XErrorEvent -> XErrorEvent -> Ordering
Ord, Int -> XErrorEvent -> String -> String
[XErrorEvent] -> String -> String
XErrorEvent -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [XErrorEvent] -> String -> String
$cshowList :: [XErrorEvent] -> String -> String
show :: XErrorEvent -> String
$cshow :: XErrorEvent -> String
showsPrec :: Int -> XErrorEvent -> String -> String
$cshowsPrec :: Int -> XErrorEvent -> String -> String
Show, Typeable, Typeable XErrorEvent
XErrorEvent -> DataType
XErrorEvent -> Constr
(forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u
forall u. (forall d. Data d => d -> u) -> XErrorEvent -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XErrorEvent)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XErrorEvent)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> XErrorEvent -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XErrorEvent -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
gmapT :: (forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
$cgmapT :: (forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XErrorEvent)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XErrorEvent)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XErrorEvent)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XErrorEvent)
dataTypeOf :: XErrorEvent -> DataType
$cdataTypeOf :: XErrorEvent -> DataType
toConstr :: XErrorEvent -> Constr
$ctoConstr :: XErrorEvent -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
Data)

{-# LINE 471 "Graphics/X11/Xlib/Misc.hsc" #-}

type ErrorHandler = FunPtr (Display -> Ptr XErrorEvent -> IO CInt)

foreign import ccall unsafe "HsXlib.h &defaultErrorHandler"
        defaultErrorHandler :: FunPtr (Display -> Ptr XErrorEvent -> IO CInt)

-- | The Xlib library reports most errors by invoking a user-provided
-- error handler.  This function installs an error handler that prints a
-- textual representation of the error.
setDefaultErrorHandler :: IO ()
setDefaultErrorHandler :: IO ()
setDefaultErrorHandler = do
        ErrorHandler
_ <- ErrorHandler -> IO ErrorHandler
xSetErrorHandler ErrorHandler
defaultErrorHandler
        forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- %fun XSetIOErrorHandler :: IOErrorHandler -> IO IOErrorHandler

foreign import ccall unsafe "HsXlib.h XSetErrorHandler"
        xSetErrorHandler   :: ErrorHandler   -> IO ErrorHandler

-- XGetErrorDatabaseText omitted
-- XGetErrorText omitted

----------------------------------------------------------------
-- -- Buffers
-- ----------------------------------------------------------------
--
-- -- OLD: Would arrays be more appropriate?
-- --
-- -- IMPURE void       XStoreBytes(display, bytes, nbytes)
-- -- IN Display*               display
-- -- VAR Int                   nbytes
-- -- IN list[nbytes] Byte      bytes
-- --
-- -- IMPURE list[nbytes] Byte  XFetchBytes(display, &nbytes)
-- -- IN Display*       display
-- -- VAR Int           nbytes
-- --
-- -- IMPURE void       XStoreBuffer(display, bytes, nbytes, buffer)
-- -- IN Display*               display
-- -- VAR Int                   nbytes
-- -- IN list[nbytes] Byte      bytes
-- -- IN Buffer         buffer
-- --
-- -- IMPURE list[nbytes] Byte  XFetchBuffer(display, &nbytes, buffer)
-- -- IN Display*       display
-- -- VAR Int           nbytes
-- -- IN Buffer buffer
-- --
-- -- IMPURE void       XRotateBuffers(display, rotate)
-- -- IN Display*       display
-- -- VAR Int           rotate

----------------------------------------------------------------
-- Extensions
----------------------------------------------------------------

-- ToDo: Use XFreeExtensionList
-- %fun XListExtensions :: Display -> IO ListString using res1 = XListExtensions(arg1,&res1_size)

-- %errfun False XQueryExtension :: Display -> String -> IO (Int,Int,Int) using res4 = XQueryExtension(arg1,arg2,&res1,&res2,&res3)->(res1,res2,res3)
-- %fun XInitExtensions :: Display -> String -> IO XExtCodes
-- %fun XAddExtensions  :: Display ->           IO XExtCodes

-- XAddToExtensionList omitted
-- XFindOnExtensionList omitted
-- XEHeadOfExtensionList omitted

----------------------------------------------------------------
-- Hosts
----------------------------------------------------------------

-- ToDo: operations to construct and destruct an XHostAddress

-- %fun XAddHost :: Display -> XHostAddress -> IO ()
-- %fun XRemoveHost :: Display -> XHostAddress -> IO ()
--
-- %fun XAddHosts    :: Display -> ListXHostAddress -> IO () using XAddHosts(arg1,arg2,arg2_size)
-- %fun XRemoveHosts :: Display -> ListXHostAddress -> IO () using XRemoveHosts(arg1,arg2,arg2_size)
--
-- -- Uses %prim to let us call XFree
-- %prim XListHosts :: Display -> IO (ListXHostAddress, Bool)
-- Bool state;
-- Int r_size;
-- XHostAddress* r = XListHosts(arg1,&r_size,&state);
-- %update(r,state);
-- XFree(r);
-- return;

-- %fun XEnableAccessControl  :: Display -> IO ()
-- %fun XDisableAccessControl :: Display -> IO ()
-- %fun XSetAccessControl     :: Display -> Access -> IO ()

----------------------------------------------------------------
-- Geometry
----------------------------------------------------------------

-- | interface to the X11 library function @XGeometry()@.
geometry :: Display -> CInt -> String -> String ->
                Dimension -> Dimension -> Dimension -> CInt -> CInt ->
                IO (CInt, Position, Position, Dimension, Dimension)
geometry :: Display
-> CInt
-> String
-> String
-> Word32
-> Word32
-> Word32
-> CInt
-> CInt
-> IO (CInt, Position, Position, Word32, Word32)
geometry Display
display CInt
screen String
position String
default_position
                Word32
bwidth Word32
fwidth Word32
fheight CInt
xadder CInt
yadder =
        forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
position forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_position ->
        forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
default_position forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_default_position ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Position
x_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Position
y_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
width_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
height_return -> do
        CInt
res <- Display
-> CInt
-> Ptr CChar
-> Ptr CChar
-> Word32
-> Word32
-> Word32
-> CInt
-> CInt
-> Ptr Position
-> Ptr Position
-> Ptr Word32
-> Ptr Word32
-> IO CInt
xGeometry Display
display CInt
screen Ptr CChar
c_position Ptr CChar
c_default_position
                Word32
bwidth Word32
fwidth Word32
fheight CInt
xadder CInt
yadder
                Ptr Position
x_return Ptr Position
y_return Ptr Word32
width_return Ptr Word32
height_return
        Position
x <- forall a. Storable a => Ptr a -> IO a
peek Ptr Position
x_return
        Position
y <- forall a. Storable a => Ptr a -> IO a
peek Ptr Position
y_return
        Word32
width <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
width_return
        Word32
height <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
height_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (CInt
res, Position
x, Position
y, Word32
width, Word32
height)
foreign import ccall unsafe "HsXlib.h XGeometry"
        xGeometry :: Display -> CInt -> CString -> CString ->
                Dimension -> Dimension -> Dimension -> CInt -> CInt ->
                Ptr Position -> Ptr Position ->
                Ptr Dimension -> Ptr Dimension -> IO CInt

-- | interface to the X11 library function @XGetGeometry()@.
getGeometry :: Display -> Drawable ->
        IO (Window, Position, Position, Dimension, Dimension, Dimension, CInt)
getGeometry :: Display
-> Atom
-> IO (Atom, Position, Position, Word32, Word32, Word32, CInt)
getGeometry Display
display Atom
d =
        forall a b c d e f g r.
(Storable a, Storable b, Storable c, Storable d, Storable e,
 Storable f, Storable g) =>
(IO r -> IO ())
-> (Ptr a
    -> Ptr b -> Ptr c -> Ptr d -> Ptr e -> Ptr f -> Ptr g -> IO r)
-> IO (a, b, c, d, e, f, g)
outParameters7 (String -> IO CInt -> IO ()
throwIfZero String
"getGeometry") forall a b. (a -> b) -> a -> b
$
                Display
-> Atom
-> Ptr Atom
-> Ptr Position
-> Ptr Position
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> Ptr CInt
-> IO CInt
xGetGeometry Display
display Atom
d
foreign import ccall unsafe "HsXlib.h XGetGeometry"
        xGetGeometry :: Display -> Drawable ->
                Ptr Window -> Ptr Position -> Ptr Position -> Ptr Dimension ->
                Ptr Dimension -> Ptr Dimension -> Ptr CInt -> IO Status

-- XParseGeometry omitted (returned bitset too weird)

----------------------------------------------------------------
-- Locale
----------------------------------------------------------------

-- | interface to the X11 library function @XSupportsLocale()@.
foreign import ccall unsafe "HsXlib.h XSupportsLocale"
        supportsLocale :: IO Bool

-- | interface to the X11 library function @XSetLocaleModifiers()@.
setLocaleModifiers :: String -> IO String
setLocaleModifiers :: String -> IO String
setLocaleModifiers String
mods =
        forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
mods forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
modifier_list -> do
        Ptr CChar
c_str <- Ptr CChar -> IO (Ptr CChar)
xSetLocaleModifiers Ptr CChar
modifier_list
        Ptr CChar -> IO String
peekCString Ptr CChar
c_str
foreign import ccall unsafe "HsXlib.h XSetLocaleModifiers"
        xSetLocaleModifiers :: CString -> IO CString

----------------------------------------------------------------
-- Screen Saver
----------------------------------------------------------------

type AllowExposuresMode = CInt
dontAllowExposures    :: AllowExposuresMode
dontAllowExposures :: CInt
dontAllowExposures    =  CInt
0
allowExposures        :: AllowExposuresMode
allowExposures :: CInt
allowExposures        =  CInt
1
defaultExposures      :: AllowExposuresMode
defaultExposures :: CInt
defaultExposures      =  CInt
2

{-# LINE 633 "Graphics/X11/Xlib/Misc.hsc" #-}

type PreferBlankingMode = CInt
dontPreferBlanking    :: PreferBlankingMode
dontPreferBlanking :: CInt
dontPreferBlanking    =  CInt
0
preferBlanking        :: PreferBlankingMode
preferBlanking :: CInt
preferBlanking        =  CInt
1
defaultBlanking       :: PreferBlankingMode
defaultBlanking :: CInt
defaultBlanking       =  CInt
2

{-# LINE 640 "Graphics/X11/Xlib/Misc.hsc" #-}

type ScreenSaverMode = CInt
screenSaverActive     :: ScreenSaverMode
screenSaverActive :: CInt
screenSaverActive     =  CInt
1
screenSaverReset      :: ScreenSaverMode
screenSaverReset :: CInt
screenSaverReset      =  CInt
0

{-# LINE 646 "Graphics/X11/Xlib/Misc.hsc" #-}

getScreenSaver :: Display ->
        IO (CInt, CInt, PreferBlankingMode, AllowExposuresMode)
getScreenSaver :: Display -> IO (CInt, CInt, CInt, CInt)
getScreenSaver Display
display = forall a b c d r.
(Storable a, Storable b, Storable c, Storable d) =>
(IO r -> IO ())
-> (Ptr a -> Ptr b -> Ptr c -> Ptr d -> IO r) -> IO (a, b, c, d)
outParameters4 forall a. a -> a
id (Display -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()
xGetScreenSaver Display
display)
foreign import ccall unsafe "HsXlib.h XGetScreenSaver"
        xGetScreenSaver :: Display -> Ptr CInt -> Ptr CInt ->
                Ptr PreferBlankingMode -> Ptr AllowExposuresMode -> IO ()

-- | interface to the X11 library function @XSetScreenSaver()@.
foreign import ccall unsafe "HsXlib.h XSetScreenSaver"
        setScreenSaver      :: Display -> CInt -> CInt ->
                PreferBlankingMode -> AllowExposuresMode -> IO ()

-- | interface to the X11 library function @XActivateScreenSaver()@.
foreign import ccall unsafe "HsXlib.h XActivateScreenSaver"
        activateScreenSaver :: Display -> IO ()

-- | interface to the X11 library function @XResetScreenSaver()@.
foreign import ccall unsafe "HsXlib.h XResetScreenSaver"
        resetScreenSaver    :: Display -> IO ()

-- | interface to the X11 library function @XForceScreenSaver()@.
foreign import ccall unsafe "HsXlib.h XForceScreenSaver"
        forceScreenSaver    :: Display -> ScreenSaverMode -> IO ()

----------------------------------------------------------------
-- Pointer
----------------------------------------------------------------

-- | interface to the X11 library function @XGetPointerControl()@.
getPointerControl :: Display -> IO (CInt, CInt, CInt)
getPointerControl :: Display -> IO (CInt, CInt, CInt)
getPointerControl Display
display = forall a b c r.
(Storable a, Storable b, Storable c) =>
(IO r -> IO ())
-> (Ptr a -> Ptr b -> Ptr c -> IO r) -> IO (a, b, c)
outParameters3 forall a. a -> a
id (Display -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()
xGetPointerControl Display
display)
foreign import ccall unsafe "HsXlib.h XGetPointerControl"
        xGetPointerControl :: Display -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()

-- | interface to the X11 library function @XWarpPointer()@.
foreign import ccall unsafe "HsXlib.h XWarpPointer"
        warpPointer :: Display -> Window -> Window -> Position -> Position ->
                Dimension -> Dimension -> Position -> Position -> IO ()

-- XGetPointerMapping omitted
-- XSetPointerMapping omitted

----------------------------------------------------------------
-- Visuals
----------------------------------------------------------------

-- | see @XVisualIDFromVisual()@
foreign import ccall unsafe "HsXlib.h XVisualIDFromVisual"
        visualIDFromVisual :: Visual -> IO VisualID

type VisualInfoMask = CLong
visualNoMask  :: VisualInfoMask
visualNoMask :: VisualInfoMask
visualNoMask  =  VisualInfoMask
0
visualIDMask  :: VisualInfoMask
visualIDMask :: VisualInfoMask
visualIDMask  =  VisualInfoMask
1
visualScreenMask  :: VisualInfoMask
visualScreenMask :: VisualInfoMask
visualScreenMask  =  VisualInfoMask
2
visualDepthMask  :: VisualInfoMask
visualDepthMask :: VisualInfoMask
visualDepthMask  =  VisualInfoMask
4
visualClassMask  :: VisualInfoMask
visualClassMask :: VisualInfoMask
visualClassMask  =  VisualInfoMask
8
visualRedMaskMask  :: VisualInfoMask
visualRedMaskMask :: VisualInfoMask
visualRedMaskMask  =  VisualInfoMask
16
visualGreenMaskMask  :: VisualInfoMask
visualGreenMaskMask :: VisualInfoMask
visualGreenMaskMask  =  VisualInfoMask
32
visualBlueMaskMask  :: VisualInfoMask
visualBlueMaskMask :: VisualInfoMask
visualBlueMaskMask  =  VisualInfoMask
64
visualColormapSizeMask  :: VisualInfoMask
visualColormapSizeMask :: VisualInfoMask
visualColormapSizeMask  =  VisualInfoMask
128
visualBitsPerRGBMask  :: VisualInfoMask
visualBitsPerRGBMask  =  256
visualAllMask  :: VisualInfoMask
visualAllMask  =  511

{-# LINE 711 "Graphics/X11/Xlib/Misc.hsc" #-}

-- | interface to the X11 library function @XGetVisualInfo()@
getVisualInfo :: Display -> VisualInfoMask -> VisualInfo -> IO [VisualInfo]
getVisualInfo dpy mask template =
        alloca $ \nItemsPtr ->
        with template $ \templatePtr -> do
        itemsPtr <- xGetVisualInfo dpy mask templatePtr nItemsPtr
        if itemsPtr == nullPtr
                then return []
                else do
                        nItems <- peek nItemsPtr
                        items <- peekArray (fromIntegral nItems) itemsPtr
                        _ <- xFree itemsPtr
                        return items

foreign import ccall unsafe "XGetVisualInfo"
        xGetVisualInfo :: Display -> VisualInfoMask -> Ptr VisualInfo ->
                Ptr CInt -> IO (Ptr VisualInfo)

-- | interface to the X11 library function @XMatchVisualInfo()@
matchVisualInfo
        :: Display -> ScreenNumber -> CInt -> CInt -> IO (Maybe VisualInfo)
matchVisualInfo :: Display -> Word32 -> CInt -> CInt -> IO (Maybe VisualInfo)
matchVisualInfo Display
dpy Word32
screen CInt
depth CInt
class_ =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr VisualInfo
infoPtr -> do
        CInt
status <- Display -> Word32 -> CInt -> CInt -> Ptr VisualInfo -> IO CInt
xMatchVisualInfo Display
dpy Word32
screen CInt
depth CInt
class_ Ptr VisualInfo
infoPtr
        if CInt
status forall a. Eq a => a -> a -> Bool
== CInt
0
                then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
                else do
                        VisualInfo
info <- forall a. Storable a => Ptr a -> IO a
peek Ptr VisualInfo
infoPtr
                        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just VisualInfo
info

foreign import ccall unsafe "XMatchVisualInfo"
        xMatchVisualInfo :: Display -> ScreenNumber -> CInt -> CInt ->
                Ptr VisualInfo -> IO Status

----------------------------------------------------------------
-- Threads
----------------------------------------------------------------

foreign import ccall unsafe "HsXlib.h XInitThreads"
        initThreads :: IO Status

foreign import ccall unsafe "HsXlib.h XLockDisplay"
        lockDisplay :: Display -> IO ()

foreign import ccall unsafe "HsXlib.h XUnlockDisplay"
        unlockDisplay :: Display -> IO ()

----------------------------------------------------------------
-- Pixmaps
----------------------------------------------------------------

-- | interface to the X11 library function @XCreatePixmap()@.
foreign import ccall unsafe "HsXlib.h XCreatePixmap"
        createPixmap :: Display -> Drawable -> Dimension -> Dimension -> CInt -> IO Pixmap

-- | interface to the X11 library function @XFreePixmap()@.
foreign import ccall unsafe "HsXlib.h XFreePixmap"
        freePixmap :: Display -> Pixmap -> IO ()

-- XCreatePixmapFromBitmapData omitted (type looks strange)

-- %fun XListPixmapFormatValues = res1 = XListPixmapFormatValues(display, &res1_size) :: Display -> ListXPixmapFormatValues

----------------------------------------------------------------
-- Bitmaps
----------------------------------------------------------------

-- ToDo: do these need to be available to the programmer?
-- Maybe I could just wire them into all other operations?

-- | interface to the X11 library function @XBitmapBitOrder()@.
foreign import ccall unsafe "HsXlib.h XBitmapBitOrder"
        bitmapBitOrder :: Display -> ByteOrder

-- | interface to the X11 library function @XBitmapUnit()@.
foreign import ccall unsafe "HsXlib.h XBitmapUnit"
        bitmapUnit     :: Display -> CInt

-- | interface to the X11 library function @XBitmapPad()@.
foreign import ccall unsafe "HsXlib.h XBitmapPad"
        bitmapPad      :: Display -> CInt

-- ToDo: make sure that initialisation works correctly for x/y_hot
-- omitted
-- IMPURE void  XWriteBitmapFile(display, filename, bitmap, width, height, x_hot, y_hot) RAISES Either
-- RETURNTYPE   BitmapFileStatus
-- GLOBAL ERROR BitmapFileStatus        RETVAL
-- IN Display*  display
-- IN String    filename
-- IN Pixmap    bitmap
-- IN Dimension width
-- IN Dimension height
-- IN Maybe Int x_hot = -1
-- IN Maybe Int y_hot = -1
-- POST: RETVAL == BitmapSuccess

-- added: unstable
-- IMPURE void  XReadBitmapFile(display, d, filename, bitmap, width, height, x_hot, y_hot) RAISES Either
-- RETURNTYPE   BitmapFileStatus
-- GLOBAL ERROR BitmapFileStatus        RETVAL
-- IN Display*  display
-- IN Drawable  d
-- IN String    filename
-- OUT Pixmap   bitmap
-- OUT Dimension        width
-- OUT Dimension        height
-- OUT Int              x_hot RAISES Maybe IF x_hot == -1
-- OUT Int              y_hot RAISES Maybe IF x_hot == -1
-- POST: RETVAL == BitmapSuccess

-- | interface to the X11 library function @XReadBitmapFile@.
readBitmapFile :: Display -> Drawable -> String
                  -> IO (Either String (Dimension, Dimension, Pixmap, Maybe CInt, Maybe CInt))
readBitmapFile :: Display
-> Atom
-> String
-> IO
     (Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
readBitmapFile Display
display Atom
d String
filename =
  forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
filename forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_filename ->
  forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
width_return ->
  forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
height_return ->
  forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
bitmap_return ->
  forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
x_hot_return ->
  forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
y_hot_return -> do
    CInt
rv <- Display
-> Atom
-> Ptr CChar
-> Ptr Word32
-> Ptr Word32
-> Ptr Atom
-> Ptr CInt
-> Ptr CInt
-> IO CInt
xReadBitmapFile Display
display Atom
d Ptr CChar
c_filename Ptr Word32
width_return Ptr Word32
height_return
         Ptr Atom
bitmap_return Ptr CInt
x_hot_return Ptr CInt
y_hot_return
    Word32
width <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
width_return
    Word32
height <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
height_return
    Atom
bitmap <- forall a. Storable a => Ptr a -> IO a
peek Ptr Atom
bitmap_return
    CInt
x_hot <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
x_hot_return
    CInt
y_hot <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
y_hot_return
    let m_x_hot :: Maybe CInt
m_x_hot | CInt
x_hot forall a. Eq a => a -> a -> Bool
== -CInt
1 = forall a. Maybe a
Nothing
                | Bool
otherwise  = forall a. a -> Maybe a
Just CInt
x_hot
        m_y_hot :: Maybe CInt
m_y_hot | CInt
y_hot forall a. Eq a => a -> a -> Bool
== -CInt
1 = forall a. Maybe a
Nothing
                | Bool
otherwise  = forall a. a -> Maybe a
Just CInt
y_hot
    case CInt
rv of
        CInt
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Word32
width, Word32
height, Atom
bitmap, Maybe CInt
m_x_hot, Maybe CInt
m_y_hot)
        CInt
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapOpenFailed"
        CInt
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapFileInvalid"
        CInt
3 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapNoMemory"
        CInt
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapUnknownError"
foreign import ccall unsafe "X11/Xlib.h XReadBitmapFile"
  xReadBitmapFile :: Display -> Drawable -> CString -> Ptr Dimension -> Ptr Dimension
                     -> Ptr Pixmap -> Ptr CInt -> Ptr CInt -> IO CInt

-- XCreateBitmapFromData omitted (awkward looking type)
-- XReadBitmapFileData omitted (awkward looking type)

----------------------------------------------------------------
-- Keycodes
----------------------------------------------------------------

-- | interface to the X11 library function @XDisplayKeycodes()@.
displayKeycodes :: Display -> (CInt,CInt)
displayKeycodes :: Display -> (CInt, CInt)
displayKeycodes Display
display =
        forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ Display -> Ptr CInt -> Ptr CInt -> IO ()
xDisplayKeycodes Display
display
foreign import ccall unsafe "HsXlib.h XDisplayKeycodes"
        xDisplayKeycodes :: Display -> Ptr CInt -> Ptr CInt -> IO ()

-- | interface to the X11 library function @XLookupKeysym()@.
foreign import ccall unsafe "HsXlib.h XLookupKeysym"
        lookupKeysym    :: XKeyEventPtr -> CInt -> IO KeySym

-- | interface to the X11 library function @XKeycodeToKeysym()@.
foreign import ccall unsafe "HsXlib.h XKeycodeToKeysym"
        keycodeToKeysym :: Display -> KeyCode -> CInt -> IO KeySym

-- | interface to the X11 library function @XKeysymToKeycode()@.
foreign import ccall unsafe "HsXlib.h XKeysymToKeycode"
        keysymToKeycode :: Display -> KeySym  -> IO KeyCode

-- | interface to the X11 library function @XKeysymToString()@.
keysymToString  :: KeySym -> String
keysymToString :: Atom -> String
keysymToString Atom
keysym = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
        Ptr CChar
c_str <- Atom -> IO (Ptr CChar)
xKeysymToString Atom
keysym
        Ptr CChar -> IO String
peekCString Ptr CChar
c_str
foreign import ccall unsafe "HsXlib.h XKeysymToString"
        xKeysymToString  :: KeySym -> IO CString

-- | interface to the X11 library function @XStringToKeysym()@.
stringToKeysym  :: String -> KeySym
stringToKeysym :: String -> Atom
stringToKeysym String
str = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$
        forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
str forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_str ->
        Ptr CChar -> IO Atom
xStringToKeysym Ptr CChar
c_str
foreign import ccall unsafe "HsXlib.h XStringToKeysym"
        xStringToKeysym  :: CString -> IO KeySym

noSymbol :: KeySym
noSymbol :: Atom
noSymbol = Atom
0
{-# LINE 897 "Graphics/X11/Xlib/Misc.hsc" #-}

newtype XComposeStatus = XComposeStatus (Ptr XComposeStatus)

{-# LINE 900 "Graphics/X11/Xlib/Misc.hsc" #-}
        deriving (XComposeStatus -> XComposeStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XComposeStatus -> XComposeStatus -> Bool
$c/= :: XComposeStatus -> XComposeStatus -> Bool
== :: XComposeStatus -> XComposeStatus -> Bool
$c== :: XComposeStatus -> XComposeStatus -> Bool
Eq, Eq XComposeStatus
XComposeStatus -> XComposeStatus -> Bool
XComposeStatus -> XComposeStatus -> Ordering
XComposeStatus -> XComposeStatus -> XComposeStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: XComposeStatus -> XComposeStatus -> XComposeStatus
$cmin :: XComposeStatus -> XComposeStatus -> XComposeStatus
max :: XComposeStatus -> XComposeStatus -> XComposeStatus
$cmax :: XComposeStatus -> XComposeStatus -> XComposeStatus
>= :: XComposeStatus -> XComposeStatus -> Bool
$c>= :: XComposeStatus -> XComposeStatus -> Bool
> :: XComposeStatus -> XComposeStatus -> Bool
$c> :: XComposeStatus -> XComposeStatus -> Bool
<= :: XComposeStatus -> XComposeStatus -> Bool
$c<= :: XComposeStatus -> XComposeStatus -> Bool
< :: XComposeStatus -> XComposeStatus -> Bool
$c< :: XComposeStatus -> XComposeStatus -> Bool
compare :: XComposeStatus -> XComposeStatus -> Ordering
$ccompare :: XComposeStatus -> XComposeStatus -> Ordering
Ord, Int -> XComposeStatus -> String -> String
[XComposeStatus] -> String -> String
XComposeStatus -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [XComposeStatus] -> String -> String
$cshowList :: [XComposeStatus] -> String -> String
show :: XComposeStatus -> String
$cshow :: XComposeStatus -> String
showsPrec :: Int -> XComposeStatus -> String -> String
$cshowsPrec :: Int -> XComposeStatus -> String -> String
Show, Typeable, Typeable XComposeStatus
XComposeStatus -> DataType
XComposeStatus -> Constr
(forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u
forall u. (forall d. Data d => d -> u) -> XComposeStatus -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XComposeStatus)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XComposeStatus)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> XComposeStatus -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XComposeStatus -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
gmapT :: (forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
$cgmapT :: (forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XComposeStatus)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XComposeStatus)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XComposeStatus)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XComposeStatus)
dataTypeOf :: XComposeStatus -> DataType
$cdataTypeOf :: XComposeStatus -> DataType
toConstr :: XComposeStatus -> Constr
$ctoConstr :: XComposeStatus -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
Data)

{-# LINE 904 "Graphics/X11/Xlib/Misc.hsc" #-}

-- XLookupString cannot handle compose, it seems.

-- | interface to the X11 library function @XLookupString()@.
lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String)
lookupString :: XKeyEventPtr -> IO (Maybe Atom, String)
lookupString XKeyEventPtr
event_ptr =
        forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
100 forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
buf ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
keysym_return -> do
        CInt
n <- XKeyEventPtr
-> Ptr CChar -> CInt -> Ptr Atom -> Ptr XComposeStatus -> IO CInt
xLookupString XKeyEventPtr
event_ptr Ptr CChar
buf CInt
100 Ptr Atom
keysym_return forall a. Ptr a
nullPtr
        String
str <- CStringLen -> IO String
peekCStringLen (Ptr CChar
buf, forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
n)
        Atom
keysym <- forall a. Storable a => Ptr a -> IO a
peek Ptr Atom
keysym_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (if Atom
keysym forall a. Eq a => a -> a -> Bool
== Atom
noSymbol then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just Atom
keysym, String
str)
foreign import ccall unsafe "HsXlib.h XLookupString"
        xLookupString :: XKeyEventPtr -> CString -> CInt ->
                Ptr KeySym -> Ptr XComposeStatus -> IO CInt

-- XQueryKeymap omitted
-- XRebindKeysym omitted
-- XDeleteModifiermapEntry omitted
-- XInsertModifiermapEntry omitted
-- XNewModifiermap omitted
-- XFreeModifiermap omitted
-- XSetModifierMapping omitted
-- XGetModifierMapping omitted
-- XGetKeyboardMapping omitted

----------------------------------------------------------------
-- Icons
----------------------------------------------------------------

-- | interface to the X11 library function @XGetIconName()@.
getIconName :: Display -> Window -> IO String
getIconName :: Display -> Atom -> IO String
getIconName Display
display Atom
w =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr (Ptr CChar)
icon_name_return -> do
        String -> IO CInt -> IO ()
throwIfZero String
"getIconName" forall a b. (a -> b) -> a -> b
$
                Display -> Atom -> Ptr (Ptr CChar) -> IO CInt
xGetIconName Display
display Atom
w Ptr (Ptr CChar)
icon_name_return
        Ptr CChar
c_icon_name <- forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CChar)
icon_name_return
        Ptr CChar -> IO String
peekCString Ptr CChar
c_icon_name
foreign import ccall unsafe "HsXlib.h XGetIconName"
        xGetIconName :: Display -> Window -> Ptr CString -> IO Status

-- | interface to the X11 library function @XSetIconName()@.
setIconName :: Display -> Window -> String -> IO ()
setIconName :: Display -> Atom -> String -> IO ()
setIconName Display
display Atom
w String
icon_name =
        forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
icon_name forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_icon_name ->
        Display -> Atom -> Ptr CChar -> IO ()
xSetIconName Display
display Atom
w Ptr CChar
c_icon_name
foreign import ccall unsafe "HsXlib.h XSetIconName"
        xSetIconName :: Display -> Window -> CString -> IO ()

----------------------------------------------------------------
-- Cursors
----------------------------------------------------------------

-- | interface to the X11 library function @XDefineCursor()@.
foreign import ccall unsafe "HsXlib.h XDefineCursor"
        defineCursor       :: Display -> Window -> Cursor -> IO ()

-- | interface to the X11 library function @XUndefineCursor()@.
foreign import ccall unsafe "HsXlib.h XUndefineCursor"
        undefineCursor     :: Display -> Window -> IO ()

-- | interface to the X11 library function @XCreatePixmapCursor()@.
createPixmapCursor :: Display -> Pixmap -> Pixmap -> Color -> Color ->
        Dimension -> Dimension -> IO Cursor
createPixmapCursor :: Display
-> Atom -> Atom -> Color -> Color -> Word32 -> Word32 -> IO Atom
createPixmapCursor Display
display Atom
source Atom
mask Color
fg_color Color
bg_color Word32
x Word32
y =
        forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
        forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color forall a b. (a -> b) -> a -> b
$ \ Ptr Color
bg_color_ptr ->
        Display
-> Atom
-> Atom
-> Ptr Color
-> Ptr Color
-> Word32
-> Word32
-> IO Atom
xCreatePixmapCursor Display
display Atom
source Atom
mask Ptr Color
fg_color_ptr Ptr Color
bg_color_ptr Word32
x Word32
y
foreign import ccall unsafe "HsXlib.h XCreatePixmapCursor"
        xCreatePixmapCursor :: Display -> Pixmap -> Pixmap ->
                Ptr Color -> Ptr Color -> Dimension -> Dimension -> IO Cursor

-- | interface to the X11 library function @XCreateGlyphCursor()@.
createGlyphCursor  :: Display -> Font   -> Font -> Glyph -> Glyph ->
        Color -> Color -> IO Cursor
createGlyphCursor :: Display
-> Atom -> Atom -> Glyph -> Glyph -> Color -> Color -> IO Atom
createGlyphCursor Display
display Atom
source_font Atom
mask_font Glyph
source_char Glyph
mask_char
                Color
fg_color Color
bg_color =
        forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
        forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color forall a b. (a -> b) -> a -> b
$ \ Ptr Color
bg_color_ptr ->
        Display
-> Atom
-> Atom
-> Glyph
-> Glyph
-> Ptr Color
-> Ptr Color
-> IO Atom
xCreateGlyphCursor Display
display Atom
source_font Atom
mask_font Glyph
source_char Glyph
mask_char
                Ptr Color
fg_color_ptr Ptr Color
bg_color_ptr
foreign import ccall unsafe "HsXlib.h XCreateGlyphCursor"
        xCreateGlyphCursor  :: Display -> Font   -> Font -> Glyph -> Glyph ->
                Ptr Color -> Ptr Color -> IO Cursor

-- | interface to the X11 library function @XCreateFontCursor()@.
foreign import ccall unsafe "HsXlib.h XCreateFontCursor"
        createFontCursor   :: Display -> Glyph  -> IO Cursor

-- | interface to the X11 library function @XFreeCursor()@.
foreign import ccall unsafe "HsXlib.h XFreeCursor"
        freeCursor         :: Display -> Font   -> IO ()

-- | interface to the X11 library function @XRecolorCursor()@.
recolorCursor      :: Display -> Cursor -> Color -> Color -> IO ()
recolorCursor :: Display -> Atom -> Color -> Color -> IO ()
recolorCursor Display
display Atom
cursor Color
fg_color Color
bg_color =
        forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
        forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color forall a b. (a -> b) -> a -> b
$ \ Ptr Color
bg_color_ptr ->
        Display -> Atom -> Ptr Color -> Ptr Color -> IO ()
xRecolorCursor Display
display Atom
cursor Ptr Color
fg_color_ptr Ptr Color
bg_color_ptr
foreign import ccall unsafe "HsXlib.h XRecolorCursor"
        xRecolorCursor      :: Display -> Cursor -> Ptr Color -> Ptr Color -> IO ()

----------------------------------------------------------------
-- Window Manager stuff
----------------------------------------------------------------

-- XConfigureWMWindow omitted (can't find documentation)
-- XReconfigureWMWindow omitted (can't find documentation)
-- XWMGeometry omitted (can't find documentation)
-- XGetWMColormapWindows omitted (can't find documentation)
-- XSetWMColormapWindows omitted (can't find documentation)
-- XGetWMProtocols omitted

-- AC, 1/9/2000: Added definition for XSetWMProtocols

-- | interface to the X11 library function @XSetWMProtocols()@.
setWMProtocols :: Display -> Window -> [Atom] -> IO ()
setWMProtocols :: Display -> Atom -> [Atom] -> IO ()
setWMProtocols Display
display Atom
w [Atom]
protocols =
        forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [Atom]
protocols forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
protocol_array ->
        Display -> Atom -> Ptr Atom -> CInt -> IO ()
xSetWMProtocols Display
display Atom
w Ptr Atom
protocol_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Atom]
protocols)
foreign import ccall unsafe "HsXlib.h XSetWMProtocols"
        xSetWMProtocols :: Display -> Window -> Ptr Atom -> CInt -> IO ()

----------------------------------------------------------------
-- Set Window Attributes
----------------------------------------------------------------

-- ToDo: generate this kind of stuff automatically.

allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a
allocaSetWindowAttributes :: forall a. (Ptr SetWindowAttributes -> IO a) -> IO a
allocaSetWindowAttributes = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
112)
{-# LINE 1035 "Graphics/X11/Xlib/Misc.hsc" #-}

---------------- Access to individual fields ----------------

set_background_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO ()
set_background_pixmap :: Ptr SetWindowAttributes -> Atom -> IO ()
set_background_pixmap = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
0)
{-# LINE 1040 "Graphics/X11/Xlib/Misc.hsc" #-}

set_background_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_background_pixel :: Ptr SetWindowAttributes -> Atom -> IO ()
set_background_pixel = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
8)
{-# LINE 1043 "Graphics/X11/Xlib/Misc.hsc" #-}

set_border_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO ()
set_border_pixmap :: Ptr SetWindowAttributes -> Atom -> IO ()
set_border_pixmap = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
16)
{-# LINE 1046 "Graphics/X11/Xlib/Misc.hsc" #-}

set_border_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_border_pixel :: Ptr SetWindowAttributes -> Atom -> IO ()
set_border_pixel = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
24)
{-# LINE 1049 "Graphics/X11/Xlib/Misc.hsc" #-}

set_bit_gravity :: Ptr SetWindowAttributes -> BitGravity -> IO ()
set_bit_gravity :: Ptr SetWindowAttributes -> CInt -> IO ()
set_bit_gravity = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
32)
{-# LINE 1052 "Graphics/X11/Xlib/Misc.hsc" #-}

set_win_gravity :: Ptr SetWindowAttributes -> WindowGravity -> IO ()
set_win_gravity :: Ptr SetWindowAttributes -> CInt -> IO ()
set_win_gravity = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
36)
{-# LINE 1055 "Graphics/X11/Xlib/Misc.hsc" #-}

set_backing_store :: Ptr SetWindowAttributes -> BackingStore -> IO ()
set_backing_store :: Ptr SetWindowAttributes -> CInt -> IO ()
set_backing_store = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
40)
{-# LINE 1058 "Graphics/X11/Xlib/Misc.hsc" #-}

set_backing_planes :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_backing_planes :: Ptr SetWindowAttributes -> Atom -> IO ()
set_backing_planes = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
48)
{-# LINE 1061 "Graphics/X11/Xlib/Misc.hsc" #-}

set_backing_pixel :: Ptr SetWindowAttributes -> Pixel -> IO ()
set_backing_pixel :: Ptr SetWindowAttributes -> Atom -> IO ()
set_backing_pixel = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
56)
{-# LINE 1064 "Graphics/X11/Xlib/Misc.hsc" #-}

set_save_under :: Ptr SetWindowAttributes -> Bool -> IO ()
set_save_under :: Ptr SetWindowAttributes -> Bool -> IO ()
set_save_under = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
64)
{-# LINE 1067 "Graphics/X11/Xlib/Misc.hsc" #-}

set_event_mask :: Ptr SetWindowAttributes -> EventMask -> IO ()
set_event_mask :: Ptr SetWindowAttributes -> Atom -> IO ()
set_event_mask = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
72)
{-# LINE 1070 "Graphics/X11/Xlib/Misc.hsc" #-}

set_do_not_propagate_mask :: Ptr SetWindowAttributes -> EventMask -> IO ()
set_do_not_propagate_mask :: Ptr SetWindowAttributes -> Atom -> IO ()
set_do_not_propagate_mask = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
80)
{-# LINE 1073 "Graphics/X11/Xlib/Misc.hsc" #-}

set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO ()
set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO ()
set_override_redirect = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
88)
{-# LINE 1076 "Graphics/X11/Xlib/Misc.hsc" #-}

set_colormap :: Ptr SetWindowAttributes -> Colormap -> IO ()
set_colormap :: Ptr SetWindowAttributes -> Atom -> IO ()
set_colormap = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
96)
{-# LINE 1079 "Graphics/X11/Xlib/Misc.hsc" #-}

set_cursor :: Ptr SetWindowAttributes -> Cursor -> IO ()
set_cursor :: Ptr SetWindowAttributes -> Atom -> IO ()
set_cursor = (\Ptr SetWindowAttributes
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
104)
{-# LINE 1082 "Graphics/X11/Xlib/Misc.hsc" #-}

----------------------------------------------------------------
-- Drawing
----------------------------------------------------------------

-- | interface to the X11 library function @XDrawPoint()@.
foreign import ccall unsafe "HsXlib.h XDrawPoint"
        drawPoint      :: Display -> Drawable -> GC -> Position -> Position -> IO ()

-- | interface to the X11 library function @XDrawPoints()@.
drawPoints :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO ()
drawPoints :: Display -> Atom -> GC -> [Point] -> CInt -> IO ()
drawPoints Display
display Atom
d GC
gc [Point]
points CInt
mode =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Point]
points forall a b. (a -> b) -> a -> b
$ \ Int
npoints Ptr Point
point_array ->
        Display -> Atom -> GC -> Ptr Point -> CInt -> CInt -> IO ()
xDrawPoints Display
display Atom
d GC
gc Ptr Point
point_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
npoints) CInt
mode
foreign import ccall unsafe "HsXlib.h XDrawPoints"
        xDrawPoints     :: Display -> Drawable -> GC -> Ptr Point -> CInt ->
                                CoordinateMode -> IO ()

-- | interface to the X11 library function @XDrawLine()@.
foreign import ccall unsafe "HsXlib.h XDrawLine"
        drawLine       :: Display -> Drawable -> GC -> Position -> Position ->
                                Position -> Position -> IO ()

-- | interface to the X11 library function @XDrawLines()@.
drawLines :: Display -> Drawable -> GC -> [Point] -> CoordinateMode -> IO ()
drawLines :: Display -> Atom -> GC -> [Point] -> CInt -> IO ()
drawLines Display
display Atom
d GC
gc [Point]
points CInt
mode =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Point]
points forall a b. (a -> b) -> a -> b
$ \ Int
npoints Ptr Point
point_array ->
        Display -> Atom -> GC -> Ptr Point -> CInt -> CInt -> IO ()
xDrawLines Display
display Atom
d GC
gc Ptr Point
point_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
npoints) CInt
mode
foreign import ccall unsafe "HsXlib.h XDrawLines"
        xDrawLines      :: Display -> Drawable -> GC -> Ptr Point -> CInt ->
                                CoordinateMode -> IO ()

-- | interface to the X11 library function @XDrawSegments()@.
drawSegments :: Display -> Drawable -> GC -> [Segment] -> IO ()
drawSegments :: Display -> Atom -> GC -> [Segment] -> IO ()
drawSegments Display
display Atom
d GC
gc [Segment]
segments =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Segment]
segments forall a b. (a -> b) -> a -> b
$ \ Int
nsegments Ptr Segment
segment_array ->
        Display -> Atom -> GC -> Ptr Segment -> CInt -> IO ()
xDrawSegments Display
display Atom
d GC
gc Ptr Segment
segment_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nsegments)
foreign import ccall unsafe "HsXlib.h XDrawSegments"
        xDrawSegments   :: Display -> Drawable -> GC -> Ptr Segment -> CInt -> IO ()

-- | interface to the X11 library function @XDrawRectangle()@.
foreign import ccall unsafe "HsXlib.h XDrawRectangle"
        drawRectangle  :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO ()

-- | interface to the X11 library function @XDrawRectangles()@.
drawRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
drawRectangles :: Display -> Atom -> GC -> [Rectangle] -> IO ()
drawRectangles Display
display Atom
d GC
gc [Rectangle]
rectangles =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Rectangle]
rectangles forall a b. (a -> b) -> a -> b
$ \ Int
nrectangles Ptr Rectangle
rectangle_array ->
        Display -> Atom -> GC -> Ptr Rectangle -> CInt -> IO ()
xDrawRectangles Display
display Atom
d GC
gc Ptr Rectangle
rectangle_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nrectangles)
foreign import ccall unsafe "HsXlib.h XDrawRectangles"
        xDrawRectangles :: Display -> Drawable -> GC -> Ptr Rectangle -> CInt -> IO ()

-- | interface to the X11 library function @XDrawArc()@.
foreign import ccall unsafe "HsXlib.h XDrawArc"
        drawArc        :: Display -> Drawable -> GC -> Position -> Position ->
                        Dimension -> Dimension -> Angle -> Angle -> IO ()

-- | interface to the X11 library function @XDrawArcs()@.
drawArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
drawArcs :: Display -> Atom -> GC -> [Arc] -> IO ()
drawArcs Display
display Atom
d GC
gc [Arc]
arcs =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Arc]
arcs forall a b. (a -> b) -> a -> b
$ \ Int
narcs Ptr Arc
arc_array ->
        Display -> Atom -> GC -> Ptr Arc -> CInt -> IO ()
xDrawArcs Display
display Atom
d GC
gc Ptr Arc
arc_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
narcs)
foreign import ccall unsafe "HsXlib.h XDrawArcs"
        xDrawArcs       :: Display -> Drawable -> GC -> Ptr Arc -> CInt -> IO ()

-- | interface to the X11 library function @XFillRectangle()@.
foreign import ccall unsafe "HsXlib.h XFillRectangle"
        fillRectangle  :: Display -> Drawable -> GC -> Position -> Position ->
                                Dimension -> Dimension -> IO ()

-- | interface to the X11 library function @XFillRectangles()@.
fillRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
fillRectangles :: Display -> Atom -> GC -> [Rectangle] -> IO ()
fillRectangles Display
display Atom
d GC
gc [Rectangle]
rectangles =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Rectangle]
rectangles forall a b. (a -> b) -> a -> b
$ \ Int
nrectangles Ptr Rectangle
rectangle_array ->
        Display -> Atom -> GC -> Ptr Rectangle -> CInt -> IO ()
xFillRectangles Display
display Atom
d GC
gc Ptr Rectangle
rectangle_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nrectangles)
foreign import ccall unsafe "HsXlib.h XFillRectangles"
        xFillRectangles :: Display -> Drawable -> GC -> Ptr Rectangle -> CInt -> IO ()

-- | interface to the X11 library function @XFillPolygon()@.
fillPolygon :: Display -> Drawable -> GC -> [Point] -> PolygonShape -> CoordinateMode -> IO ()
fillPolygon :: Display -> Atom -> GC -> [Point] -> CInt -> CInt -> IO ()
fillPolygon Display
display Atom
d GC
gc [Point]
points CInt
shape CInt
mode =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Point]
points forall a b. (a -> b) -> a -> b
$ \ Int
npoints Ptr Point
point_array ->
        Display -> Atom -> GC -> Ptr Point -> CInt -> CInt -> CInt -> IO ()
xFillPolygon Display
display Atom
d GC
gc Ptr Point
point_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
npoints) CInt
shape CInt
mode
foreign import ccall unsafe "HsXlib.h XFillPolygon"
        xFillPolygon    :: Display -> Drawable -> GC -> Ptr Point -> CInt -> PolygonShape -> CoordinateMode -> IO ()

-- | interface to the X11 library function @XFillArc()@.
foreign import ccall unsafe "HsXlib.h XFillArc"
        fillArc        :: Display -> Drawable -> GC -> Position -> Position ->
                        Dimension -> Dimension -> Angle -> Angle -> IO ()

-- | interface to the X11 library function @XFillArcs()@.
fillArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
fillArcs :: Display -> Atom -> GC -> [Arc] -> IO ()
fillArcs Display
display Atom
d GC
gc [Arc]
arcs =
        forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Arc]
arcs forall a b. (a -> b) -> a -> b
$ \ Int
narcs Ptr Arc
arc_array ->
        Display -> Atom -> GC -> Ptr Arc -> CInt -> IO ()
xFillArcs Display
display Atom
d GC
gc Ptr Arc
arc_array (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
narcs)
foreign import ccall unsafe "HsXlib.h XFillArcs"
        xFillArcs       :: Display -> Drawable -> GC -> Ptr Arc -> CInt -> IO ()

-- | interface to the X11 library function @XCopyArea()@.
foreign import ccall unsafe "HsXlib.h XCopyArea"
        copyArea       :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO ()

-- | interface to the X11 library function @XCopyPlane()@.
foreign import ccall unsafe "HsXlib.h XCopyPlane"
        copyPlane      :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> Pixel -> IO ()

-- draw characters over existing background

-- | interface to the X11 library function @XDrawString()@.
drawString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO ()
drawString :: Display -> Atom -> GC -> Position -> Position -> String -> IO ()
drawString Display
display Atom
d GC
gc Position
x Position
y String
str =
        forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
str forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_str, Int
len) ->
        Display
-> Atom -> GC -> Position -> Position -> Ptr CChar -> CInt -> IO ()
xDrawString Display
display Atom
d GC
gc Position
x Position
y Ptr CChar
c_str (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
foreign import ccall unsafe "HsXlib.h XDrawString"
        xDrawString     :: Display -> Drawable -> GC -> Position -> Position -> CString -> CInt -> IO ()

-- draw characters over a blank rectangle of current background colour

-- | interface to the X11 library function @XDrawImageString()@.
drawImageString :: Display -> Drawable -> GC -> Position -> Position -> String -> IO ()
drawImageString :: Display -> Atom -> GC -> Position -> Position -> String -> IO ()
drawImageString Display
display Atom
d GC
gc Position
x Position
y String
str =
        forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
str forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_str, Int
len) ->
        Display
-> Atom -> GC -> Position -> Position -> Ptr CChar -> CInt -> IO ()
xDrawImageString Display
display Atom
d GC
gc Position
x Position
y Ptr CChar
c_str (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
foreign import ccall unsafe "HsXlib.h XDrawImageString"
        xDrawImageString :: Display -> Drawable -> GC -> Position -> Position -> CString -> CInt -> IO ()

-- XDrawString16 omitted (16bit chars not supported)
-- XDrawImageString16 omitted (16bit chars not supported)
-- XDrawText omitted (XTextItem not supported)
-- XDrawText16 omitted (XTextItem not supported)

----------------------------------------------------------------
-- Cut and paste buffers
----------------------------------------------------------------

-- | interface to the X11 library function @XStoreBuffer()@.
storeBuffer :: Display -> String -> CInt -> IO ()
storeBuffer :: Display -> String -> CInt -> IO ()
storeBuffer Display
display String
bytes CInt
buffer =
        forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
bytes forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_bytes, Int
nbytes) ->
        String -> IO CInt -> IO ()
throwIfZero String
"storeBuffer" forall a b. (a -> b) -> a -> b
$
                Display -> Ptr CChar -> CInt -> CInt -> IO CInt
xStoreBuffer Display
display Ptr CChar
c_bytes (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nbytes) CInt
buffer
foreign import ccall unsafe "HsXlib.h XStoreBuffer"
        xStoreBuffer :: Display -> CString -> CInt -> CInt -> IO Status

-- | interface to the X11 library function @XStoreBytes()@.
storeBytes :: Display -> String -> IO ()
storeBytes :: Display -> String -> IO ()
storeBytes Display
display String
bytes =
        forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
bytes forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_bytes, Int
nbytes) ->
        String -> IO CInt -> IO ()
throwIfZero String
"storeBytes" forall a b. (a -> b) -> a -> b
$
                Display -> Ptr CChar -> CInt -> IO CInt
xStoreBytes Display
display Ptr CChar
c_bytes (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nbytes)
foreign import ccall unsafe "HsXlib.h XStoreBytes"
        xStoreBytes :: Display -> CString -> CInt -> IO Status

-- | interface to the X11 library function @XFetchBuffer()@.
fetchBuffer :: Display -> CInt -> IO String
fetchBuffer :: Display -> CInt -> IO String
fetchBuffer Display
display CInt
buffer =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
nbytes_return -> do
        Ptr CChar
c_bytes <- forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"fetchBuffer" forall a b. (a -> b) -> a -> b
$
                Display -> Ptr CInt -> CInt -> IO (Ptr CChar)
xFetchBuffer Display
display Ptr CInt
nbytes_return CInt
buffer
        CInt
nbytes <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
nbytes_return
        String
bytes <- CStringLen -> IO String
peekCStringLen (Ptr CChar
c_bytes, (forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
nbytes))
        CInt
_ <- forall a. Ptr a -> IO CInt
xFree Ptr CChar
c_bytes
        forall (m :: * -> *) a. Monad m => a -> m a
return String
bytes
foreign import ccall unsafe "HsXlib.h XFetchBuffer"
        xFetchBuffer :: Display -> Ptr CInt -> CInt -> IO CString

-- | interface to the X11 library function @XFetchBytes()@.
fetchBytes :: Display -> IO String
fetchBytes :: Display -> IO String
fetchBytes Display
display =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
nbytes_return -> do
        Ptr CChar
c_bytes <- forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"fetchBytes" forall a b. (a -> b) -> a -> b
$
                Display -> Ptr CInt -> IO (Ptr CChar)
xFetchBytes Display
display Ptr CInt
nbytes_return
        CInt
nbytes <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
nbytes_return
        String
bytes <- CStringLen -> IO String
peekCStringLen (Ptr CChar
c_bytes, (forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
nbytes))
        CInt
_ <- forall a. Ptr a -> IO CInt
xFree Ptr CChar
c_bytes
        forall (m :: * -> *) a. Monad m => a -> m a
return String
bytes
foreign import ccall unsafe "HsXlib.h XFetchBytes"
        xFetchBytes :: Display -> Ptr CInt -> IO CString

-- | interface to the X11 library function @XRotateBuffers()@.
rotateBuffers :: Display -> CInt -> IO ()
rotateBuffers :: Display -> CInt -> IO ()
rotateBuffers Display
display CInt
rot =
        String -> IO CInt -> IO ()
throwIfZero String
"rotateBuffers" forall a b. (a -> b) -> a -> b
$
                Display -> CInt -> IO CInt
xRotateBuffers Display
display CInt
rot
foreign import ccall unsafe "HsXlib.h XRotateBuffers"
        xRotateBuffers :: Display -> CInt -> IO Status

----------------------------------------------------------------
-- Window properties
----------------------------------------------------------------

newtype XTextProperty = XTextProperty (Ptr XTextProperty)

{-# LINE 1276 "Graphics/X11/Xlib/Misc.hsc" #-}
        deriving (XTextProperty -> XTextProperty -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XTextProperty -> XTextProperty -> Bool
$c/= :: XTextProperty -> XTextProperty -> Bool
== :: XTextProperty -> XTextProperty -> Bool
$c== :: XTextProperty -> XTextProperty -> Bool
Eq, Eq XTextProperty
XTextProperty -> XTextProperty -> Bool
XTextProperty -> XTextProperty -> Ordering
XTextProperty -> XTextProperty -> XTextProperty
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: XTextProperty -> XTextProperty -> XTextProperty
$cmin :: XTextProperty -> XTextProperty -> XTextProperty
max :: XTextProperty -> XTextProperty -> XTextProperty
$cmax :: XTextProperty -> XTextProperty -> XTextProperty
>= :: XTextProperty -> XTextProperty -> Bool
$c>= :: XTextProperty -> XTextProperty -> Bool
> :: XTextProperty -> XTextProperty -> Bool
$c> :: XTextProperty -> XTextProperty -> Bool
<= :: XTextProperty -> XTextProperty -> Bool
$c<= :: XTextProperty -> XTextProperty -> Bool
< :: XTextProperty -> XTextProperty -> Bool
$c< :: XTextProperty -> XTextProperty -> Bool
compare :: XTextProperty -> XTextProperty -> Ordering
$ccompare :: XTextProperty -> XTextProperty -> Ordering
Ord, Int -> XTextProperty -> String -> String
[XTextProperty] -> String -> String
XTextProperty -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [XTextProperty] -> String -> String
$cshowList :: [XTextProperty] -> String -> String
show :: XTextProperty -> String
$cshow :: XTextProperty -> String
showsPrec :: Int -> XTextProperty -> String -> String
$cshowsPrec :: Int -> XTextProperty -> String -> String
Show, Typeable, Typeable XTextProperty
XTextProperty -> DataType
XTextProperty -> Constr
(forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> XTextProperty -> u
forall u. (forall d. Data d => d -> u) -> XTextProperty -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XTextProperty)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XTextProperty)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XTextProperty -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XTextProperty -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> XTextProperty -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XTextProperty -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
gmapT :: (forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
$cgmapT :: (forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XTextProperty)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XTextProperty)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XTextProperty)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XTextProperty)
dataTypeOf :: XTextProperty -> DataType
$cdataTypeOf :: XTextProperty -> DataType
toConstr :: XTextProperty -> Constr
$ctoConstr :: XTextProperty -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
Data)

{-# LINE 1280 "Graphics/X11/Xlib/Misc.hsc" #-}

-- | interface to the X11 library function @XSetTextProperty()@.
setTextProperty :: Display -> Window -> String -> Atom -> IO ()
setTextProperty :: Display -> Atom -> String -> Atom -> IO ()
setTextProperty Display
display Atom
w String
value Atom
property =
        forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
value forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_value, Int
value_len) ->
        forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
32) forall a b. (a -> b) -> a -> b
$ \ Ptr XTextProperty
text_prop -> do
{-# LINE 1286 "Graphics/X11/Xlib/Misc.hsc" #-}
        (\Ptr XTextProperty
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
0) Ptr XTextProperty
text_prop Ptr CChar
c_value
{-# LINE 1287 "Graphics/X11/Xlib/Misc.hsc" #-}
        (\Ptr XTextProperty
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
8) Ptr XTextProperty
text_prop Atom
sTRING
{-# LINE 1288 "Graphics/X11/Xlib/Misc.hsc" #-}
        (\Ptr XTextProperty
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
16) Ptr XTextProperty
text_prop (CInt
8::CInt)
{-# LINE 1289 "Graphics/X11/Xlib/Misc.hsc" #-}
        (\Ptr XTextProperty
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
24) Ptr XTextProperty
text_prop (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
value_len::Word32)
{-# LINE 1290 "Graphics/X11/Xlib/Misc.hsc" #-}
        Display -> Atom -> Ptr XTextProperty -> Atom -> IO ()
xSetTextProperty Display
display Atom
w Ptr XTextProperty
text_prop Atom
property
foreign import ccall unsafe "HsXlib.h XSetTextProperty"
        xSetTextProperty :: Display -> Window -> Ptr XTextProperty -> Atom -> IO ()

-- %fun XSetStandardProperties :: Display -> Window -> String -> String -> Pixmap -> [String] -> XSizeHints -> IO ()
-- %code Status err = XSetStandardProperties(arg1,arg2,arg3,arg4,arg5,arg6,arg6_size,&arg7)
-- %fail { Success != err }{ BadStatus(err,XSetStandardProperties) }

----------------------------------------------------------------
-- Canned handling of output parameters
----------------------------------------------------------------

outParameters2 :: (Storable a, Storable b) =>
        (IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a,b)
outParameters2 :: forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 IO r -> IO ()
check Ptr a -> Ptr b -> IO r
fn =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr b
b_return -> do
        IO r -> IO ()
check (Ptr a -> Ptr b -> IO r
fn Ptr a
a_return Ptr b
b_return)
        a
a <- forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
        b
b <- forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b)

outParameters3 :: (Storable a, Storable b, Storable c) =>
        (IO r -> IO ()) -> (Ptr a -> Ptr b -> Ptr c -> IO r) -> IO (a,b,c)
outParameters3 :: forall a b c r.
(Storable a, Storable b, Storable c) =>
(IO r -> IO ())
-> (Ptr a -> Ptr b -> Ptr c -> IO r) -> IO (a, b, c)
outParameters3 IO r -> IO ()
check Ptr a -> Ptr b -> Ptr c -> IO r
fn =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr b
b_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr c
c_return -> do
        IO r -> IO ()
check (Ptr a -> Ptr b -> Ptr c -> IO r
fn Ptr a
a_return Ptr b
b_return Ptr c
c_return)
        a
a <- forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
        b
b <- forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
        c
c <- forall a. Storable a => Ptr a -> IO a
peek Ptr c
c_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c)

outParameters4 :: (Storable a, Storable b, Storable c, Storable d) =>
        (IO r -> IO ()) -> (Ptr a -> Ptr b -> Ptr c -> Ptr d -> IO r) ->
        IO (a,b,c,d)
outParameters4 :: forall a b c d r.
(Storable a, Storable b, Storable c, Storable d) =>
(IO r -> IO ())
-> (Ptr a -> Ptr b -> Ptr c -> Ptr d -> IO r) -> IO (a, b, c, d)
outParameters4 IO r -> IO ()
check Ptr a -> Ptr b -> Ptr c -> Ptr d -> IO r
fn =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr b
b_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr c
c_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr d
d_return -> do
        IO r -> IO ()
check (Ptr a -> Ptr b -> Ptr c -> Ptr d -> IO r
fn Ptr a
a_return Ptr b
b_return Ptr c
c_return Ptr d
d_return)
        a
a <- forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
        b
b <- forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
        c
c <- forall a. Storable a => Ptr a -> IO a
peek Ptr c
c_return
        d
d <- forall a. Storable a => Ptr a -> IO a
peek Ptr d
d_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d)

outParameters7 :: (Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g) =>
        (IO r -> IO ()) -> (Ptr a -> Ptr b -> Ptr c -> Ptr d -> Ptr e -> Ptr f -> Ptr g -> IO r) ->
        IO (a,b,c,d,e,f,g)
outParameters7 :: forall a b c d e f g r.
(Storable a, Storable b, Storable c, Storable d, Storable e,
 Storable f, Storable g) =>
(IO r -> IO ())
-> (Ptr a
    -> Ptr b -> Ptr c -> Ptr d -> Ptr e -> Ptr f -> Ptr g -> IO r)
-> IO (a, b, c, d, e, f, g)
outParameters7 IO r -> IO ()
check Ptr a -> Ptr b -> Ptr c -> Ptr d -> Ptr e -> Ptr f -> Ptr g -> IO r
fn =
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr b
b_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr c
c_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr d
d_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr e
e_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr f
f_return ->
        forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \ Ptr g
g_return -> do
        IO r -> IO ()
check (Ptr a -> Ptr b -> Ptr c -> Ptr d -> Ptr e -> Ptr f -> Ptr g -> IO r
fn Ptr a
a_return Ptr b
b_return Ptr c
c_return Ptr d
d_return Ptr e
e_return Ptr f
f_return Ptr g
g_return)
        a
a <- forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
        b
b <- forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
        c
c <- forall a. Storable a => Ptr a -> IO a
peek Ptr c
c_return
        d
d <- forall a. Storable a => Ptr a -> IO a
peek Ptr d
d_return
        e
e <- forall a. Storable a => Ptr a -> IO a
peek Ptr e
e_return
        f
f <- forall a. Storable a => Ptr a -> IO a
peek Ptr f
f_return
        g
g <- forall a. Storable a => Ptr a -> IO a
peek Ptr g
g_return
        forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g)

----------------------------------------------------------------
-- End
----------------------------------------------------------------