{-# 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 (Window, FocusMode)
getInputFocus Display
display =
(Ptr Window -> IO (Window, FocusMode)) -> IO (Window, FocusMode)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window -> IO (Window, FocusMode)) -> IO (Window, FocusMode))
-> (Ptr Window -> IO (Window, FocusMode)) -> IO (Window, FocusMode)
forall a b. (a -> b) -> a -> b
$ \ Ptr Window
focus_return ->
(Ptr FocusMode -> IO (Window, FocusMode)) -> IO (Window, FocusMode)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode -> IO (Window, FocusMode))
-> IO (Window, FocusMode))
-> (Ptr FocusMode -> IO (Window, FocusMode))
-> IO (Window, FocusMode)
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
revert_to_return -> do
Display -> Ptr Window -> Ptr FocusMode -> IO ()
xGetInputFocus Display
display Ptr Window
focus_return Ptr FocusMode
revert_to_return
Window
focus <- Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
focus_return
FocusMode
revert_to <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
revert_to_return
(Window, FocusMode) -> IO (Window, FocusMode)
forall (m :: * -> *) a. Monad m => a -> m a
return (Window
focus, FocusMode
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
-> Window -> Dimension -> Dimension -> IO (Dimension, Dimension)
queryBestTile Display
display Window
which_screen Dimension
width Dimension
height =
(IO FocusMode -> IO ())
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO FocusMode -> IO ()
throwIfZero String
"queryBestTile") ((Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension))
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$
Display
-> Window
-> Dimension
-> Dimension
-> Ptr Dimension
-> Ptr Dimension
-> IO FocusMode
xQueryBestTile Display
display Window
which_screen Dimension
width Dimension
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
-> Window -> Dimension -> Dimension -> IO (Dimension, Dimension)
queryBestStipple Display
display Window
which_screen Dimension
width Dimension
height =
(IO FocusMode -> IO ())
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO FocusMode -> IO ()
throwIfZero String
"queryBestStipple") ((Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension))
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$
Display
-> Window
-> Dimension
-> Dimension
-> Ptr Dimension
-> Ptr Dimension
-> IO FocusMode
xQueryBestStipple Display
display Window
which_screen Dimension
width Dimension
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
-> Window -> Dimension -> Dimension -> IO (Dimension, Dimension)
queryBestCursor Display
display Window
d Dimension
width Dimension
height =
(IO FocusMode -> IO ())
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO FocusMode -> IO ()
throwIfZero String
"queryBestCursor") ((Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension))
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$
Display
-> Window
-> Dimension
-> Dimension
-> Ptr Dimension
-> Ptr Dimension
-> IO FocusMode
xQueryBestCursor Display
display Window
d Dimension
width Dimension
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
-> FocusMode
-> Window
-> Dimension
-> Dimension
-> IO (Dimension, Dimension)
queryBestSize Display
display FocusMode
shape_class Window
which_screen Dimension
width Dimension
height =
(IO FocusMode -> IO ())
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b r.
(Storable a, Storable b) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> IO r) -> IO (a, b)
outParameters2 (String -> IO FocusMode -> IO ()
throwIfZero String
"queryBestSize") ((Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension))
-> (Ptr Dimension -> Ptr Dimension -> IO FocusMode)
-> IO (Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$
Display
-> FocusMode
-> Window
-> Dimension
-> Dimension
-> Ptr Dimension
-> Ptr Dimension
-> IO FocusMode
xQueryBestSize Display
display FocusMode
shape_class Window
which_screen Dimension
width Dimension
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
-> Window
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
queryPointer Display
display Window
w =
(Ptr Window
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> (Ptr Window
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr Window
root_return ->
(Ptr Window
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> (Ptr Window
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr Window
child_return ->
(Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> (Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
root_x_return ->
(Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> (Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
root_y_return ->
(Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> (Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
win_x_return ->
(Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> (Ptr FocusMode
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
win_y_return ->
(Ptr Modifier
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Modifier
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> (Ptr Modifier
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier))
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall a b. (a -> b) -> a -> b
$ \ Ptr Modifier
mask_return -> do
Bool
rel <- Display
-> Window
-> Ptr Window
-> Ptr Window
-> Ptr FocusMode
-> Ptr FocusMode
-> Ptr FocusMode
-> Ptr FocusMode
-> Ptr Modifier
-> IO Bool
xQueryPointer Display
display Window
w Ptr Window
root_return Ptr Window
child_return Ptr FocusMode
root_x_return
Ptr FocusMode
root_y_return Ptr FocusMode
win_x_return Ptr FocusMode
win_y_return Ptr Modifier
mask_return
Window
root <- Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
root_return
Window
child <- Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
child_return
FocusMode
root_x <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
root_x_return
FocusMode
root_y <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
root_y_return
FocusMode
win_x <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
win_x_return
FocusMode
win_y <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
win_y_return
Modifier
mask <- Ptr Modifier -> IO Modifier
forall a. Storable a => Ptr a -> IO a
peek Ptr Modifier
mask_return
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
-> IO
(Bool, Window, Window, FocusMode, FocusMode, FocusMode, FocusMode,
Modifier)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
rel, Window
root, Window
child, FocusMode
root_x, FocusMode
root_y, FocusMode
win_x, FocusMode
win_y, Modifier
mask)
foreign import ccall unsafe "HsXlib.h XQueryPointer"
xQueryPointer :: Display -> Window ->
Ptr Window -> Ptr Window -> Ptr CInt -> Ptr CInt ->
Ptr CInt -> Ptr CInt -> Ptr Modifier -> IO Bool
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 -> (CString -> IO String) -> IO String
forall a. String -> (CString -> IO a) -> IO a
withCString String
str ((CString -> IO String) -> IO String)
-> (CString -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ CString
c_str -> do
CString
c_name <- CString -> IO CString
xDisplayName CString
c_str
CString -> IO String
peekCString CString
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
/= :: XErrorEvent -> XErrorEvent -> Bool
$c/= :: XErrorEvent -> XErrorEvent -> Bool
== :: XErrorEvent -> XErrorEvent -> Bool
$c== :: 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
min :: XErrorEvent -> XErrorEvent -> XErrorEvent
$cmin :: XErrorEvent -> XErrorEvent -> XErrorEvent
max :: XErrorEvent -> XErrorEvent -> XErrorEvent
$cmax :: XErrorEvent -> XErrorEvent -> XErrorEvent
>= :: XErrorEvent -> XErrorEvent -> Bool
$c>= :: XErrorEvent -> XErrorEvent -> Bool
> :: XErrorEvent -> XErrorEvent -> Bool
$c> :: XErrorEvent -> XErrorEvent -> Bool
<= :: XErrorEvent -> XErrorEvent -> Bool
$c<= :: XErrorEvent -> XErrorEvent -> Bool
< :: XErrorEvent -> XErrorEvent -> Bool
$c< :: XErrorEvent -> XErrorEvent -> Bool
compare :: XErrorEvent -> XErrorEvent -> Ordering
$ccompare :: XErrorEvent -> XErrorEvent -> Ordering
$cp1Ord :: Eq 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
showList :: [XErrorEvent] -> String -> String
$cshowList :: [XErrorEvent] -> String -> String
show :: XErrorEvent -> String
$cshow :: XErrorEvent -> String
showsPrec :: Int -> XErrorEvent -> String -> String
$cshowsPrec :: Int -> XErrorEvent -> String -> String
Show, Typeable, Typeable XErrorEvent
DataType
Constr
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 -> DataType
XErrorEvent -> Constr
(forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cXErrorEvent :: Constr
$tXErrorEvent :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
gmapMp :: (forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
gmapM :: (forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XErrorEvent -> m XErrorEvent
gmapQi :: Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XErrorEvent -> u
gmapQ :: (forall d. Data d => d -> u) -> XErrorEvent -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XErrorEvent -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XErrorEvent -> r
gmapT :: (forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
$cgmapT :: (forall b. Data b => b -> b) -> XErrorEvent -> XErrorEvent
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XErrorEvent)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XErrorEvent)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c XErrorEvent)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XErrorEvent)
dataTypeOf :: XErrorEvent -> DataType
$cdataTypeOf :: XErrorEvent -> DataType
toConstr :: XErrorEvent -> Constr
$ctoConstr :: XErrorEvent -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XErrorEvent
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XErrorEvent -> c XErrorEvent
$cp1Data :: Typeable 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
_ <- ErrorHandler -> IO ErrorHandler
xSetErrorHandler ErrorHandler
defaultErrorHandler
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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
-> FocusMode
-> String
-> String
-> Dimension
-> Dimension
-> Dimension
-> FocusMode
-> FocusMode
-> IO (FocusMode, Position, Position, Dimension, Dimension)
geometry Display
display FocusMode
screen String
position String
default_position
Dimension
bwidth Dimension
fwidth Dimension
fheight FocusMode
xadder FocusMode
yadder =
String
-> (CString
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a. String -> (CString -> IO a) -> IO a
withCString String
position ((CString
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> (CString
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$ \ CString
c_position ->
String
-> (CString
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a. String -> (CString -> IO a) -> IO a
withCString String
default_position ((CString
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> (CString
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$ \ CString
c_default_position ->
(Ptr Position
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Position
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> (Ptr Position
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$ \ Ptr Position
x_return ->
(Ptr Position
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Position
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> (Ptr Position
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$ \ Ptr Position
y_return ->
(Ptr Dimension
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Dimension
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> (Ptr Dimension
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$ \ Ptr Dimension
width_return ->
(Ptr Dimension
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Dimension
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> (Ptr Dimension
-> IO (FocusMode, Position, Position, Dimension, Dimension))
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall a b. (a -> b) -> a -> b
$ \ Ptr Dimension
height_return -> do
FocusMode
res <- Display
-> FocusMode
-> CString
-> CString
-> Dimension
-> Dimension
-> Dimension
-> FocusMode
-> FocusMode
-> Ptr Position
-> Ptr Position
-> Ptr Dimension
-> Ptr Dimension
-> IO FocusMode
xGeometry Display
display FocusMode
screen CString
c_position CString
c_default_position
Dimension
bwidth Dimension
fwidth Dimension
fheight FocusMode
xadder FocusMode
yadder
Ptr Position
x_return Ptr Position
y_return Ptr Dimension
width_return Ptr Dimension
height_return
Position
x <- Ptr Position -> IO Position
forall a. Storable a => Ptr a -> IO a
peek Ptr Position
x_return
Position
y <- Ptr Position -> IO Position
forall a. Storable a => Ptr a -> IO a
peek Ptr Position
y_return
Dimension
width <- Ptr Dimension -> IO Dimension
forall a. Storable a => Ptr a -> IO a
peek Ptr Dimension
width_return
Dimension
height <- Ptr Dimension -> IO Dimension
forall a. Storable a => Ptr a -> IO a
peek Ptr Dimension
height_return
(FocusMode, Position, Position, Dimension, Dimension)
-> IO (FocusMode, Position, Position, Dimension, Dimension)
forall (m :: * -> *) a. Monad m => a -> m a
return (FocusMode
res, Position
x, Position
y, Dimension
width, Dimension
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
-> Window
-> IO
(Window, Position, Position, Dimension, Dimension, Dimension,
FocusMode)
getGeometry Display
display Window
d =
(IO FocusMode -> IO ())
-> (Ptr Window
-> Ptr Position
-> Ptr Position
-> Ptr Dimension
-> Ptr Dimension
-> Ptr Dimension
-> Ptr FocusMode
-> IO FocusMode)
-> IO
(Window, Position, Position, Dimension, Dimension, Dimension,
FocusMode)
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 FocusMode -> IO ()
throwIfZero String
"getGeometry") ((Ptr Window
-> Ptr Position
-> Ptr Position
-> Ptr Dimension
-> Ptr Dimension
-> Ptr Dimension
-> Ptr FocusMode
-> IO FocusMode)
-> IO
(Window, Position, Position, Dimension, Dimension, Dimension,
FocusMode))
-> (Ptr Window
-> Ptr Position
-> Ptr Position
-> Ptr Dimension
-> Ptr Dimension
-> Ptr Dimension
-> Ptr FocusMode
-> IO FocusMode)
-> IO
(Window, Position, Position, Dimension, Dimension, Dimension,
FocusMode)
forall a b. (a -> b) -> a -> b
$
Display
-> Window
-> Ptr Window
-> Ptr Position
-> Ptr Position
-> Ptr Dimension
-> Ptr Dimension
-> Ptr Dimension
-> Ptr FocusMode
-> IO FocusMode
xGetGeometry Display
display Window
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 -> (CString -> IO String) -> IO String
forall a. String -> (CString -> IO a) -> IO a
withCString String
mods ((CString -> IO String) -> IO String)
-> (CString -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ CString
modifier_list -> do
CString
c_str <- CString -> IO CString
xSetLocaleModifiers CString
modifier_list
CString -> IO String
peekCString CString
c_str
foreign import ccall unsafe "HsXlib.h XSetLocaleModifiers"
xSetLocaleModifiers :: CString -> IO CString
type AllowExposuresMode = CInt
dontAllowExposures :: AllowExposuresMode
dontAllowExposures :: FocusMode
dontAllowExposures = FocusMode
0
allowExposures :: AllowExposuresMode
allowExposures :: FocusMode
allowExposures = FocusMode
1
defaultExposures :: AllowExposuresMode
defaultExposures :: FocusMode
defaultExposures = FocusMode
2
{-# LINE 633 "Graphics/X11/Xlib/Misc.hsc" #-}
type PreferBlankingMode = CInt
dontPreferBlanking :: PreferBlankingMode
dontPreferBlanking :: FocusMode
dontPreferBlanking = FocusMode
0
preferBlanking :: PreferBlankingMode
preferBlanking :: FocusMode
preferBlanking = FocusMode
1
defaultBlanking :: PreferBlankingMode
defaultBlanking :: FocusMode
defaultBlanking = FocusMode
2
{-# LINE 640 "Graphics/X11/Xlib/Misc.hsc" #-}
type ScreenSaverMode = CInt
screenSaverActive :: ScreenSaverMode
screenSaverActive :: FocusMode
screenSaverActive = FocusMode
1
screenSaverReset :: ScreenSaverMode
screenSaverReset :: FocusMode
screenSaverReset = FocusMode
0
{-# LINE 646 "Graphics/X11/Xlib/Misc.hsc" #-}
getScreenSaver :: Display ->
IO (CInt, CInt, PreferBlankingMode, AllowExposuresMode)
getScreenSaver :: Display -> IO (FocusMode, FocusMode, FocusMode, FocusMode)
getScreenSaver Display
display = (IO () -> IO ())
-> (Ptr FocusMode
-> Ptr FocusMode -> Ptr FocusMode -> Ptr FocusMode -> IO ())
-> IO (FocusMode, FocusMode, FocusMode, FocusMode)
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 FocusMode
-> Ptr FocusMode
-> Ptr FocusMode
-> Ptr FocusMode
-> 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 (FocusMode, FocusMode, FocusMode)
getPointerControl Display
display = (IO () -> IO ())
-> (Ptr FocusMode -> Ptr FocusMode -> Ptr FocusMode -> IO ())
-> IO (FocusMode, FocusMode, FocusMode)
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 FocusMode -> Ptr FocusMode -> Ptr FocusMode -> 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
-> Dimension -> FocusMode -> FocusMode -> IO (Maybe VisualInfo)
matchVisualInfo Display
dpy Dimension
screen FocusMode
depth FocusMode
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
FocusMode
status <- Display
-> Dimension
-> FocusMode
-> FocusMode
-> Ptr VisualInfo
-> IO FocusMode
xMatchVisualInfo Display
dpy Dimension
screen FocusMode
depth FocusMode
class_ Ptr VisualInfo
infoPtr
if FocusMode
status FocusMode -> FocusMode -> Bool
forall a. Eq a => a -> a -> Bool
== FocusMode
0
then Maybe VisualInfo -> IO (Maybe VisualInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe VisualInfo
forall a. Maybe a
Nothing
else do
VisualInfo
info <- Ptr VisualInfo -> IO VisualInfo
forall a. Storable a => Ptr a -> IO a
peek Ptr VisualInfo
infoPtr
Maybe VisualInfo -> IO (Maybe VisualInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe VisualInfo -> IO (Maybe VisualInfo))
-> Maybe VisualInfo -> IO (Maybe VisualInfo)
forall a b. (a -> b) -> a -> b
$ VisualInfo -> Maybe VisualInfo
forall a. a -> Maybe a
Just VisualInfo
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
-> Window
-> String
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
readBitmapFile Display
display Window
d String
filename =
String
-> (CString
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a. String -> (CString -> IO a) -> IO a
withCString String
filename ((CString
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> (CString
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ \ CString
c_filename ->
(Ptr Dimension
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Dimension
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> (Ptr Dimension
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ \ Ptr Dimension
width_return ->
(Ptr Dimension
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Dimension
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> (Ptr Dimension
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ \ Ptr Dimension
height_return ->
(Ptr Window
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> (Ptr Window
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ \ Ptr Window
bitmap_return ->
(Ptr FocusMode
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> (Ptr FocusMode
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
x_hot_return ->
(Ptr FocusMode
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> (Ptr FocusMode
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
y_hot_return -> do
FocusMode
rv <- Display
-> Window
-> CString
-> Ptr Dimension
-> Ptr Dimension
-> Ptr Window
-> Ptr FocusMode
-> Ptr FocusMode
-> IO FocusMode
xReadBitmapFile Display
display Window
d CString
c_filename Ptr Dimension
width_return Ptr Dimension
height_return
Ptr Window
bitmap_return Ptr FocusMode
x_hot_return Ptr FocusMode
y_hot_return
Dimension
width <- Ptr Dimension -> IO Dimension
forall a. Storable a => Ptr a -> IO a
peek Ptr Dimension
width_return
Dimension
height <- Ptr Dimension -> IO Dimension
forall a. Storable a => Ptr a -> IO a
peek Ptr Dimension
height_return
Window
bitmap <- Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
bitmap_return
FocusMode
x_hot <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
x_hot_return
FocusMode
y_hot <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
y_hot_return
let m_x_hot :: Maybe FocusMode
m_x_hot | FocusMode
x_hot FocusMode -> FocusMode -> Bool
forall a. Eq a => a -> a -> Bool
== -FocusMode
1 = Maybe FocusMode
forall a. Maybe a
Nothing
| Bool
otherwise = FocusMode -> Maybe FocusMode
forall a. a -> Maybe a
Just FocusMode
x_hot
m_y_hot :: Maybe FocusMode
m_y_hot | FocusMode
y_hot FocusMode -> FocusMode -> Bool
forall a. Eq a => a -> a -> Bool
== -FocusMode
1 = Maybe FocusMode
forall a. Maybe a
Nothing
| Bool
otherwise = FocusMode -> Maybe FocusMode
forall a. a -> Maybe a
Just FocusMode
y_hot
case FocusMode
rv of
FocusMode
0 -> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ (Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
forall a b. b -> Either a b
Right (Dimension
width, Dimension
height, Window
bitmap, Maybe FocusMode
m_x_hot, Maybe FocusMode
m_y_hot)
FocusMode
1 -> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ String
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapOpenFailed"
FocusMode
2 -> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ String
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapFileInvalid"
FocusMode
3 -> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ String
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
forall a b. a -> Either a b
Left String
"readBitmapFile: BitmapNoMemory"
FocusMode
_ -> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)))
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
-> IO
(Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode))
forall a b. (a -> b) -> a -> b
$ String
-> Either
String
(Dimension, Dimension, Window, Maybe FocusMode, Maybe FocusMode)
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 -> (FocusMode, FocusMode)
displayKeycodes Display
display =
IO (FocusMode, FocusMode) -> (FocusMode, FocusMode)
forall a. IO a -> a
unsafePerformIO (IO (FocusMode, FocusMode) -> (FocusMode, FocusMode))
-> IO (FocusMode, FocusMode) -> (FocusMode, FocusMode)
forall a b. (a -> b) -> a -> b
$ (IO () -> IO ())
-> (Ptr FocusMode -> Ptr FocusMode -> IO ())
-> IO (FocusMode, FocusMode)
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 FocusMode -> Ptr FocusMode -> IO ())
-> IO (FocusMode, FocusMode))
-> (Ptr FocusMode -> Ptr FocusMode -> IO ())
-> IO (FocusMode, FocusMode)
forall a b. (a -> b) -> a -> b
$ Display -> Ptr FocusMode -> Ptr FocusMode -> 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 :: Window -> String
keysymToString Window
keysym = IO String -> String
forall a. IO a -> a
unsafePerformIO (IO String -> String) -> IO String -> String
forall a b. (a -> b) -> a -> b
$ do
CString
c_str <- Window -> IO CString
xKeysymToString Window
keysym
CString -> IO String
peekCString CString
c_str
foreign import ccall unsafe "HsXlib.h XKeysymToString"
xKeysymToString :: KeySym -> IO CString
stringToKeysym :: String -> KeySym
stringToKeysym :: String -> Window
stringToKeysym String
str = IO Window -> Window
forall a. IO a -> a
unsafePerformIO (IO Window -> Window) -> IO Window -> Window
forall a b. (a -> b) -> a -> b
$
String -> (CString -> IO Window) -> IO Window
forall a. String -> (CString -> IO a) -> IO a
withCString String
str ((CString -> IO Window) -> IO Window)
-> (CString -> IO Window) -> IO Window
forall a b. (a -> b) -> a -> b
$ \ CString
c_str ->
CString -> IO Window
xStringToKeysym CString
c_str
foreign import ccall unsafe "HsXlib.h XStringToKeysym"
xStringToKeysym :: CString -> IO KeySym
noSymbol :: KeySym
noSymbol :: Window
noSymbol = Window
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
/= :: XComposeStatus -> XComposeStatus -> Bool
$c/= :: XComposeStatus -> XComposeStatus -> Bool
== :: XComposeStatus -> XComposeStatus -> Bool
$c== :: 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
min :: XComposeStatus -> XComposeStatus -> XComposeStatus
$cmin :: XComposeStatus -> XComposeStatus -> XComposeStatus
max :: XComposeStatus -> XComposeStatus -> XComposeStatus
$cmax :: XComposeStatus -> XComposeStatus -> XComposeStatus
>= :: XComposeStatus -> XComposeStatus -> Bool
$c>= :: XComposeStatus -> XComposeStatus -> Bool
> :: XComposeStatus -> XComposeStatus -> Bool
$c> :: XComposeStatus -> XComposeStatus -> Bool
<= :: XComposeStatus -> XComposeStatus -> Bool
$c<= :: XComposeStatus -> XComposeStatus -> Bool
< :: XComposeStatus -> XComposeStatus -> Bool
$c< :: XComposeStatus -> XComposeStatus -> Bool
compare :: XComposeStatus -> XComposeStatus -> Ordering
$ccompare :: XComposeStatus -> XComposeStatus -> Ordering
$cp1Ord :: Eq 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
showList :: [XComposeStatus] -> String -> String
$cshowList :: [XComposeStatus] -> String -> String
show :: XComposeStatus -> String
$cshow :: XComposeStatus -> String
showsPrec :: Int -> XComposeStatus -> String -> String
$cshowsPrec :: Int -> XComposeStatus -> String -> String
Show, Typeable, Typeable XComposeStatus
DataType
Constr
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 -> DataType
XComposeStatus -> Constr
(forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cXComposeStatus :: Constr
$tXComposeStatus :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
gmapMp :: (forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
gmapM :: (forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> XComposeStatus -> m XComposeStatus
gmapQi :: Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> XComposeStatus -> u
gmapQ :: (forall d. Data d => d -> u) -> XComposeStatus -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XComposeStatus -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XComposeStatus -> r
gmapT :: (forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
$cgmapT :: (forall b. Data b => b -> b) -> XComposeStatus -> XComposeStatus
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XComposeStatus)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XComposeStatus)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c XComposeStatus)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XComposeStatus)
dataTypeOf :: XComposeStatus -> DataType
$cdataTypeOf :: XComposeStatus -> DataType
toConstr :: XComposeStatus -> Constr
$ctoConstr :: XComposeStatus -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XComposeStatus
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XComposeStatus -> c XComposeStatus
$cp1Data :: Typeable XComposeStatus
Data)
{-# LINE 904 "Graphics/X11/Xlib/Misc.hsc" #-}
lookupString :: XKeyEventPtr -> IO (Maybe KeySym, String)
lookupString :: XKeyEventPtr -> IO (Maybe Window, String)
lookupString XKeyEventPtr
event_ptr =
Int
-> (CString -> IO (Maybe Window, String))
-> IO (Maybe Window, String)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
100 ((CString -> IO (Maybe Window, String))
-> IO (Maybe Window, String))
-> (CString -> IO (Maybe Window, String))
-> IO (Maybe Window, String)
forall a b. (a -> b) -> a -> b
$ \ CString
buf ->
(Ptr Window -> IO (Maybe Window, String))
-> IO (Maybe Window, String)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Window -> IO (Maybe Window, String))
-> IO (Maybe Window, String))
-> (Ptr Window -> IO (Maybe Window, String))
-> IO (Maybe Window, String)
forall a b. (a -> b) -> a -> b
$ \ Ptr Window
keysym_return -> do
FocusMode
n <- XKeyEventPtr
-> CString
-> FocusMode
-> Ptr Window
-> Ptr XComposeStatus
-> IO FocusMode
xLookupString XKeyEventPtr
event_ptr CString
buf FocusMode
100 Ptr Window
keysym_return Ptr XComposeStatus
forall a. Ptr a
nullPtr
String
str <- CStringLen -> IO String
peekCStringLen (CString
buf, FocusMode -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral FocusMode
n)
Window
keysym <- Ptr Window -> IO Window
forall a. Storable a => Ptr a -> IO a
peek Ptr Window
keysym_return
(Maybe Window, String) -> IO (Maybe Window, String)
forall (m :: * -> *) a. Monad m => a -> m a
return (if Window
keysym Window -> Window -> Bool
forall a. Eq a => a -> a -> Bool
== Window
noSymbol then Maybe Window
forall a. Maybe a
Nothing else Window -> Maybe Window
forall a. a -> Maybe a
Just Window
keysym, String
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 -> Window -> IO String
getIconName Display
display Window
w =
(Ptr CString -> IO String) -> IO String
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CString -> IO String) -> IO String)
-> (Ptr CString -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr CString
icon_name_return -> do
String -> IO FocusMode -> IO ()
throwIfZero String
"getIconName" (IO FocusMode -> IO ()) -> IO FocusMode -> IO ()
forall a b. (a -> b) -> a -> b
$
Display -> Window -> Ptr CString -> IO FocusMode
xGetIconName Display
display Window
w Ptr CString
icon_name_return
CString
c_icon_name <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
icon_name_return
CString -> IO String
peekCString CString
c_icon_name
foreign import ccall unsafe "HsXlib.h XGetIconName"
xGetIconName :: Display -> Window -> Ptr CString -> IO Status
setIconName :: Display -> Window -> String -> IO ()
setIconName :: Display -> Window -> String -> IO ()
setIconName Display
display Window
w String
icon_name =
String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
icon_name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
c_icon_name ->
Display -> Window -> CString -> IO ()
xSetIconName Display
display Window
w CString
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
-> Window
-> Window
-> Color
-> Color
-> Dimension
-> Dimension
-> IO Window
createPixmapCursor Display
display Window
source Window
mask Color
fg_color Color
bg_color Dimension
x Dimension
y =
Color -> (Ptr Color -> IO Window) -> IO Window
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color ((Ptr Color -> IO Window) -> IO Window)
-> (Ptr Color -> IO Window) -> IO Window
forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
Color -> (Ptr Color -> IO Window) -> IO Window
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color ((Ptr Color -> IO Window) -> IO Window)
-> (Ptr Color -> IO Window) -> IO Window
forall a b. (a -> b) -> a -> b
$ \ Ptr Color
bg_color_ptr ->
Display
-> Window
-> Window
-> Ptr Color
-> Ptr Color
-> Dimension
-> Dimension
-> IO Window
xCreatePixmapCursor Display
display Window
source Window
mask Ptr Color
fg_color_ptr Ptr Color
bg_color_ptr Dimension
x Dimension
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
-> Window
-> Window
-> Glyph
-> Glyph
-> Color
-> Color
-> IO Window
createGlyphCursor Display
display Window
source_font Window
mask_font Glyph
source_char Glyph
mask_char
Color
fg_color Color
bg_color =
Color -> (Ptr Color -> IO Window) -> IO Window
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
fg_color ((Ptr Color -> IO Window) -> IO Window)
-> (Ptr Color -> IO Window) -> IO Window
forall a b. (a -> b) -> a -> b
$ \ Ptr Color
fg_color_ptr ->
Color -> (Ptr Color -> IO Window) -> IO Window
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Color
bg_color ((Ptr Color -> IO Window) -> IO Window)
-> (Ptr Color -> IO Window) -> IO Window
forall a b. (a -> b) -> a -> b
$ \ Ptr Color
bg_color_ptr ->
Display
-> Window
-> Window
-> Glyph
-> Glyph
-> Ptr Color
-> Ptr Color
-> IO Window
xCreateGlyphCursor Display
display Window
source_font Window
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 -> Window -> Color -> Color -> IO ()
recolorCursor Display
display Window
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 -> Window -> Ptr Color -> Ptr Color -> IO ()
xRecolorCursor Display
display Window
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 -> Window -> [Window] -> IO ()
setWMProtocols Display
display Window
w [Window]
protocols =
[Window] -> (Ptr Window -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [Window]
protocols ((Ptr Window -> IO ()) -> IO ()) -> (Ptr Window -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Ptr Window
protocol_array ->
Display -> Window -> Ptr Window -> FocusMode -> IO ()
xSetWMProtocols Display
display Window
w Ptr Window
protocol_array (Int -> FocusMode
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> FocusMode) -> Int -> FocusMode
forall a b. (a -> b) -> a -> b
$ [Window] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Window]
protocols)
foreign import ccall unsafe "HsXlib.h XSetWMProtocols"
xSetWMProtocols :: Display -> Window -> Ptr Atom -> CInt -> IO ()
allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a
allocaSetWindowAttributes :: (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 -> Window -> IO ()
set_background_pixmap = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> Window -> IO ()
set_background_pixel = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> Window -> IO ()
set_border_pixmap = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> Window -> IO ()
set_border_pixel = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> FocusMode -> IO ()
set_bit_gravity = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> FocusMode -> 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 -> FocusMode -> IO ()
set_win_gravity = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> FocusMode -> 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 -> FocusMode -> IO ()
set_backing_store = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> FocusMode -> 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 -> Window -> IO ()
set_backing_planes = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> Window -> IO ()
set_backing_pixel = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 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 -> Window -> IO ()
set_event_mask = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> Window -> IO ()
set_do_not_propagate_mask = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 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 -> Window -> IO ()
set_colormap = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> Window -> IO ()
set_cursor = (\Ptr SetWindowAttributes
hsc_ptr -> Ptr SetWindowAttributes -> Int -> Window -> 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 -> Window -> GC -> [Point] -> FocusMode -> IO ()
drawPoints Display
display Window
d GC
gc [Point]
points FocusMode
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
-> Window -> GC -> Ptr Point -> FocusMode -> FocusMode -> IO ()
xDrawPoints Display
display Window
d GC
gc Ptr Point
point_array (Int -> FocusMode
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
npoints) FocusMode
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 -> Window -> GC -> [Point] -> FocusMode -> IO ()
drawLines Display
display Window
d GC
gc [Point]
points FocusMode
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
-> Window -> GC -> Ptr Point -> FocusMode -> FocusMode -> IO ()
xDrawLines Display
display Window
d GC
gc Ptr Point
point_array (Int -> FocusMode
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
npoints) FocusMode
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 -> Window -> GC -> [Segment] -> IO ()
drawSegments Display
display Window
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 -> Window -> GC -> Ptr Segment -> FocusMode -> IO ()
xDrawSegments Display
display Window
d GC
gc Ptr Segment
segment_array (Int -> FocusMode
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 -> Window -> GC -> [Rectangle] -> IO ()
drawRectangles Display
display Window
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 -> Window -> GC -> Ptr Rectangle -> FocusMode -> IO ()
xDrawRectangles Display
display Window
d GC
gc Ptr Rectangle
rectangle_array (Int -> FocusMode
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 -> Window -> GC -> [Arc] -> IO ()
drawArcs Display
display Window
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 -> Window -> GC -> Ptr Arc -> FocusMode -> IO ()
xDrawArcs Display
display Window
d GC
gc Ptr Arc
arc_array (Int -> FocusMode
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 -> Window -> GC -> [Rectangle] -> IO ()
fillRectangles Display
display Window
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 -> Window -> GC -> Ptr Rectangle -> FocusMode -> IO ()
xFillRectangles Display
display Window
d GC
gc Ptr Rectangle
rectangle_array (Int -> FocusMode
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
-> Window -> GC -> [Point] -> FocusMode -> FocusMode -> IO ()
fillPolygon Display
display Window
d GC
gc [Point]
points FocusMode
shape FocusMode
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
-> Window
-> GC
-> Ptr Point
-> FocusMode
-> FocusMode
-> FocusMode
-> IO ()
xFillPolygon Display
display Window
d GC
gc Ptr Point
point_array (Int -> FocusMode
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
npoints) FocusMode
shape FocusMode
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 -> Window -> GC -> [Arc] -> IO ()
fillArcs Display
display Window
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 -> Window -> GC -> Ptr Arc -> FocusMode -> IO ()
xFillArcs Display
display Window
d GC
gc Ptr Arc
arc_array (Int -> FocusMode
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 -> Window -> GC -> Position -> Position -> String -> IO ()
drawString Display
display Window
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
$ \ (CString
c_str, Int
len) ->
Display
-> Window
-> GC
-> Position
-> Position
-> CString
-> FocusMode
-> IO ()
xDrawString Display
display Window
d GC
gc Position
x Position
y CString
c_str (Int -> FocusMode
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 -> Window -> GC -> Position -> Position -> String -> IO ()
drawImageString Display
display Window
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
$ \ (CString
c_str, Int
len) ->
Display
-> Window
-> GC
-> Position
-> Position
-> CString
-> FocusMode
-> IO ()
xDrawImageString Display
display Window
d GC
gc Position
x Position
y CString
c_str (Int -> FocusMode
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 -> FocusMode -> IO ()
storeBuffer Display
display String
bytes FocusMode
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
$ \ (CString
c_bytes, Int
nbytes) ->
String -> IO FocusMode -> IO ()
throwIfZero String
"storeBuffer" (IO FocusMode -> IO ()) -> IO FocusMode -> IO ()
forall a b. (a -> b) -> a -> b
$
Display -> CString -> FocusMode -> FocusMode -> IO FocusMode
xStoreBuffer Display
display CString
c_bytes (Int -> FocusMode
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nbytes) FocusMode
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
$ \ (CString
c_bytes, Int
nbytes) ->
String -> IO FocusMode -> IO ()
throwIfZero String
"storeBytes" (IO FocusMode -> IO ()) -> IO FocusMode -> IO ()
forall a b. (a -> b) -> a -> b
$
Display -> CString -> FocusMode -> IO FocusMode
xStoreBytes Display
display CString
c_bytes (Int -> FocusMode
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 -> FocusMode -> IO String
fetchBuffer Display
display FocusMode
buffer =
(Ptr FocusMode -> IO String) -> IO String
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode -> IO String) -> IO String)
-> (Ptr FocusMode -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
nbytes_return -> do
CString
c_bytes <- String -> IO CString -> IO CString
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"fetchBuffer" (IO CString -> IO CString) -> IO CString -> IO CString
forall a b. (a -> b) -> a -> b
$
Display -> Ptr FocusMode -> FocusMode -> IO CString
xFetchBuffer Display
display Ptr FocusMode
nbytes_return FocusMode
buffer
FocusMode
nbytes <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
nbytes_return
String
bytes <- CStringLen -> IO String
peekCStringLen (CString
c_bytes, (FocusMode -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral FocusMode
nbytes))
FocusMode
_ <- CString -> IO FocusMode
forall a. Ptr a -> IO FocusMode
xFree CString
c_bytes
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
bytes
foreign import ccall unsafe "HsXlib.h XFetchBuffer"
xFetchBuffer :: Display -> Ptr CInt -> CInt -> IO CString
fetchBytes :: Display -> IO String
fetchBytes :: Display -> IO String
fetchBytes Display
display =
(Ptr FocusMode -> IO String) -> IO String
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr FocusMode -> IO String) -> IO String)
-> (Ptr FocusMode -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \ Ptr FocusMode
nbytes_return -> do
CString
c_bytes <- String -> IO CString -> IO CString
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"fetchBytes" (IO CString -> IO CString) -> IO CString -> IO CString
forall a b. (a -> b) -> a -> b
$
Display -> Ptr FocusMode -> IO CString
xFetchBytes Display
display Ptr FocusMode
nbytes_return
FocusMode
nbytes <- Ptr FocusMode -> IO FocusMode
forall a. Storable a => Ptr a -> IO a
peek Ptr FocusMode
nbytes_return
String
bytes <- CStringLen -> IO String
peekCStringLen (CString
c_bytes, (FocusMode -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral FocusMode
nbytes))
FocusMode
_ <- CString -> IO FocusMode
forall a. Ptr a -> IO FocusMode
xFree CString
c_bytes
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
bytes
foreign import ccall unsafe "HsXlib.h XFetchBytes"
xFetchBytes :: Display -> Ptr CInt -> IO CString
rotateBuffers :: Display -> CInt -> IO ()
rotateBuffers :: Display -> FocusMode -> IO ()
rotateBuffers Display
display FocusMode
rot =
String -> IO FocusMode -> IO ()
throwIfZero String
"rotateBuffers" (IO FocusMode -> IO ()) -> IO FocusMode -> IO ()
forall a b. (a -> b) -> a -> b
$
Display -> FocusMode -> IO FocusMode
xRotateBuffers Display
display FocusMode
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
/= :: XTextProperty -> XTextProperty -> Bool
$c/= :: XTextProperty -> XTextProperty -> Bool
== :: XTextProperty -> XTextProperty -> Bool
$c== :: 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
min :: XTextProperty -> XTextProperty -> XTextProperty
$cmin :: XTextProperty -> XTextProperty -> XTextProperty
max :: XTextProperty -> XTextProperty -> XTextProperty
$cmax :: XTextProperty -> XTextProperty -> XTextProperty
>= :: XTextProperty -> XTextProperty -> Bool
$c>= :: XTextProperty -> XTextProperty -> Bool
> :: XTextProperty -> XTextProperty -> Bool
$c> :: XTextProperty -> XTextProperty -> Bool
<= :: XTextProperty -> XTextProperty -> Bool
$c<= :: XTextProperty -> XTextProperty -> Bool
< :: XTextProperty -> XTextProperty -> Bool
$c< :: XTextProperty -> XTextProperty -> Bool
compare :: XTextProperty -> XTextProperty -> Ordering
$ccompare :: XTextProperty -> XTextProperty -> Ordering
$cp1Ord :: Eq 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
showList :: [XTextProperty] -> String -> String
$cshowList :: [XTextProperty] -> String -> String
show :: XTextProperty -> String
$cshow :: XTextProperty -> String
showsPrec :: Int -> XTextProperty -> String -> String
$cshowsPrec :: Int -> XTextProperty -> String -> String
Show, Typeable, Typeable XTextProperty
DataType
Constr
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 -> DataType
XTextProperty -> Constr
(forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cXTextProperty :: Constr
$tXTextProperty :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
gmapMp :: (forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
gmapM :: (forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> XTextProperty -> m XTextProperty
gmapQi :: Int -> (forall d. Data d => d -> u) -> XTextProperty -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> XTextProperty -> u
gmapQ :: (forall d. Data d => d -> u) -> XTextProperty -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> XTextProperty -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> XTextProperty -> r
gmapT :: (forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
$cgmapT :: (forall b. Data b => b -> b) -> XTextProperty -> XTextProperty
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XTextProperty)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c XTextProperty)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c XTextProperty)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c XTextProperty)
dataTypeOf :: XTextProperty -> DataType
$cdataTypeOf :: XTextProperty -> DataType
toConstr :: XTextProperty -> Constr
$ctoConstr :: XTextProperty -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c XTextProperty
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> XTextProperty -> c XTextProperty
$cp1Data :: Typeable XTextProperty
Data)
{-# LINE 1280 "Graphics/X11/Xlib/Misc.hsc" #-}
setTextProperty :: Display -> Window -> String -> Atom -> IO ()
setTextProperty :: Display -> Window -> String -> Window -> IO ()
setTextProperty Display
display Window
w String
value Window
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
$ \ (CString
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 -> CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
0) Ptr XTextProperty
text_prop CString
c_value
{-# LINE 1287 "Graphics/X11/Xlib/Misc.hsc" #-}
(\Ptr XTextProperty
hsc_ptr -> Ptr XTextProperty -> Int -> Window -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
8) Ptr XTextProperty
text_prop Window
sTRING
{-# LINE 1288 "Graphics/X11/Xlib/Misc.hsc" #-}
(\Ptr XTextProperty
hsc_ptr -> Ptr XTextProperty -> Int -> FocusMode -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
16) Ptr XTextProperty
text_prop (FocusMode
8::CInt)
{-# LINE 1289 "Graphics/X11/Xlib/Misc.hsc" #-}
(\Ptr XTextProperty
hsc_ptr -> Ptr XTextProperty -> Int -> Dimension -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XTextProperty
hsc_ptr Int
24) Ptr XTextProperty
text_prop (Int -> Dimension
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
value_len::Word32)
{-# LINE 1290 "Graphics/X11/Xlib/Misc.hsc" #-}
Display -> Window -> Ptr XTextProperty -> Window -> IO ()
xSetTextProperty Display
display Window
w Ptr XTextProperty
text_prop Window
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 :: (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
a <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b
b <- Ptr b -> IO b
forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
(a, b) -> IO (a, b)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b)
outParameters3 :: (Storable a, Storable b, Storable c) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> Ptr c -> IO r) -> IO (a,b,c)
outParameters3 :: (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
a <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b
b <- Ptr b -> IO b
forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
c
c <- Ptr c -> IO c
forall a. Storable a => Ptr a -> IO a
peek Ptr c
c_return
(a, b, c) -> IO (a, b, c)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c)
outParameters4 :: (Storable a, Storable b, Storable c, Storable d) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> Ptr c -> Ptr d -> IO r) ->
IO (a,b,c,d)
outParameters4 :: (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
a <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b
b <- Ptr b -> IO b
forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
c
c <- Ptr c -> IO c
forall a. Storable a => Ptr a -> IO a
peek Ptr c
c_return
d
d <- Ptr d -> IO d
forall a. Storable a => Ptr a -> IO a
peek Ptr d
d_return
(a, b, c, d) -> IO (a, b, c, d)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d)
outParameters7 :: (Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g) =>
(IO r -> IO ()) -> (Ptr a -> Ptr b -> Ptr c -> Ptr d -> Ptr e -> Ptr f -> Ptr g -> IO r) ->
IO (a,b,c,d,e,f,g)
outParameters7 :: (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
a <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
a_return
b
b <- Ptr b -> IO b
forall a. Storable a => Ptr a -> IO a
peek Ptr b
b_return
c
c <- Ptr c -> IO c
forall a. Storable a => Ptr a -> IO a
peek Ptr c
c_return
d
d <- Ptr d -> IO d
forall a. Storable a => Ptr a -> IO a
peek Ptr d
d_return
e
e <- Ptr e -> IO e
forall a. Storable a => Ptr a -> IO a
peek Ptr e
e_return
f
f <- Ptr f -> IO f
forall a. Storable a => Ptr a -> IO a
peek Ptr f
f_return
g
g <- Ptr g -> IO g
forall a. Storable a => Ptr a -> IO a
peek Ptr g
g_return
(a, b, c, d, e, f, g) -> IO (a, b, c, d, e, f, g)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g)