{-# LINE 1 "Graphics/X11/Xlib/Misc.hsc" #-}
{-# LANGUAGE DeriveDataTypeable #-}
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,
displayName,
setDefaultErrorHandler,
geometry,
getGeometry,
supportsLocale,
setLocaleModifiers,
AllowExposuresMode,
dontAllowExposures,
allowExposures,
defaultExposures,
PreferBlankingMode,
dontPreferBlanking,
preferBlanking,
defaultBlanking,
ScreenSaverMode,
screenSaverActive,
screenSaverReset,
getScreenSaver,
setScreenSaver,
activateScreenSaver,
resetScreenSaver,
forceScreenSaver,
getPointerControl,
warpPointer,
visualIDFromVisual,
VisualInfoMask,
visualNoMask,
visualIDMask,
visualScreenMask,
visualDepthMask,
visualClassMask,
visualRedMaskMask,
visualGreenMaskMask,
visualBlueMaskMask,
visualColormapSizeMask,
visualBitsPerRGBMask,
visualAllMask,
getVisualInfo,
matchVisualInfo,
initThreads,
lockDisplay,
unlockDisplay,
createPixmap,
freePixmap,
bitmapBitOrder,
bitmapUnit,
bitmapPad,
readBitmapFile,
displayKeycodes,
lookupKeysym,
keycodeToKeysym,
keysymToKeycode,
keysymToString,
stringToKeysym,
noSymbol,
lookupString,
getIconName,
setIconName,
defineCursor,
undefineCursor,
createPixmapCursor,
createGlyphCursor,
createFontCursor,
freeCursor,
recolorCursor,
setWMProtocols,
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,
drawPoint,
drawPoints,
drawLine,
drawLines,
drawSegments,
drawRectangle,
drawRectangles,
drawArc,
drawArcs,
fillRectangle,
fillRectangles,
fillPolygon,
fillArc,
fillArcs,
copyArea,
copyPlane,
drawString,
drawImageString,
storeBuffer,
storeBytes,
fetchBuffer,
fetchBytes,
rotateBuffers,
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" #-}
foreign import ccall unsafe "HsXlib.h XrmInitialize"
rmInitialize :: IO ()
foreign import ccall unsafe "HsXlib.h XAutoRepeatOff"
autoRepeatOff :: Display -> IO ()
foreign import ccall unsafe "HsXlib.h XAutoRepeatOn"
autoRepeatOn :: Display -> IO ()
foreign import ccall unsafe "HsXlib.h XBell"
bell :: Display -> CInt -> IO ()
foreign import ccall unsafe "HsXlib.h XSetCloseDownMode"
setCloseDownMode :: Display -> CloseDownMode -> IO ()
foreign import ccall unsafe "HsXlib.h XLastKnownRequestProcessed"
lastKnownRequestProcessed :: Display -> IO CInt
getInputFocus :: Display -> IO (Window, FocusMode)
getInputFocus :: Display -> IO (Atom, CInt)
getInputFocus Display
display =
(Ptr Atom -> IO (Atom, CInt)) -> IO (Atom, CInt)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Atom -> IO (Atom, CInt)) -> IO (Atom, CInt))
-> (Ptr Atom -> IO (Atom, CInt)) -> IO (Atom, CInt)
forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
focus_return ->
(Ptr CInt -> IO (Atom, CInt)) -> IO (Atom, CInt)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (Atom, CInt)) -> IO (Atom, CInt))
-> (Ptr CInt -> IO (Atom, CInt)) -> IO (Atom, CInt)
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
focus <- Ptr Atom -> IO Atom
forall a. Storable a => Ptr a -> IO a
peek Ptr Atom
focus_return
revert_to <- peek revert_to_return
return (focus, revert_to)
foreign import ccall unsafe "HsXlib.h XGetInputFocus"
xGetInputFocus :: Display -> Ptr Window -> Ptr FocusMode -> IO ()
foreign import ccall unsafe "HsXlib.h XSetInputFocus"
setInputFocus :: Display -> Window -> FocusMode -> Time -> IO ()
foreign import ccall unsafe "HsXlib.h XGrabButton"
grabButton :: Display -> Button -> ButtonMask -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> IO ()
foreign import ccall unsafe "HsXlib.h XUngrabButton"
ungrabButton :: Display -> Button -> ButtonMask -> Window -> IO ()
foreign import ccall unsafe "HsXlib.h XGrabPointer"
grabPointer :: Display -> Window -> Bool -> EventMask -> GrabMode -> GrabMode -> Window -> Cursor -> Time -> IO GrabStatus
foreign import ccall unsafe "HsXlib.h XUngrabPointer"
ungrabPointer :: Display -> Time -> IO ()
foreign import ccall unsafe "HsXlib.h XGrabKey"
grabKey :: Display -> KeyCode -> KeyMask -> Window -> Bool -> GrabMode -> GrabMode -> IO ()
foreign import ccall unsafe "HsXlib.h XUngrabKey"
ungrabKey :: Display -> KeyCode -> KeyMask -> Window -> IO ()
foreign import ccall unsafe "HsXlib.h XGrabKeyboard"
grabKeyboard :: Display -> Window -> Bool -> GrabMode -> GrabMode -> Time -> IO GrabStatus
foreign import ccall unsafe "HsXlib.h XUngrabKeyboard"
ungrabKeyboard :: Display -> Time -> IO ()
foreign import ccall unsafe "HsXlib.h XGrabServer"
grabServer :: Display -> IO ()
foreign import ccall unsafe "HsXlib.h XUngrabServer"
ungrabServer :: Display -> IO ()
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 =
(IO CInt -> IO ())
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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") ((Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32))
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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
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 =
(IO CInt -> IO ())
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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") ((Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32))
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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
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 =
(IO CInt -> IO ())
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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") ((Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32))
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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
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 =
(IO CInt -> IO ())
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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") ((Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32))
-> (Ptr Word32 -> Ptr Word32 -> IO CInt) -> IO (Word32, Word32)
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
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 =
(Ptr Atom
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Atom
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> (Ptr Atom
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
root_return ->
(Ptr Atom
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Atom
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> (Ptr Atom
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
child_return ->
(Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> (Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
root_x_return ->
(Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> (Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
root_y_return ->
(Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> (Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
win_x_return ->
(Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> (Ptr CInt
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
win_y_return ->
(Ptr Modifier
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Modifier
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> (Ptr Modifier
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier))
-> IO (Bool, Atom, Atom, CInt, CInt, CInt, CInt, Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr Modifier
mask_return -> do
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
root <- peek root_return
child <- peek child_return
root_x <- peek root_x_return
root_y <- peek root_y_return
win_x <- peek win_x_return
win_y <- peek win_y_return
mask <- peek mask_return
return (rel, root, child, root_x, root_y, win_x, win_y, 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
displayName :: String -> String
displayName :: String -> String
displayName String
str = IO String -> String
forall a. IO a -> a
unsafePerformIO (IO String -> String) -> IO String -> String
forall a b. (a -> b) -> a -> b
$
String -> (Ptr CChar -> IO String) -> IO String
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
str ((Ptr CChar -> IO String) -> IO String)
-> (Ptr CChar -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_str -> do
c_name <- Ptr CChar -> IO (Ptr CChar)
xDisplayName Ptr CChar
c_str
peekCString c_name
foreign import ccall unsafe "HsXlib.h XDisplayName"
xDisplayName :: CString -> IO CString
{-# CFILES cbits/auxiliaries.c #-}
newtype XErrorEvent = XErrorEvent (Ptr XErrorEvent)
{-# LINE 467 "Graphics/X11/Xlib/Misc.hsc" #-}
deriving (XErrorEvent -> XErrorEvent -> Bool
(XErrorEvent -> XErrorEvent -> Bool)
-> (XErrorEvent -> XErrorEvent -> Bool) -> Eq XErrorEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: XErrorEvent -> XErrorEvent -> Bool
== :: XErrorEvent -> XErrorEvent -> Bool
$c/= :: XErrorEvent -> XErrorEvent -> Bool
/= :: XErrorEvent -> XErrorEvent -> Bool
Eq, Eq XErrorEvent
Eq XErrorEvent =>
(XErrorEvent -> XErrorEvent -> Ordering)
-> (XErrorEvent -> XErrorEvent -> Bool)
-> (XErrorEvent -> XErrorEvent -> Bool)
-> (XErrorEvent -> XErrorEvent -> Bool)
-> (XErrorEvent -> XErrorEvent -> Bool)
-> (XErrorEvent -> XErrorEvent -> XErrorEvent)
-> (XErrorEvent -> XErrorEvent -> XErrorEvent)
-> Ord 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
$ccompare :: XErrorEvent -> XErrorEvent -> Ordering
compare :: XErrorEvent -> XErrorEvent -> Ordering
$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
>= :: XErrorEvent -> XErrorEvent -> Bool
$cmax :: XErrorEvent -> XErrorEvent -> XErrorEvent
max :: XErrorEvent -> XErrorEvent -> XErrorEvent
$cmin :: XErrorEvent -> XErrorEvent -> XErrorEvent
min :: XErrorEvent -> XErrorEvent -> XErrorEvent
Ord, Int -> XErrorEvent -> String -> String
[XErrorEvent] -> String -> String
XErrorEvent -> String
(Int -> XErrorEvent -> String -> String)
-> (XErrorEvent -> String)
-> ([XErrorEvent] -> String -> String)
-> Show XErrorEvent
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> XErrorEvent -> String -> String
showsPrec :: Int -> XErrorEvent -> String -> String
$cshow :: XErrorEvent -> String
show :: XErrorEvent -> String
$cshowList :: [XErrorEvent] -> String -> String
showList :: [XErrorEvent] -> String -> String
Show, Typeable, Typeable XErrorEvent
Typeable XErrorEvent =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent)
-> (XErrorEvent -> Constr)
-> (XErrorEvent -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent)
-> (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 u. (forall d. Data d => d -> u) -> XErrorEvent -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent)
-> Data XErrorEvent
XErrorEvent -> Constr
XErrorEvent -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent
$ctoConstr :: XErrorEvent -> Constr
toConstr :: XErrorEvent -> Constr
$cdataTypeOf :: XErrorEvent -> DataType
dataTypeOf :: XErrorEvent -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XErrorEvent)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XErrorEvent)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XErrorEvent)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XErrorEvent)
$cgmapT :: (forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
gmapT :: (forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XErrorEvent -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> XErrorEvent -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m 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)
setDefaultErrorHandler :: IO ()
setDefaultErrorHandler :: IO ()
setDefaultErrorHandler = do
_ <- ErrorHandler -> IO ErrorHandler
xSetErrorHandler ErrorHandler
defaultErrorHandler
return ()
foreign import ccall unsafe "HsXlib.h XSetErrorHandler"
xSetErrorHandler :: ErrorHandler -> IO ErrorHandler
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 =
String
-> (Ptr CChar -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
position ((Ptr CChar -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32))
-> (Ptr CChar -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_position ->
String
-> (Ptr CChar -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
default_position ((Ptr CChar -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32))
-> (Ptr CChar -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_default_position ->
(Ptr Position -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Position -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32))
-> (Ptr Position -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. (a -> b) -> a -> b
$ \ Ptr Position
x_return ->
(Ptr Position -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Position -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32))
-> (Ptr Position -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. (a -> b) -> a -> b
$ \ Ptr Position
y_return ->
(Ptr Word32 -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32))
-> (Ptr Word32 -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
width_return ->
(Ptr Word32 -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32))
-> (Ptr Word32 -> IO (CInt, Position, Position, Word32, Word32))
-> IO (CInt, Position, Position, Word32, Word32)
forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
height_return -> do
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
x <- peek x_return
y <- peek y_return
width <- peek width_return
height <- peek height_return
return (res, x, y, width, 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
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 =
(IO CInt -> IO ())
-> (Ptr Atom
-> Ptr Position
-> Ptr Position
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> Ptr CInt
-> IO CInt)
-> IO (Atom, Position, Position, Word32, Word32, Word32, CInt)
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") ((Ptr Atom
-> Ptr Position
-> Ptr Position
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> Ptr CInt
-> IO CInt)
-> IO (Atom, Position, Position, Word32, Word32, Word32, CInt))
-> (Ptr Atom
-> Ptr Position
-> Ptr Position
-> Ptr Word32
-> Ptr Word32
-> Ptr Word32
-> Ptr CInt
-> IO CInt)
-> IO (Atom, Position, Position, Word32, Word32, Word32, CInt)
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
foreign import ccall unsafe "HsXlib.h XSupportsLocale"
supportsLocale :: IO Bool
setLocaleModifiers :: String -> IO String
setLocaleModifiers :: String -> IO String
setLocaleModifiers String
mods =
String -> (Ptr CChar -> IO String) -> IO String
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
mods ((Ptr CChar -> IO String) -> IO String)
-> (Ptr CChar -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
modifier_list -> do
c_str <- Ptr CChar -> IO (Ptr CChar)
xSetLocaleModifiers Ptr CChar
modifier_list
peekCString c_str
foreign import ccall unsafe "HsXlib.h XSetLocaleModifiers"
xSetLocaleModifiers :: CString -> IO CString
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 = (IO () -> IO ())
-> (Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ())
-> IO (CInt, CInt, CInt, CInt)
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 () -> IO ()
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 ()
foreign import ccall unsafe "HsXlib.h XSetScreenSaver"
setScreenSaver :: Display -> CInt -> CInt ->
PreferBlankingMode -> AllowExposuresMode -> IO ()
foreign import ccall unsafe "HsXlib.h XActivateScreenSaver"
activateScreenSaver :: Display -> IO ()
foreign import ccall unsafe "HsXlib.h XResetScreenSaver"
resetScreenSaver :: Display -> IO ()
foreign import ccall unsafe "HsXlib.h XForceScreenSaver"
forceScreenSaver :: Display -> ScreenSaverMode -> IO ()
getPointerControl :: Display -> IO (CInt, CInt, CInt)
getPointerControl :: Display -> IO (CInt, CInt, CInt)
getPointerControl Display
display = (IO () -> IO ())
-> (Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ())
-> IO (CInt, CInt, CInt)
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 () -> IO ()
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 ()
foreign import ccall unsafe "HsXlib.h XWarpPointer"
warpPointer :: Display -> Window -> Window -> Position -> Position ->
Dimension -> Dimension -> Position -> Position -> IO ()
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" #-}
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)
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_ =
(Ptr VisualInfo -> IO (Maybe VisualInfo)) -> IO (Maybe VisualInfo)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr VisualInfo -> IO (Maybe VisualInfo))
-> IO (Maybe VisualInfo))
-> (Ptr VisualInfo -> IO (Maybe VisualInfo))
-> IO (Maybe VisualInfo)
forall a b. (a -> b) -> a -> b
$ \Ptr VisualInfo
infoPtr -> do
status <- Display -> Word32 -> CInt -> CInt -> Ptr VisualInfo -> IO CInt
xMatchVisualInfo Display
dpy Word32
screen CInt
depth CInt
class_ Ptr VisualInfo
infoPtr
if status == 0
then return Nothing
else do
info <- peek infoPtr
return $ Just info
foreign import ccall unsafe "XMatchVisualInfo"
xMatchVisualInfo :: Display -> ScreenNumber -> CInt -> CInt ->
Ptr VisualInfo -> IO Status
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 ()
foreign import ccall unsafe "HsXlib.h XCreatePixmap"
createPixmap :: Display -> Drawable -> Dimension -> Dimension -> CInt -> IO Pixmap
foreign import ccall unsafe "HsXlib.h XFreePixmap"
freePixmap :: Display -> Pixmap -> IO ()
foreign import ccall unsafe "HsXlib.h XBitmapBitOrder"
bitmapBitOrder :: Display -> ByteOrder
foreign import ccall unsafe "HsXlib.h XBitmapUnit"
bitmapUnit :: Display -> CInt
foreign import ccall unsafe "HsXlib.h XBitmapPad"
bitmapPad :: Display -> CInt
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 =
String
-> (Ptr CChar
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
filename ((Ptr CChar
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> (Ptr CChar
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
c_filename ->
(Ptr Word32
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> (Ptr Word32
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
width_return ->
(Ptr Word32
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> (Ptr Word32
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ \ Ptr Word32
height_return ->
(Ptr Atom
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Atom
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> (Ptr Atom
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
bitmap_return ->
(Ptr CInt
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> (Ptr CInt
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
x_hot_return ->
(Ptr CInt
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> (Ptr CInt
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
y_hot_return -> do
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
width <- peek width_return
height <- peek height_return
bitmap <- peek bitmap_return
x_hot <- peek x_hot_return
y_hot <- peek y_hot_return
let m_x_hot | CInt
x_hot CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== -CInt
1 = Maybe CInt
forall a. Maybe a
Nothing
| Bool
otherwise = CInt -> Maybe CInt
forall a. a -> Maybe a
Just CInt
x_hot
m_y_hot | CInt
y_hot CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== -CInt
1 = Maybe CInt
forall a. Maybe a
Nothing
| Bool
otherwise = CInt -> Maybe CInt
forall a. a -> Maybe a
Just CInt
y_hot
case rv of
CInt
0 -> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
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 -> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ String
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapOpenFailed"
CInt
2 -> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ String
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapFileInvalid"
CInt
3 -> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ String
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapNoMemory"
CInt
_ -> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)))
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
-> IO
(Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt))
forall a b. (a -> b) -> a -> b
$ String
-> Either String (Word32, Word32, Atom, Maybe CInt, Maybe CInt)
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
displayKeycodes :: Display -> (CInt,CInt)
displayKeycodes :: Display -> (CInt, CInt)
displayKeycodes Display
display =
IO (CInt, CInt) -> (CInt, CInt)
forall a. IO a -> a
unsafePerformIO (IO (CInt, CInt) -> (CInt, CInt))
-> IO (CInt, CInt) -> (CInt, CInt)
forall a b. (a -> b) -> a -> b
$ (IO () -> IO ())
-> (Ptr CInt -> Ptr CInt -> IO ()) -> IO (CInt, CInt)
forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 IO () -> IO ()
forall a. a -> a
id ((Ptr CInt -> Ptr CInt -> IO ()) -> IO (CInt, CInt))
-> (Ptr CInt -> Ptr CInt -> IO ()) -> IO (CInt, CInt)
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 ()
foreign import ccall unsafe "HsXlib.h XLookupKeysym"
lookupKeysym :: XKeyEventPtr -> CInt -> IO KeySym
foreign import ccall unsafe "HsXlib.h XKeycodeToKeysym"
keycodeToKeysym :: Display -> KeyCode -> CInt -> IO KeySym
foreign import ccall unsafe "HsXlib.h XKeysymToKeycode"
keysymToKeycode :: Display -> KeySym -> IO KeyCode
keysymToString :: KeySym -> String
keysymToString :: Atom -> String
keysymToString Atom
keysym = IO String -> String
forall a. IO a -> a
unsafePerformIO (IO String -> String) -> IO String -> String
forall a b. (a -> b) -> a -> b
$ do
c_str <- Atom -> IO (Ptr CChar)
xKeysymToString Atom
keysym
peekCString c_str
foreign import ccall unsafe "HsXlib.h XKeysymToString"
xKeysymToString :: KeySym -> IO CString
stringToKeysym :: String -> KeySym
stringToKeysym :: String -> Atom
stringToKeysym String
str = IO Atom -> Atom
forall a. IO a -> a
unsafePerformIO (IO Atom -> Atom) -> IO Atom -> Atom
forall a b. (a -> b) -> a -> b
$
String -> (Ptr CChar -> IO Atom) -> IO Atom
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
str ((Ptr CChar -> IO Atom) -> IO Atom)
-> (Ptr CChar -> IO Atom) -> IO Atom
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
(XComposeStatus -> XComposeStatus -> Bool)
-> (XComposeStatus -> XComposeStatus -> Bool) -> Eq XComposeStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: XComposeStatus -> XComposeStatus -> Bool
== :: XComposeStatus -> XComposeStatus -> Bool
$c/= :: XComposeStatus -> XComposeStatus -> Bool
/= :: XComposeStatus -> XComposeStatus -> Bool
Eq, Eq XComposeStatus
Eq XComposeStatus =>
(XComposeStatus -> XComposeStatus -> Ordering)
-> (XComposeStatus -> XComposeStatus -> Bool)
-> (XComposeStatus -> XComposeStatus -> Bool)
-> (XComposeStatus -> XComposeStatus -> Bool)
-> (XComposeStatus -> XComposeStatus -> Bool)
-> (XComposeStatus -> XComposeStatus -> XComposeStatus)
-> (XComposeStatus -> XComposeStatus -> XComposeStatus)
-> Ord 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
$ccompare :: XComposeStatus -> XComposeStatus -> Ordering
compare :: XComposeStatus -> XComposeStatus -> Ordering
$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
>= :: XComposeStatus -> XComposeStatus -> Bool
$cmax :: XComposeStatus -> XComposeStatus -> XComposeStatus
max :: XComposeStatus -> XComposeStatus -> XComposeStatus
$cmin :: XComposeStatus -> XComposeStatus -> XComposeStatus
min :: XComposeStatus -> XComposeStatus -> XComposeStatus
Ord, Int -> XComposeStatus -> String -> String
[XComposeStatus] -> String -> String
XComposeStatus -> String
(Int -> XComposeStatus -> String -> String)
-> (XComposeStatus -> String)
-> ([XComposeStatus] -> String -> String)
-> Show XComposeStatus
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> XComposeStatus -> String -> String
showsPrec :: Int -> XComposeStatus -> String -> String
$cshow :: XComposeStatus -> String
show :: XComposeStatus -> String
$cshowList :: [XComposeStatus] -> String -> String
showList :: [XComposeStatus] -> String -> String
Show, Typeable, Typeable XComposeStatus
Typeable XComposeStatus =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus)
-> (XComposeStatus -> Constr)
-> (XComposeStatus -> DataType)
-> (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))
-> ((forall b. Data b => b -> b)
-> XComposeStatus -> XComposeStatus)
-> (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 u.
(forall d. Data d => d -> u) -> XComposeStatus -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus)
-> Data XComposeStatus
XComposeStatus -> Constr
XComposeStatus -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus
$ctoConstr :: XComposeStatus -> Constr
toConstr :: XComposeStatus -> Constr
$cdataTypeOf :: XComposeStatus -> DataType
dataTypeOf :: XComposeStatus -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XComposeStatus)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XComposeStatus)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XComposeStatus)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XComposeStatus)
$cgmapT :: (forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
gmapT :: (forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XComposeStatus -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> XComposeStatus -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
Data)
{-# LINE 904 "Graphics/X11/Xlib/Misc.hsc" #-}
lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String)
lookupString :: XKeyEventPtr -> IO (Maybe Atom, String)
lookupString XKeyEventPtr
event_ptr =
Int
-> (Ptr CChar -> IO (Maybe Atom, String))
-> IO (Maybe Atom, String)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
100 ((Ptr CChar -> IO (Maybe Atom, String)) -> IO (Maybe Atom, String))
-> (Ptr CChar -> IO (Maybe Atom, String))
-> IO (Maybe Atom, String)
forall a b. (a -> b) -> a -> b
$ \ Ptr CChar
buf ->
(Ptr Atom -> IO (Maybe Atom, String)) -> IO (Maybe Atom, String)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Atom -> IO (Maybe Atom, String)) -> IO (Maybe Atom, String))
-> (Ptr Atom -> IO (Maybe Atom, String)) -> IO (Maybe Atom, String)
forall a b. (a -> b) -> a -> b
$ \ Ptr Atom
keysym_return -> do
n <- XKeyEventPtr
-> Ptr CChar -> CInt -> Ptr Atom -> Ptr XComposeStatus -> IO CInt
xLookupString XKeyEventPtr
event_ptr Ptr CChar
buf CInt
100 Ptr Atom
keysym_return Ptr XComposeStatus
forall a. Ptr a
nullPtr
str <- peekCStringLen (buf, fromIntegral n)
keysym <- peek keysym_return
return (if keysym == noSymbol then Nothing else Just keysym, str)
foreign import ccall unsafe "HsXlib.h XLookupString"
xLookupString :: XKeyEventPtr -> CString -> CInt ->
Ptr KeySym -> Ptr XComposeStatus -> IO CInt
getIconName :: Display -> Window -> IO String
getIconName :: Display -> Atom -> IO String
getIconName Display
display Atom
w =
(Ptr (Ptr CChar) -> IO String) -> IO String
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr CChar) -> IO String) -> IO String)
-> (Ptr (Ptr CChar) -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr (Ptr CChar)
icon_name_return -> do
String -> IO CInt -> IO ()
throwIfZero String
"getIconName" (IO CInt -> IO ()) -> IO CInt -> IO ()
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
c_icon_name <- Ptr (Ptr CChar) -> IO (Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CChar)
icon_name_return
peekCString c_icon_name
foreign import ccall unsafe "HsXlib.h XGetIconName"
xGetIconName :: Display -> Window -> Ptr CString -> IO Status
setIconName :: Display -> Window -> String -> IO ()
setIconName :: Display -> Atom -> String -> IO ()
setIconName Display
display Atom
w String
icon_name =
String -> (Ptr CChar -> IO ()) -> IO ()
forall a. String -> (Ptr CChar -> IO a) -> IO a
withCString String
icon_name ((Ptr CChar -> IO ()) -> IO ()) -> (Ptr CChar -> IO ()) -> IO ()
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 ()
foreign import ccall unsafe "HsXlib.h XDefineCursor"
defineCursor :: Display -> Window -> Cursor -> IO ()
foreign import ccall unsafe "HsXlib.h XUndefineCursor"
undefineCursor :: Display -> Window -> IO ()
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 =
Color -> (Ptr Color -> IO Atom) -> IO Atom
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color ((Ptr Color -> IO Atom) -> IO Atom)
-> (Ptr Color -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
Color -> (Ptr Color -> IO Atom) -> IO Atom
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color ((Ptr Color -> IO Atom) -> IO Atom)
-> (Ptr Color -> IO Atom) -> IO Atom
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
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 =
Color -> (Ptr Color -> IO Atom) -> IO Atom
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color ((Ptr Color -> IO Atom) -> IO Atom)
-> (Ptr Color -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
Color -> (Ptr Color -> IO Atom) -> IO Atom
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color ((Ptr Color -> IO Atom) -> IO Atom)
-> (Ptr Color -> IO Atom) -> IO Atom
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
foreign import ccall unsafe "HsXlib.h XCreateFontCursor"
createFontCursor :: Display -> Glyph -> IO Cursor
foreign import ccall unsafe "HsXlib.h XFreeCursor"
freeCursor :: Display -> Font -> IO ()
recolorCursor :: Display -> Cursor -> Color -> Color -> IO ()
recolorCursor :: Display -> Atom -> Color -> Color -> IO ()
recolorCursor Display
display Atom
cursor Color
fg_color Color
bg_color =
Color -> (Ptr Color -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color ((Ptr Color -> IO ()) -> IO ()) -> (Ptr Color -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
Color -> (Ptr Color -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color ((Ptr Color -> IO ()) -> IO ()) -> (Ptr Color -> IO ()) -> IO ()
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 ()
setWMProtocols :: Display -> Window -> [Atom] -> IO ()
setWMProtocols :: Display -> Atom -> [Atom] -> IO ()
setWMProtocols Display
display Atom
w [Atom]
protocols =
[Atom] -> (Ptr Atom -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [Atom]
protocols ((Ptr Atom -> IO ()) -> IO ()) -> (Ptr Atom -> IO ()) -> IO ()
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 (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [Atom] -> Int
forall a. [a] -> Int
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 ()
allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a
allocaSetWindowAttributes :: forall a. (Ptr SetWindowAttributes -> IO a) -> IO a
allocaSetWindowAttributes = Int -> (Ptr SetWindowAttributes -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
112)
{-# LINE 1035 "Graphics/X11/Xlib/Misc.hsc" #-}
set_background_pixmap :: Ptr SetWindowAttributes -> Pixmap -> IO ()
set_background_pixmap :: Ptr SetWindowAttributes -> Atom -> IO ()
set_background_pixmap = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Bool -> IO ()
forall b. Ptr b -> Int -> Bool -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Bool -> IO ()
forall b. Ptr b -> Int -> Bool -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr SetWindowAttributes -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr SetWindowAttributes
hsc_ptr Int
104)
{-# LINE 1082 "Graphics/X11/Xlib/Misc.hsc" #-}
foreign import ccall unsafe "HsXlib.h XDrawPoint"
drawPoint :: Display -> Drawable -> GC -> Position -> Position -> IO ()
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 =
[Point] -> (Int -> Ptr Point -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Point]
points ((Int -> Ptr Point -> IO ()) -> IO ())
-> (Int -> Ptr Point -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
foreign import ccall unsafe "HsXlib.h XDrawLine"
drawLine :: Display -> Drawable -> GC -> Position -> Position ->
Position -> Position -> IO ()
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 =
[Point] -> (Int -> Ptr Point -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Point]
points ((Int -> Ptr Point -> IO ()) -> IO ())
-> (Int -> Ptr Point -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
drawSegments :: Display -> Drawable -> GC -> [Segment] -> IO ()
drawSegments :: Display -> Atom -> GC -> [Segment] -> IO ()
drawSegments Display
display Atom
d GC
gc [Segment]
segments =
[Segment] -> (Int -> Ptr Segment -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Segment]
segments ((Int -> Ptr Segment -> IO ()) -> IO ())
-> (Int -> Ptr Segment -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
foreign import ccall unsafe "HsXlib.h XDrawRectangle"
drawRectangle :: Display -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> IO ()
drawRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
drawRectangles :: Display -> Atom -> GC -> [Rectangle] -> IO ()
drawRectangles Display
display Atom
d GC
gc [Rectangle]
rectangles =
[Rectangle] -> (Int -> Ptr Rectangle -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Rectangle]
rectangles ((Int -> Ptr Rectangle -> IO ()) -> IO ())
-> (Int -> Ptr Rectangle -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
foreign import ccall unsafe "HsXlib.h XDrawArc"
drawArc :: Display -> Drawable -> GC -> Position -> Position ->
Dimension -> Dimension -> Angle -> Angle -> IO ()
drawArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
drawArcs :: Display -> Atom -> GC -> [Arc] -> IO ()
drawArcs Display
display Atom
d GC
gc [Arc]
arcs =
[Arc] -> (Int -> Ptr Arc -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Arc]
arcs ((Int -> Ptr Arc -> IO ()) -> IO ())
-> (Int -> Ptr Arc -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
foreign import ccall unsafe "HsXlib.h XFillRectangle"
fillRectangle :: Display -> Drawable -> GC -> Position -> Position ->
Dimension -> Dimension -> IO ()
fillRectangles :: Display -> Drawable -> GC -> [Rectangle] -> IO ()
fillRectangles :: Display -> Atom -> GC -> [Rectangle] -> IO ()
fillRectangles Display
display Atom
d GC
gc [Rectangle]
rectangles =
[Rectangle] -> (Int -> Ptr Rectangle -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Rectangle]
rectangles ((Int -> Ptr Rectangle -> IO ()) -> IO ())
-> (Int -> Ptr Rectangle -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
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 =
[Point] -> (Int -> Ptr Point -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Point]
points ((Int -> Ptr Point -> IO ()) -> IO ())
-> (Int -> Ptr Point -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
foreign import ccall unsafe "HsXlib.h XFillArc"
fillArc :: Display -> Drawable -> GC -> Position -> Position ->
Dimension -> Dimension -> Angle -> Angle -> IO ()
fillArcs :: Display -> Drawable -> GC -> [Arc] -> IO ()
fillArcs :: Display -> Atom -> GC -> [Arc] -> IO ()
fillArcs Display
display Atom
d GC
gc [Arc]
arcs =
[Arc] -> (Int -> Ptr Arc -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Arc]
arcs ((Int -> Ptr Arc -> IO ()) -> IO ())
-> (Int -> Ptr Arc -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
foreign import ccall unsafe "HsXlib.h XCopyArea"
copyArea :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> IO ()
foreign import ccall unsafe "HsXlib.h XCopyPlane"
copyPlane :: Display -> Drawable -> Drawable -> GC -> Position -> Position -> Dimension -> Dimension -> Position -> Position -> Pixel -> IO ()
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 =
String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
str ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
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 =
String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
str ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
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 (Int -> CInt
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 ()
storeBuffer :: Display -> String -> CInt -> IO ()
storeBuffer :: Display -> String -> CInt -> IO ()
storeBuffer Display
display String
bytes CInt
buffer =
String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
bytes ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_bytes, Int
nbytes) ->
String -> IO CInt -> IO ()
throwIfZero String
"storeBuffer" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
Display -> Ptr CChar -> CInt -> CInt -> IO CInt
xStoreBuffer Display
display Ptr CChar
c_bytes (Int -> CInt
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
storeBytes :: Display -> String -> IO ()
storeBytes :: Display -> String -> IO ()
storeBytes Display
display String
bytes =
String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
bytes ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_bytes, Int
nbytes) ->
String -> IO CInt -> IO ()
throwIfZero String
"storeBytes" (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$
Display -> Ptr CChar -> CInt -> IO CInt
xStoreBytes Display
display Ptr CChar
c_bytes (Int -> CInt
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
fetchBuffer :: Display -> CInt -> IO String
fetchBuffer :: Display -> CInt -> IO String
fetchBuffer Display
display CInt
buffer =
(Ptr CInt -> IO String) -> IO String
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO String) -> IO String)
-> (Ptr CInt -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
nbytes_return -> do
c_bytes <- String -> IO (Ptr CChar) -> IO (Ptr CChar)
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"fetchBuffer" (IO (Ptr CChar) -> IO (Ptr CChar))
-> IO (Ptr CChar) -> IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$
Display -> Ptr CInt -> CInt -> IO (Ptr CChar)
xFetchBuffer Display
display Ptr CInt
nbytes_return CInt
buffer
nbytes <- peek nbytes_return
bytes <- peekCStringLen (c_bytes, (fromIntegral nbytes))
_ <- xFree c_bytes
return bytes
foreign import ccall unsafe "HsXlib.h XFetchBuffer"
xFetchBuffer :: Display -> Ptr CInt -> CInt -> IO CString
fetchBytes :: Display -> IO String
fetchBytes :: Display -> IO String
fetchBytes Display
display =
(Ptr CInt -> IO String) -> IO String
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO String) -> IO String)
-> (Ptr CInt -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr CInt
nbytes_return -> do
c_bytes <- String -> IO (Ptr CChar) -> IO (Ptr CChar)
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"fetchBytes" (IO (Ptr CChar) -> IO (Ptr CChar))
-> IO (Ptr CChar) -> IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$
Display -> Ptr CInt -> IO (Ptr CChar)
xFetchBytes Display
display Ptr CInt
nbytes_return
nbytes <- peek nbytes_return
bytes <- peekCStringLen (c_bytes, (fromIntegral nbytes))
_ <- xFree c_bytes
return bytes
foreign import ccall unsafe "HsXlib.h XFetchBytes"
xFetchBytes :: Display -> Ptr CInt -> IO CString
rotateBuffers :: Display -> CInt -> IO ()
rotateBuffers :: Display -> CInt -> IO ()
rotateBuffers Display
display CInt
rot =
String -> IO CInt -> IO ()
throwIfZero String
"rotateBuffers" (IO CInt -> IO ()) -> IO CInt -> IO ()
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
newtype XTextProperty = XTextProperty (Ptr XTextProperty)
{-# LINE 1276 "Graphics/X11/Xlib/Misc.hsc" #-}
deriving (XTextProperty -> XTextProperty -> Bool
(XTextProperty -> XTextProperty -> Bool)
-> (XTextProperty -> XTextProperty -> Bool) -> Eq XTextProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: XTextProperty -> XTextProperty -> Bool
== :: XTextProperty -> XTextProperty -> Bool
$c/= :: XTextProperty -> XTextProperty -> Bool
/= :: XTextProperty -> XTextProperty -> Bool
Eq, Eq XTextProperty
Eq XTextProperty =>
(XTextProperty -> XTextProperty -> Ordering)
-> (XTextProperty -> XTextProperty -> Bool)
-> (XTextProperty -> XTextProperty -> Bool)
-> (XTextProperty -> XTextProperty -> Bool)
-> (XTextProperty -> XTextProperty -> Bool)
-> (XTextProperty -> XTextProperty -> XTextProperty)
-> (XTextProperty -> XTextProperty -> XTextProperty)
-> Ord 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
$ccompare :: XTextProperty -> XTextProperty -> Ordering
compare :: XTextProperty -> XTextProperty -> Ordering
$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
>= :: XTextProperty -> XTextProperty -> Bool
$cmax :: XTextProperty -> XTextProperty -> XTextProperty
max :: XTextProperty -> XTextProperty -> XTextProperty
$cmin :: XTextProperty -> XTextProperty -> XTextProperty
min :: XTextProperty -> XTextProperty -> XTextProperty
Ord, Int -> XTextProperty -> String -> String
[XTextProperty] -> String -> String
XTextProperty -> String
(Int -> XTextProperty -> String -> String)
-> (XTextProperty -> String)
-> ([XTextProperty] -> String -> String)
-> Show XTextProperty
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> XTextProperty -> String -> String
showsPrec :: Int -> XTextProperty -> String -> String
$cshow :: XTextProperty -> String
show :: XTextProperty -> String
$cshowList :: [XTextProperty] -> String -> String
showList :: [XTextProperty] -> String -> String
Show, Typeable, Typeable XTextProperty
Typeable XTextProperty =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty)
-> (XTextProperty -> Constr)
-> (XTextProperty -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> XTextProperty -> XTextProperty)
-> (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 u. (forall d. Data d => d -> u) -> XTextProperty -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> XTextProperty -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty)
-> Data XTextProperty
XTextProperty -> Constr
XTextProperty -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty
$ctoConstr :: XTextProperty -> Constr
toConstr :: XTextProperty -> Constr
$cdataTypeOf :: XTextProperty -> DataType
dataTypeOf :: XTextProperty -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XTextProperty)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XTextProperty)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XTextProperty)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XTextProperty)
$cgmapT :: (forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
gmapT :: (forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XTextProperty -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> XTextProperty -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XTextProperty -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XTextProperty -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
Data)
{-# LINE 1280 "Graphics/X11/Xlib/Misc.hsc" #-}
setTextProperty :: Display -> Window -> String -> Atom -> IO ()
setTextProperty :: Display -> Atom -> String -> Atom -> IO ()
setTextProperty Display
display Atom
w String
value Atom
property =
String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
value ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ (Ptr CChar
c_value, Int
value_len) ->
Int -> (Ptr XTextProperty -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
32) ((Ptr XTextProperty -> IO ()) -> IO ())
-> (Ptr XTextProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Ptr XTextProperty
text_prop -> do
{-# LINE 1286 "Graphics/X11/Xlib/Misc.hsc" #-}
(\Ptr XTextProperty
hsc_ptr -> Ptr XTextProperty -> Int -> Ptr CChar -> IO ()
forall b. Ptr b -> Int -> Ptr CChar -> IO ()
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 -> Ptr XTextProperty -> Int -> Atom -> IO ()
forall b. Ptr b -> Int -> Atom -> IO ()
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 -> Ptr XTextProperty -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
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 -> Ptr XTextProperty -> Int -> Word32 -> IO ()
forall b. Ptr b -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
24) Ptr XTextProperty
text_prop (Int -> Word32
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 ()
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 =
(Ptr a -> IO (a, b)) -> IO (a, b)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr a -> IO (a, b)) -> IO (a, b))
-> (Ptr a -> IO (a, b)) -> IO (a, b)
forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
(Ptr b -> IO (a, b)) -> IO (a, b)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr b -> IO (a, b)) -> IO (a, b))
-> (Ptr b -> IO (a, b)) -> IO (a, b)
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 <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b <- peek b_return
return (a,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 =
(Ptr a -> IO (a, b, c)) -> IO (a, b, c)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr a -> IO (a, b, c)) -> IO (a, b, c))
-> (Ptr a -> IO (a, b, c)) -> IO (a, b, c)
forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
(Ptr b -> IO (a, b, c)) -> IO (a, b, c)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr b -> IO (a, b, c)) -> IO (a, b, c))
-> (Ptr b -> IO (a, b, c)) -> IO (a, b, c)
forall a b. (a -> b) -> a -> b
$ \ Ptr b
b_return ->
(Ptr c -> IO (a, b, c)) -> IO (a, b, c)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr c -> IO (a, b, c)) -> IO (a, b, c))
-> (Ptr c -> IO (a, b, c)) -> IO (a, b, c)
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 <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b <- peek b_return
c <- peek c_return
return (a,b,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 =
(Ptr a -> IO (a, b, c, d)) -> IO (a, b, c, d)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr a -> IO (a, b, c, d)) -> IO (a, b, c, d))
-> (Ptr a -> IO (a, b, c, d)) -> IO (a, b, c, d)
forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
(Ptr b -> IO (a, b, c, d)) -> IO (a, b, c, d)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr b -> IO (a, b, c, d)) -> IO (a, b, c, d))
-> (Ptr b -> IO (a, b, c, d)) -> IO (a, b, c, d)
forall a b. (a -> b) -> a -> b
$ \ Ptr b
b_return ->
(Ptr c -> IO (a, b, c, d)) -> IO (a, b, c, d)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr c -> IO (a, b, c, d)) -> IO (a, b, c, d))
-> (Ptr c -> IO (a, b, c, d)) -> IO (a, b, c, d)
forall a b. (a -> b) -> a -> b
$ \ Ptr c
c_return ->
(Ptr d -> IO (a, b, c, d)) -> IO (a, b, c, d)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr d -> IO (a, b, c, d)) -> IO (a, b, c, d))
-> (Ptr d -> IO (a, b, c, d)) -> IO (a, b, c, d)
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 <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b <- peek b_return
c <- peek c_return
d <- peek d_return
return (a,b,c,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 =
(Ptr a -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr a -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g))
-> (Ptr a -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \ Ptr a
a_return ->
(Ptr b -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr b -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g))
-> (Ptr b -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \ Ptr b
b_return ->
(Ptr c -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr c -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g))
-> (Ptr c -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \ Ptr c
c_return ->
(Ptr d -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr d -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g))
-> (Ptr d -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \ Ptr d
d_return ->
(Ptr e -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr e -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g))
-> (Ptr e -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \ Ptr e
e_return ->
(Ptr f -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr f -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g))
-> (Ptr f -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \ Ptr f
f_return ->
(Ptr g -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr g -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g))
-> (Ptr g -> IO (a, b, c, d, e, f, g)) -> IO (a, b, c, d, e, f, g)
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 <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b <- peek b_return
c <- peek c_return
d <- peek d_return
e <- peek e_return
f <- peek f_return
g <- peek g_return
return (a,b,c,d,e,f,g)